[Haskell-cafe] Wouter-style expressions

Ron Alford ronwalf at volus.net
Wed Jun 4 02:21:45 EDT 2008


Here's something that should be an easy extension of Wouter's approach
to extensible datatypes, but I'm failing (possibly since it's 2:20am).
 I several classes of expressions I'm trying to represent (thus,
Wouter's approach), and  my first operation to implement over them is
printing.

Attached is a simplified version of what I'm doing.  Expressions are
composed of conjunctives (and) and atoms.  Atoms are composed of a
predicate string and a list of fillers (taken from 'Const' and 'Var').
 For example (in a lisp like syntax):
(and (pred c ?var1) (pred ?var1 ?var2))

To do this, I defined a 'Printable' class:
class Functor f => Printable f where
    exprDoc :: f t -> Doc

I think the 't' here will get me into trouble later.

Combinations of printable types are also printable:
instance (Printable f, Printable g) => Printable (f :+: g) where
    exprDoc (Inr x) = exprDoc x
    exprDoc (Inl y) = exprDoc y


Constants, variables, and atoms are defined to be printable:
instance Printable Var where
    exprDoc (Var name) = text ('?':name)

instance Printable Const where
    exprDoc (Const name) = text name

instance Printable f => Printable (Atomic (Expr f)) where
    exprDoc (Atomic p tl) = parens $ hsep $
        (text p) : (map (\ (In t) -> exprDoc t) tl)

But the obvious definition for conjunction doesn't work:
instance Printable And where
    exprDoc (And el) = sep (map exprDoc el)

GHC barfs, throwing:
Couldn't match expected type `f t' against inferred type `t1'
      `t1' is a rigid type variable bound by
           the type signature for `exprDoc' at WouterTest.hs:62:17
      Expected type: [f t]
      Inferred type: [t1]
    In the second argument of `map', namely `el'
    In the first argument of `sep', namely `(map exprDoc el)'


I've attached the code.  Compile and inspect with:
$ ghci -fglasgow-exts -fallow-overlapping-instances WouterTest.hs

test1 works great (other than needing some redundant typing, any hints?).

test2 needs the definition of 'Printable And' to print, but I haven't
gotten that to work yet.  It also needs the redundant typing.


-Ron

However, I tried making more complex expression (conjunction, in this
case), but I can't get the types to align.  In particular, if I
uncomment the obvious definition
-------------- next part --------------
A non-text attachment was scrubbed...
Name: WouterTest.hs
Type: application/octet-stream
Size: 2502 bytes
Desc: not available
Url : http://www.haskell.org/pipermail/haskell-cafe/attachments/20080604/0eb8ece1/WouterTest.obj


More information about the Haskell-Cafe mailing list