[Haskell-cafe] Help with associated types
Niklas Broberg
niklas.broberg at gmail.com
Sat Apr 19 08:57:23 EDT 2008
Hi Emil,
On 4/17/08, Emil Axelsson <emax at cs.chalmers.se> wrote:
> 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))
> ...
>
the problem here is that Leaf p doesn't determine p, e.g. there can be
many different types p for which Leaf p = Int. It has nothing to do
with the Struct type.
> What's the easiest way to encode that pb can be inferred from (Struct pb)
> and (Leaf pb)?
If you want the dependency Leaf p -> p then Leaf needs to be
injective, i.e. you need to use an accociated datatype rather than
just a type. Here's a sketch that shows this:
class Port p
where
data Leaf p -- note the use of data here
type Struct p
toList :: p -> [Leaf p]
fromList :: [Leaf p] -> p
instance Port Int
where
newtype Leaf Int = IntLeaf Int
type Struct Int = ()
toList a = [IntLeaf a]
fromList [IntLeaf a] = a
instance Port Bool
where
newtype Leaf Bool = BoolLeaf Bool
type Struct Bool = ()
toList a = [BoolLeaf a]
fromList [BoolLeaf a] = a
mapPort ::
( Port pa
, Port pb
, Struct pa ~ Struct pb
) =>
(Leaf pa -> Leaf pb) -> (pa -> pb)
mapPort f = fromList . map f . toList
The problem now is of course that the arguments to f will now be a lot
more complex, since the Leaf type is more complex. So to call this you
would have to say
*Port> let f (IntLeaf n) = BoolLeaf (even n) in mapPort f 1
False
Not very pretty, but that's the way it goes if you want that
dependency. So in the general case,
> If I have a class with some dependencies, say
>
> a -> ..., b c -> ...
>
> Is it possible to encode this using associated types without having all of a, b
> and c as class parameters?
Yes it can be done, if you use associated *datatypes* instead of
associated types. But as you can see, it introduces extra overhead.
Cheers,
/Niklas
More information about the Haskell-Cafe
mailing list