Re: [Haskell-cafe] Mutually recursive types?

2008-04-16 Thread Ryan Ingram
minor correction:

test = and [empty, empty]

On 4/16/08, Ryan Ingram <[EMAIL PROTECTED]> wrote:
> You probably want to look at this:
>   http://wadler.blogspot.com/2008/02/data-types-la-carte.html
> which refers to a paper about this exact problem.
>
> The main types you want are:
>   newtype Fix a = In { out :: a (Fix a) }
>   data (f :+: g) x = Inl (f x) | Inr (g x)
>
> Yes, you end up with a ton of constructors, but you can use typeclass
> machinery and "smart constructors" to help with this problem; see, for
> example, 
> http://www.haskell.org/pipermail/haskell-cafe/2008-February/040098.html
>
> With (:<:) and inj as defined by that post, you can end up with something 
> like:
>
> and :: (t :<: LogicalConnective) => [Fix t] -> Fix t
> and ps = In (inj (And ps))
>
> empty :: (t :<: BasicGoal) => Fix t
> empty = In (inj Empty)
>
> type Problem1 = Fix (LogicalConnective :+: BasicGoal)
>
> test :: Problem1
> test = and empty empty
>
>  -- ryan
>
> On 4/16/08, Ron Alford <[EMAIL PROTECTED]> wrote:
> > Here's the setup:
> > I have a series of problems that use various logical connectives.  The
> > problem is that they're not all the same.  So instead of creating one
> > giant datatype (or duplicating much code), I'd like to assemble them
> > like toy blocks.
> >
> > I've boiled down an example here:
> >
> > data LogicalConnective a =
> >Not a
> >| And [a]
> >| Or [a]
> >
> > data BasicGoal a =
> >Atomic String [Term]
> >| Empty
> >| Logical (LogicalConnective a)
> >deriving (Show, Eq)
> >
> > data PreferenceGoal1 =
> >Basic1 PreferenceGoal1
> >| Prefer1 PreferenceGoal1
> >
> > This works OK, but PreferenceGoal1 is a dead end.  I can't combine it
> > with other connectives.  So I try:
> >
> > data PreferenceGoal2 a =
> >Basic2  (PreferenceGoal2 a)
> >| Prefer2 (PreferenceGoal2 a)
> >
> > And this works fine, but seems impossible to explicitly type (ie,
> > there is nothing to substitute for 'a' in a type declaration).  Or am
> > I wrong?
> >
> > Also, it could be that this is just an ugly way to represent things
> > (it does require a huge number of constructors).  Any suggestions?
> >
> > -Ron
> > ___
> > 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] Mutually recursive types?

2008-04-16 Thread Ryan Ingram
You probably want to look at this:
   http://wadler.blogspot.com/2008/02/data-types-la-carte.html
which refers to a paper about this exact problem.

The main types you want are:
   newtype Fix a = In { out :: a (Fix a) }
   data (f :+: g) x = Inl (f x) | Inr (g x)

Yes, you end up with a ton of constructors, but you can use typeclass
machinery and "smart constructors" to help with this problem; see, for
example, http://www.haskell.org/pipermail/haskell-cafe/2008-February/040098.html

With (:<:) and inj as defined by that post, you can end up with something like:

and :: (t :<: LogicalConnective) => [Fix t] -> Fix t
and ps = In (inj (And ps))

empty :: (t :<: BasicGoal) => Fix t
empty = In (inj Empty)

type Problem1 = Fix (LogicalConnective :+: BasicGoal)

test :: Problem1
test = and empty empty

  -- ryan

On 4/16/08, Ron Alford <[EMAIL PROTECTED]> wrote:
> Here's the setup:
> I have a series of problems that use various logical connectives.  The
> problem is that they're not all the same.  So instead of creating one
> giant datatype (or duplicating much code), I'd like to assemble them
> like toy blocks.
>
> I've boiled down an example here:
>
> data LogicalConnective a =
>Not a
>| And [a]
>| Or [a]
>
> data BasicGoal a =
>Atomic String [Term]
>| Empty
>| Logical (LogicalConnective a)
>deriving (Show, Eq)
>
> data PreferenceGoal1 =
>Basic1 PreferenceGoal1
>| Prefer1 PreferenceGoal1
>
> This works OK, but PreferenceGoal1 is a dead end.  I can't combine it
> with other connectives.  So I try:
>
> data PreferenceGoal2 a =
>Basic2  (PreferenceGoal2 a)
>| Prefer2 (PreferenceGoal2 a)
>
> And this works fine, but seems impossible to explicitly type (ie,
> there is nothing to substitute for 'a' in a type declaration).  Or am
> I wrong?
>
> Also, it could be that this is just an ugly way to represent things
> (it does require a huge number of constructors).  Any suggestions?
>
> -Ron
> ___
> 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] Mutually recursive types?

2008-04-16 Thread Ron Alford
Here's the setup:
I have a series of problems that use various logical connectives.  The
problem is that they're not all the same.  So instead of creating one
giant datatype (or duplicating much code), I'd like to assemble them
like toy blocks.

I've boiled down an example here:

data LogicalConnective a =
Not a
| And [a]
| Or [a]

data BasicGoal a =
Atomic String [Term]
| Empty
| Logical (LogicalConnective a)
deriving (Show, Eq)

data PreferenceGoal1 =
Basic1 PreferenceGoal1
| Prefer1 PreferenceGoal1

This works OK, but PreferenceGoal1 is a dead end.  I can't combine it
with other connectives.  So I try:

data PreferenceGoal2 a =
Basic2  (PreferenceGoal2 a)
| Prefer2 (PreferenceGoal2 a)

And this works fine, but seems impossible to explicitly type (ie,
there is nothing to substitute for 'a' in a type declaration).  Or am
I wrong?

Also, it could be that this is just an ugly way to represent things
(it does require a huge number of constructors).  Any suggestions?

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


Re: [Haskell-cafe] mutually recursive types

2007-08-08 Thread Brent Yorgey
> Notice that Scenario depends on a list of steps and Step has a dependence
> with scenario. I know that this is a kind of "bad smell" in Haskell, are
> there any pattern or language idiom to deal with cyclical dependences?


Just a little something to add, this is not a "bad smell" at all... in fact,
recursive (including mutually recursive) data types are the bread and butter
of Haskell (and functional languages in general).  For example:

data BinTree a = Empty | Branch a (BinTree a) (BinTree a)

This says that a binary tree containing 'a's is either Empty, or a Branch
consisting of an 'a' and two binary trees.  This isn't stinky, it's quite
elegant.  Your Scenario and Step data types look just peachy from an
idiomatic point of view; the solution (as others have pointed out) is to use
data declarations rather than type synonyms.

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


Re: [Haskell-cafe] mutually recursive types

2007-08-08 Thread Tillmann Rendel

Rodrigo wrote:

type Scenario = (String, String, [Step])
type Step = (String, Scenario, String, String, String)


Recursive types are not supported by type-declarations. use data 
declarations instead:


  data Scenario = Scenario String String [Step]
  data Step = Step String Scenario String String String

As a general rule, data declaration are more approbiate then type 
declarations with a tuple on the right-hand-side. a type declarations 
introduces a type synonym, that is, a new name for an existing type. 
Data declarations introduce a new type. most of the time, you want new 
types, not more names for the same types. different names for the same 
thing lead to confusion, but different things for different usages lead 
to static type safety.


(But this is only a general rule, and sometimes you want exactly the 
behaviour of type synonyms, of course)


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


[Haskell-cafe] mutually recursive types

2007-08-08 Thread rodrigo.bonifacio
Hi, I am learning the haskell programming language and had tried to define the 
following types:

type Scenario = (String, String, [Step])
type Step = (String, Scenario, String, String, String)

Notice that Scenario depends on a list of steps and Step has a dependence with 
scenario. I know that this is a kind of "bad smell" in Haskell, are there 
any pattern or language idiom to deal with cyclical dependences?

Regards,

Rodrigo.





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