[Haskell-cafe] Help with associated types
Emil Axelsson
emax at cs.chalmers.se
Thu Apr 17 08:18:36 EDT 2008
Hello!
I'm trying to rewrite some FD classes to use associated types instead. The Port
class is for type structures whose leaves have the same type:
class Port p
where
type Leaf p
type Struct p
toList :: p -> [Leaf p]
fromList :: [Leaf p] -> p
(Leaf p) gives the leaf type, and (Struct p) gives a canonical representation of
the structure regardless of leaf type. Here we just instantiate two leaf types:
instance Port Int
where
type Leaf Int = Int
type Struct Int = ()
toList a = [a]
fromList [a] = a
instance Port Bool
where
type Leaf Bool = Bool
type Struct Bool = ()
toList a = [a]
fromList [a] = a
There's also a function for mapping over ports:
mapPort ::
( Port pa
, Port pb
, Struct pa ~ Struct pb
) =>
(Leaf pa -> Leaf pb) -> (pa -> pb)
mapPort f = fromList . map f . toList
The equality constraint makes sure that we're mapping between equal structures.
When I try to run this, I get:
*Main> mapPort even (5::Int)
<interactive>:1:8:
No instance for (Integral (Leaf Int))
...
because as it stands, mapPort is not able to infer (pb = Bool) from (Struct pb =
()) and (Leaf pb = Bool).
What's the easiest way to encode that pb can be inferred from (Struct pb) and
(Leaf pb)?
Thanks,
/ Emil
PS.
I used to have a class
class SameStruct pa a pb b | pa -> a, pa b -> pb, pb -> b, pb a -> pa
In the example above, we'd have pa=Int and b==Bool, so the second dependeny
would infer pb=Bool.
More information about the Haskell-Cafe
mailing list