Trouble understanding records and existential types

Hi, A while back I asked about OO programming in Haskell and discovered existential types. I understood that existential types allowed me to write heterogeneous lists which seemed sufficient at the time. Now trying to combine those ideas with records: data AnyNode = forall a. Node a => AnyNode a class Node -- yadda yadda data Branch = Branch { name :: String, description :: String, children :: [AnyNode] } data Leaf = Leaf { name :: String, value :: String } The problem here is I can't use the same 'name' field for both Branch and Leaf. Ideally I'd like the name field in the Node class, but it doesn't seem that Haskell classes are for that sort of thing. -John

On Jan 24, 2007, at 19:34 , John Ky wrote:
class Node -- yadda yadda
data Branch = Branch { name :: String, description :: String, children :: [AnyNode] } data Leaf = Leaf { name :: String, value :: String }
The problem here is I can't use the same 'name' field for both Branch and Leaf. Ideally I'd like the name field in the Node class, but it doesn't seem that Haskell classes are for that sort of thing.
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 is legal -- leaving Node available if you still need it (b) I think you *can* do this with a class: class Node a where name :: a -> String data Branch = Branch { brName :: String, ... } data Leaf = Leaf { lName :: String, ... } instance Node Branch where name = brName instance Node Leaf where name = lName -- brandon s. allbery [linux,solaris,freebsd,perl] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

On 1/25/07, Brandon S. Allbery KF8NH
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 is legal -- leaving Node available if you still need it
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] (b) I think you *can* do this with a class:
class Node a where name :: a -> String
data Branch = Branch { brName :: String, ... } data Leaf = Leaf { lName :: String, ... }
instance Node Branch where name = brName
instance Node Leaf where name = lName
Okay, though it's a lot more wordy. -John

On Jan 25, 2007, at 2:08 , John Ky wrote:
On 1/25/07, Brandon S. Allbery KF8NH
wrote: data ANode = Branch { name :: String, description :: String, children :: [AnyNode] } | Leaf { name :: String, value :: String } -- this reuse is legal -- leaving Node available if you still need it Would I be able to this?
getLeaves :: ANode -> [Leaf]
Leaf is a data constructor, not a type. Your second one:
getLeaves :: ANode -> [ANode]
is correct. If you want the type system to ensure they are only leaves, then indeed you can't use this method.
(b) I think you *can* do this with a class:
class Node a where name :: a -> String
data Branch = Branch { brName :: String, ... } data Leaf = Leaf { lName :: String, ... }
instance Node Branch where name = brName
instance Node Leaf where name = lName
Okay, though it's a lot more wordy.
How so? You were declaring the class and instances anyway; I simply defined a new method to go into it and renamed the constructor fields to obey Haskell's rules, but you will probably be using the class method so your code won't care about the latter. -- brandon s. allbery [linux,solaris,freebsd,perl] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

Let me try this option and see how I go.
Thanks
-John
On 1/25/07, Brandon S. Allbery KF8NH
(b) I think you *can* do this with a class:
class Node a where name :: a -> String
data Branch = Branch { brName :: String, ... } data Leaf = Leaf { lName :: String, ... }
instance Node Branch where name = brName
instance Node Leaf where name = lName
Okay, though it's a lot more wordy.
How so? You were declaring the class and instances anyway; I simply defined a new method to go into it and renamed the constructor fields to obey Haskell's rules, but you will probably be using the class method so your code won't care about the latter.
-- brandon s. allbery [linux,solaris,freebsd,perl] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

On Thursday, January 25, 2007 7:08 AM, John Ky wrote:
On 1/25/07, Brandon S. Allbery KF8NH
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. -- http://www.metamilk.com

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
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.

Chris Kuklewicz wrote:
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]
Thanks Chris - that's really neat! I see it's the explicit wrapping and unwrapping of the existential that solves the typechecking problem, and the use of newtype ensures there's no run-time penalty for this. Also the wrapping of the existential allowed higher order functions to be used making the code much neater. Regarding the question of why in the original example the typechecker was trying to match (forall b.ANode b) against (ANode a) and not (ANode IsLeaf), I think the answer is probably that the typechecker first finds the MGU of the types occupying the same position in all the left hand sides first, then it tries to match this against the declared type at that position, whereas for the original example to have typechecked it would have to treat each equation separately. Anyway it's now an irrelevant point given the clarity of your solution which compiles fine, Best regards, Brian. -- http://www.metamilk.com

Brian Hulley wrote:
Chris Kuklewicz wrote:
This is how I would write getLeaves, based on your GADT:
data IsLeaf data IsBranch
newtype Node = Node { getNode :: (forall c. ANode c) } [snip] Thanks Chris - that's really neat! I see it's the explicit wrapping and unwrapping of the existential that solves the typechecking problem,
Actually, Node is universally quantified. This makes it not inhabitated given the ANode GADT. So, you can consume a Node, but you can not produce a non-bottom one. Existential quantification version: data IsLeaf data IsBranch data Node = forall c . Node ( 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' rest getLeaves x@(Leaf {}) = [x] getLeaves' :: Node -> [ANode IsLeaf] getLeaves' (Node x) = getLeaves x Regards, Zun.

John Ky wrote:
On 1/25/07, BBrraannddoonn SS.. AAllllbbeerryy KKFF88NNHH <_a_l_l_b_e_r_y_@_e_c_e_._c_m_u_._e_d_u> 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 is legal -- leaving Node available if you still need it
Would I be able to this?
getLeaves :: ANode -> [Leaf]
data Branch = Branch { name :: String, description :: String, children :: [AnyNode] } data Leaf = Leaf { name :: String, value :: String } data AnyNode = Either Branch Leaf Now if you absolutely insist on overloading the 'name' identifier, you can do this: data Branch = Branch { brName :: String, description :: String, children :: [AnyNode] } data Leaf = Leaf { lName :: String, value :: String } data AnyNode = Either Branch Leaf class HasName a where name :: a -> Name instance HasName Branch where name = brName instance HasName Leaf where name = lName instance HasName AnyNode where name = either brName lName Okay, you lose record update and construction syntax for AnyNode, but I don't think that's so much of a loss. On a side note, all this has nothing to do with OOP. If you wanted to simulate objects, you would "replace case by polymorphism", but I can't demonstrate how to do that, since none of your "objects" has any methods. -Udo. -- "Technology is a word that describes something that doesn't work yet." -- Douglas Adams, JavaOne keynote, 1999

On Thu, Jan 25, 2007 at 11:34:55AM +1100, John Ky wrote:
A while back I asked about OO programming in Haskell and discovered existential types. I understood that existential types allowed me to write heterogeneous lists which seemed sufficient at the time.
Now trying to combine those ideas with records:
data AnyNode = forall a. Node a => AnyNode a
class Node -- yadda yadda
data Branch = Branch { name :: String, description :: String, children :: [AnyNode] } data Leaf = Leaf { name :: String, value :: String }
The problem here is I can't use the same 'name' field for both Branch and Leaf. Ideally I'd like the name field in the Node class, but it doesn't seem that Haskell classes are for that sort of thing.
They are - it's the record system that's biting you. Haskell-98 style records are widely acknowledged as sucking, and there are something like half a dozen proposals all of which are widely acknowledged as vastly superior. Expect to be stuck with H98 records for the remainder of time; see "bikeshed". (Plea to SPJ: stop deliberating and flip a coin!) Anyway, in the one of the proposals whose syntax I can mostly remember: data AnyNode = forall a. a \ name => AnyNode { a | name :: String } data Branch = Branch { name :: String, description :: String, children :: [AnyNode] } data Leaf = Leaf { name :: String, value :: String }

On Wed, Jan 24, 2007 at 05:03:18PM -0800, Stefan O'Rear wrote:
Haskell-98 style records are widely acknowledged as sucking, and there are something like half a dozen proposals all of which are widely acknowledged as vastly superior. Expect to be stuck with H98 records for the remainder of time; see "bikeshed".
actually, the problem is that we keep calling them records. Haskell 98 records are actually labeled fields, not records, and as labeled fields they perform just fine. Not that records or named tuples or whatever you like to call them wouldn't be useful but they would likely be something in addition to labeled fields, not replacing it. (Not that the current labeled field mechanism couldn't be improved some.) personally, something based on Daan's scoped labels proposal is the clear leader of the bunch. John -- John Meacham - ⑆repetae.net⑆john⑈

John Meacham wrote:
On Wed, Jan 24, 2007 at 05:03:18PM -0800, Stefan O'Rear wrote:
Haskell-98 style records are widely acknowledged as sucking, and there are something like half a dozen proposals all of which are widely acknowledged as vastly superior. Expect to be stuck with H98 records for the remainder of time; see "bikeshed".
actually, the problem is that we keep calling them records. Haskell 98 records are actually labeled fields, not records, and as labeled fields they perform just fine.
Not that records or named tuples or whatever you like to call them wouldn't be useful but they would likely be something in addition to labeled fields, not replacing it. (Not that the current labeled field mechanism couldn't be improved some.)
personally, something based on Daan's scoped labels proposal is the clear leader of the bunch.
John
I also really liked Daan's "Extensible records with scoped labels", which is available at http://www.cs.uu.nl/~daan/pubs.html#scopedlabels for those who still have not read it. The system seems very simple, but also seems to have required moving beyond an imperative viewpoint to come up with.
participants (8)
-
Brandon S. Allbery KF8NH
-
Brian Hulley
-
Chris Kuklewicz
-
John Ky
-
John Meacham
-
Roberto Zunino
-
Stefan O'Rear
-
Udo Stenzel