[Haskell-cafe] Trouble understanding records and existential types

Chris Kuklewicz haskell at list.mightyreason.com
Thu Jan 25 06:04:49 EST 2007


This is how I would write getLeaves, based on your GADT:

> data IsLeaf
> data IsBranch
> 
> newtype Node = Node { getNode :: (forall c. ANode c) }
> 
> data ANode :: * -> * where
>     Branch :: String -> String -> (ANode a,ANode b) -> [Node] -> ANode IsBranch
>     Leaf :: String -> String -> ANode IsLeaf
> 
> getLeaves :: ANode a -> [ANode IsLeaf]
> getLeaves (Branch _ _ (l1,l2) rest) = getLeaves l1 ++ getLeaves l2 ++ concatMap (getLeaves.getNode) rest
> getLeaves x@(Leaf {}) = [x]


Brian Hulley wrote:
> On Thursday, January 25, 2007 7:08 AM, John Ky wrote:
>>> On 1/25/07, Brandon S. Allbery KF8NH <allbery at ece.cmu.edu> wrote:
>>> I'm probably missing something, but:
>>>
>>> (a) Why not:
>>>
>>> data ANode
>>>         = Branch { name :: String, description :: String,
>>>                                     children :: [AnyNode] }
>>>           | Leaf { name :: String, value :: String } -- this reuse
>>
>> Would I be able to this?
>>
>>   getLeaves :: ANode -> [Leaf]
>>
>> If not, is it the case that people generally don't bother and do this
>> instead?
>>
>>   getLeaves :: ANode -> [ANode]
> 
> As has been pointed out, Leaf is a data constructor not a type so you'd
> have to use [ANode].
> Inspired by the problem I tried a GADT:
> 
>    data IsLeaf
>    data IsBranch
> 
>    data ANode a where
>        Branch :: String -> String -> [forall b. ANode b] -> ANode IsBranch
>        Leaf :: String -> String -> ANode IsLeaf
> 
>    getLeaves :: ANode IsBranch -> [ANode IsLeaf]
>    getLeaves (Branch _ _ ls) = leaves ls
> 
>    leaves :: [forall b. ANode b] -> [ANode IsLeaf]
>    leaves (l@(Leaf _ _) : ls) = l : leaves ls
>    leaves (Branch _ _ ls : lls) = leaves ls ++ leaves lls
> 
> but unfortunately the above code generates the following error by GHC6.6:
> 
>    Couldn't match expected type `forall b. ANode b'
>        against inferred type `ANode a'
>    In the pattern: Leaf _ _
>    In the pattern: (l@(Leaf _ _)) : ls
>    In the definition of `leaves':
>        leaves ((l@(Leaf _ _)) : ls) = l : (leaves ls)
> 
> Just out of curiosity, does anyone know why the above code doesn't
> compile ie why is the inferred type for the pattern:
> 
>    Leaf _ _
> 
> (ANode a) and not (ANode IsLeaf)?
> 
> Thanks, Brian.



More information about the Haskell-Cafe mailing list