Re: [Haskell-cafe] Trouble understanding records and existential types

2007-01-27 Thread Roberto Zunino

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.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Trouble understanding records and existential types

2007-01-26 Thread Udo Stenzel
John Ky wrote:
> On 1/25/07, BBrraannddoonn SS.. AAllllbbeerryy 
> KKFF88NNHH <[EMAIL PROTECTED]> 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


signature.asc
Description: Digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Trouble understanding records and existential types

2007-01-25 Thread Brian Hulley

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 


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Trouble understanding records and existential types

2007-01-25 Thread John Ky

Let me try this option and see how I go.

Thanks

-John

On 1/25/07, Brandon S. Allbery KF8NH <[EMAIL PROTECTED]> wrote:


> (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] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH




___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Trouble understanding records and existential types

2007-01-25 Thread Chris Kuklewicz
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 <[EMAIL PROTECTED]> 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.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Trouble understanding records and existential types

2007-01-25 Thread Brian Hulley

On Thursday, January 25, 2007 7:08 AM, John Ky wrote:

On 1/25/07, Brandon S. Allbery KF8NH <[EMAIL PROTECTED]> 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 


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Trouble understanding records and existential types

2007-01-24 Thread Brandon S. Allbery KF8NH


On Jan 25, 2007, at 2:08 , John Ky wrote:


On 1/25/07, Brandon S. Allbery KF8NH <[EMAIL PROTECTED]> 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] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Trouble understanding records and existential types

2007-01-24 Thread John Ky

On 1/25/07, Brandon S. Allbery KF8NH <[EMAIL PROTECTED]> 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]

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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Trouble understanding records and existential types

2007-01-24 Thread Brandon S. Allbery KF8NH


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] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Trouble understanding records and existential types

2007-01-24 Thread John Ky

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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe