[Haskell-cafe] Mutually recursive types?

Ryan Ingram ryani.spam at gmail.com
Wed Apr 16 21:26:27 EDT 2008


minor correction:

test = and [empty, empty]

On 4/16/08, Ryan Ingram <ryani.spam at gmail.com> 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 <ronwalf at umd.edu> 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 at haskell.org
> > http://www.haskell.org/mailman/listinfo/haskell-cafe
> >
>


More information about the Haskell-Cafe mailing list