[Haskell-cafe] number-parameterized types and heterogeneous lists

Harald ROTTER harald.rotter at sagem.com
Fri Jun 20 08:01:13 EDT 2008


Dear Haskellers,

after reading Oleg Kiselyov's paper on number-parameterized types I started
to play around with
the class Digits that encodes decimal numbers in types. The "typed number"
10 would e.g. be defined as

      D1 $ D0 $ Sz

I wondered if it would be possible replace the expression above by a
heterogeneous list like

      [D1,D0]

so I tried to define

      data Digit = forall a b.(Digits a, Digits (b a)) => Digit (a -> b a)

Loading this into ghci yields:

:t Digit D0

<interactive>:1:0:
    Ambiguous type variable `a' in the constraint:
      `Digits a' arising from a use of `Digit' at <interactive>:1:0-7
    Probable fix: add a type signature that fixes these type variable(s)

Removing the type constraints in the definition of "Digit":

      data Digit = forall a b.Digit (a -> b a)

makes it work like this:

      :t Digit D0
      Digit D0 :: Digit

      :t [Digit D0, Digit D1]
      [Digit D0, Digit D1] :: [Digit]

"Digit", however, is far too general (it also includes e.g. \x -> [x]), but
I would like it to be restricted to the Digit class.

Any help is appreciated.

Thanks

Harald.


CODE:

module Test where

data D0 a = D0 a
data D1 a = D1 a
data D2 a = D2 a
data D3 a = D3 a
data D4 a = D4 a
data D5 a = D5 a
data D6 a = D6 a
data D7 a = D7 a
data D8 a = D8 a
data D9 a = D9 a

class Digits ds where
    d2num :: Num a => ds -> a -> a

data Sz = Sz    -- zero size
instance Digits Sz where
    d2num _ acc = acc

instance Digits ds => Digits (D0 ds) where
    d2num dds acc = d2num (t22 dds) (10*acc)
instance Digits ds => Digits (D1 ds) where
    d2num dds acc = d2num (t22 dds) (10*acc+1)
instance Digits ds => Digits (D2 ds) where
    d2num dds acc = d2num (t22 dds) (10*acc+2)
instance Digits ds => Digits (D3 ds) where
    d2num dds acc = d2num (t22 dds) (10*acc+3)
instance Digits ds => Digits (D4 ds) where
    d2num dds acc = d2num (t22 dds) (10*acc+4)
instance Digits ds => Digits (D5 ds) where
    d2num dds acc = d2num (t22 dds) (10*acc+5)
instance Digits ds => Digits (D6 ds) where
    d2num dds acc = d2num (t22 dds) (10*acc+6)
instance Digits ds => Digits (D7 ds) where
    d2num dds acc = d2num (t22 dds) (10*acc+7)
instance Digits ds => Digits (D8 ds) where
    d2num dds acc = d2num (t22 dds) (10*acc+8)
instance Digits ds => Digits (D9 ds) where
    d2num dds acc = d2num (t22 dds) (10*acc+9)

t22 :: f x -> x
t22 = undefined

--data Digit = forall a b.(Digits a, Digits (b a)) => Digit (a -> b a)
data Digit = forall a b.Digit (a -> b a)

-------------------------------------------------------------------------------------------------



" Ce courriel et les documents qui y sont attaches peuvent contenir des informations confidentielles. Si vous n'etes  pas le destinataire escompte, merci d'en informer l'expediteur immediatement et de detruire ce courriel  ainsi que tous les documents attaches de votre systeme informatique. Toute divulgation, distribution ou copie du present courriel et des documents attaches sans autorisation prealable de son emetteur est interdite." 

" This e-mail and any attached documents may contain confidential or proprietary information. If you are not the intended recipient, please advise the sender immediately and delete this e-mail and all attached documents from your computer system. Any unauthorised disclosure, distribution or copying hereof is prohibited."


More information about the Haskell-Cafe mailing list