[Haskell-cafe] Re: Cyclic data declarations

2009-08-04 Thread Heinrich Apfelmus
Job Vranish wrote:
 
 I think that in an ideal world haskell would have some way of allowing
 infinite types if you asked for them explicitly (say in the type signature
 somehow) and then just automatically wrap/unwrap everything with newtypes
 behind the scenes (well maybe in an ideal world it wouldn't have to do this
 either). This wouldn't change the underlying semantics, but would get rid of
 alot of messyness.
 
 Infinite types are possible, My toy language infers infinite types just fine
 :) and I think Ocaml has an option for them, but niether of those have type
 classes so I'm not sure how compatable the idea is with haskell in general.

There was a thread with a compelling reason against vanilla infinite
types some time ago:

http://thread.gmane.org/gmane.comp.lang.haskell.cafe/17103


Of course, you can have all the recursion you want by using  newtype ,
it's just that you need to annotate them with the extraneous
constructor. In fact, that's exactly the purpose of the constructor;
think of it as an aid for the type checker.


Regards,
apfelmus

--
http://apfelmus.nfshost.com

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


Re: [Haskell-cafe] Re: Cyclic data declarations

2009-08-04 Thread Job Vranish
In a lot of cases though annotating all the recursive aspects with newtypes
is a _royal_ pain, and is even worse if you want the datatypes to be
instances of common type classes like Functor, Applicative, etc... (try it
sometime)
I don't advocate allowing infinite types wholesale, just in specific cases
with a special annotation (like a type signature specifying the allowed
infinite type). I think this would be the best of both worlds.

- Job


On Tue, Aug 4, 2009 at 4:23 AM, Heinrich Apfelmus apfel...@quantentunnel.de
 wrote:

 Job Vranish wrote:
 
  I think that in an ideal world haskell would have some way of allowing
  infinite types if you asked for them explicitly (say in the type
 signature
  somehow) and then just automatically wrap/unwrap everything with newtypes
  behind the scenes (well maybe in an ideal world it wouldn't have to do
 this
  either). This wouldn't change the underlying semantics, but would get rid
 of
  alot of messyness.
 
  Infinite types are possible, My toy language infers infinite types just
 fine
  :) and I think Ocaml has an option for them, but niether of those have
 type
  classes so I'm not sure how compatable the idea is with haskell in
 general.

 There was a thread with a compelling reason against vanilla infinite
 types some time ago:

http://thread.gmane.org/gmane.comp.lang.haskell.cafe/17103


 Of course, you can have all the recursion you want by using  newtype ,
 it's just that you need to annotate them with the extraneous
 constructor. In fact, that's exactly the purpose of the constructor;
 think of it as an aid for the type checker.


 Regards,
 apfelmus

 --
 http://apfelmus.nfshost.com

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

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


Re: [Haskell-cafe] Re: Cyclic data declarations

2009-08-03 Thread Job Vranish
I ran into exactly the same problem while working on my own toy language :)

I used a fixed point datatype to solve it as well. This is really the best
way, as it lets your expression (or statment) type be a member of
functor/foldable/traversable, which is super handy. I made a graph module
that lets me convert any fixpointed functor into a graph, which made the
rest of that whole process much nicer. If you're interested in the graph
module, let me know :)

I think that in an ideal world haskell would have some way of allowing
infinite types if you asked for them explicitly (say in the type signature
somehow) and then just automatically wrap/unwrap everything with newtypes
behind the scenes (well maybe in an ideal world it wouldn't have to do this
either). This wouldn't change the underlying semantics, but would get rid of
alot of messyness.

Infinite types are possible, My toy language infers infinite types just fine
:) and I think Ocaml has an option for them, but niether of those have type
classes so I'm not sure how compatable the idea is with haskell in general.

- Job

On Sun, Aug 2, 2009 at 9:06 PM, Michal D. michal.dobrog...@gmail.comwrote:

 
newtype StmtRec = StmtRec (Stmt [StmtRec])
 

 That's pretty much were I threw in the towel last night. Except I had
 a bunch of places where I had to add the extra constructor statements.
 I wish there was a solution that didn't require these... they really
 butcher pattern matching clarity.

  will do. More generally, you can use
 
newtype Fix f = In { out :: f (Fix f) }
 
  and define
 
type StmtRec = Fix ([] `O` Stmt)
 
  where  O  denotes composition of functors
 
newtype O f g a = O (f (g a))
 

 Thanks for that! This provoked some thought on my part about what
 exactly is going on. I think I could solve this if I added some way to
 identify that a type parameter is actually referring to the whole
 type. Say we had a reserved word fixpoint for this. Then we'd have
 something like:

 data Stmt x = SIf x x

 then when we actually go to use it, it would be referred to as the type:

 Stmt [fixpoint]

 Which would get treated exactly like the data declaration:

 data Stmt = SIf [Stmt] [Stmt]

 I'll need to add the newtype declaration for the code but I'd be
 interested if anyone had further thoughts on this topic. I have an
 implementation of both approaches on a toy parser, but I doubt
 anyone's interested in seeing that.

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

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


[Haskell-cafe] Re: Cyclic data declarations

2009-08-02 Thread Heinrich Apfelmus
Michal D. wrote:
 I'm in the process of writing a toy compiler but I'm having some
 trouble trying to make my datatypes general. For example, using parsec
 I parse statements as:
 
 data Stmt = SIf Test [Stmt] [Stmt]   |   ...
 
 However, when it's time to create a control flow graph it would be
 nice to represent statements as (the Int's signify the node id's for
 either case of the if statement):
 
 data Stmt = SIf Test Int Int   |   ...

(I recommend to replace  Int  with something more descriptive, like

type Id = Int

)

 So, in a eureka moment I decided that this should be allowable with
 the following declaration:
 
 data Stmt link = SIf Test link link   |   ...
 
 Ofcourse, the problem is trying to declare the resulting type for
 parsing: parse - Stmt [Stmt [Stmt ]]. Any hints on whether
 there is a way to accomplish what I'm trying to do or do I have to
 bite the bullet and declare two seperate datatypes? I tried being
 clever and declaring a 'helper' type as type StmtRec = Stmt [StmtRec]
 but to no avail... GHC won't let it slide: Cycle in type synonym 
 declarations!

   newtype StmtRec = StmtRec (Stmt [StmtRec])

will do. More generally, you can use

   newtype Fix f = In { out :: f (Fix f) }

and define

   type StmtRec = Fix ([] `O` Stmt)

where  O  denotes composition of functors

   newtype O f g a = O (f (g a))


Introducing a parameter in  Stmt  like you did and tying the recursion
afterwards is a known technique, but I can't seem to find a wiki page
that concisely explains it right now.


Regards,
apfelmus

--
http://apfelmus.nfshost.com

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


Re: [Haskell-cafe] Re: Cyclic data declarations

2009-08-02 Thread Michal D.

   newtype StmtRec = StmtRec (Stmt [StmtRec])


That's pretty much were I threw in the towel last night. Except I had
a bunch of places where I had to add the extra constructor statements.
I wish there was a solution that didn't require these... they really
butcher pattern matching clarity.

 will do. More generally, you can use

   newtype Fix f = In { out :: f (Fix f) }

 and define

   type StmtRec = Fix ([] `O` Stmt)

 where  O  denotes composition of functors

   newtype O f g a = O (f (g a))


Thanks for that! This provoked some thought on my part about what
exactly is going on. I think I could solve this if I added some way to
identify that a type parameter is actually referring to the whole
type. Say we had a reserved word fixpoint for this. Then we'd have
something like:

data Stmt x = SIf x x

then when we actually go to use it, it would be referred to as the type:

Stmt [fixpoint]

Which would get treated exactly like the data declaration:

data Stmt = SIf [Stmt] [Stmt]

I'll need to add the newtype declaration for the code but I'd be
interested if anyone had further thoughts on this topic. I have an
implementation of both approaches on a toy parser, but I doubt
anyone's interested in seeing that.

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