[Haskell-cafe] Fixed point newtype confusion
Francesco Mazzoli
f at mazzo.li
Sun May 6 15:29:50 CEST 2012
Sorry, I think I misunderstood your question, if I understand correctly
you want some function to convert nested Expr to Fix'ed Exprs.
You can do that with a typeclass, but you have to provide the Fix'ed
type at the bottom:
--------------------------------------
{-# LANGUAGE FlexibleInstances #-}
data E e = Lit Int | Add e e
data Fix f = Fix {unFix :: f (Fix f)}
type Expr = Fix E
lit :: Int -> Expr
lit = Fix . Lit
add :: Expr -> Expr -> Expr
add e1 e2 = Fix (Add e1 e2)
term :: Expr
term = add (lit 1) (add (lit 2) (lit 3))
class FixE e where
fix :: e -> Expr
instance FixE Expr where
fix = id
instance FixE e => FixE (E e) where
fix (Lit i) = lit i
fix (Add e1 e2) = add (fix e1) (fix e2)
------------------------------------
This is because your `term' works since you don't have any occurrence of
`expr' at leaves of your Expr tree, and that works because the leaves
are all literals. However, we can't guarantee this statically.
We can, of course, write an unsafe instance based on the assumption that
the the values at the leaves of the expression tree will be literals:
------------------------------------
instance FixE (E e) where
fix (Lit i) = lit i
fix _ = error "non-literal!"
------------------------------------
Francesco.
On 06/05/12 13:59, Sebastien Zany wrote:
> Hi,
>
> Suppose I have the following types:
>
> > data Expr expr = Lit Nat | Add (expr, expr)
> > newtype Fix f = Fix {unFix :: f (Fix f)}
>
> I can construct a sample term:
>
> > term :: Expr (Expr (Expr expr))
> > term = Add (Lit 1, Add (Lit 2, Lit 3))
>
> But isn't quite what I need. What I really need is:
>
> > term' :: Fix Expr
> > term' = Fix . Add $ (Fix . Lit $ 1, Fix . Add $ (Fix . Lit $ 2, Fix .
> Lit $ 3))
>
> I feel like there's a stupidly simple way to automatically produce term'
> from term, but I'm not seeing it.
>
> Any ideas?
>
> Best,
> Sebastien
>
>
> _______________________________________________
> 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