Re: [Haskell] Ambiguous type variable when using Data.Generic

2006-05-20 Thread Neil Mitchell

Hi Bas,

I had a requirement to do something similar as part of one of my
projects, essentially reduce full Haskell to a small and manageable
subset. Unfortunately I think you'll find that this task is a lot
bigger than you first realise, and in particular that case-of is
probably the expression you want to reduce everything to - rather than
if-then-else. case-of can represent pattern matches in a much more
uniform way than if-then-else, which is just a case-of on a boolean.

The way I went about this was by using Yhc -core [1] to generate a
Core language. GHC also has a Core language, which has various
differences to the Yhc generated Core, and may be more to your liking
(or perhaps less). I would suggest you explore these avenues before
trying to write your own simplifier.

Thanks

Neil

[1] http://www.haskell.org/haskellwiki/Yhc/API/Core
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Ambiguous type variable when using Data.Generic

2006-05-20 Thread Taral

On 5/20/06, Bas van Dijk <[EMAIL PROTECTED]> wrote:

How can I make this work?


As far as I know, you can't. To see the problem, rewrite it using dictionaries:

data Simplify a = Simplify { simplify :: a -> a }

simplify_HsExp (HsInfixApp e1 op e2) = HsApp (HsApp (opToExp op) e1) e2
simplify_HsExp (HsLeftSection  e  op)= HsApp (opToExp op) e
simplify_HsExp (HsRightSection op e) = HsApp (opToExp op) e
simplify_HsExp (HsParen e) = e
simplify_HsExp e = e

Simplify_HsExp = Simplify simplify_HsExp

etc.

You will end up with a bunch of Simplify_* objects. Now in the application:

preProcess = everywhere (mkT simplify)

how do you convert this? If you use (mkT (simplify ...)), you're
fixing simplify to only one type. If you use (mkT simplify), you get a
type error.

GHC is telling you that you need to tell it which instance of simplify
to use. In your example, you can use:

everywhere (mkT (simplify :: HsExp -> HsExp))
. everywhere (mkT (simplify :: HsPat -> HsPat))
. everywhere (mkT (simplify :: HsRhs -> HsRhs))

Of course, that's not any simpler.

--
Taral <[EMAIL PROTECTED]>
"You can't prove anything."
   -- Gödel's Incompetence Theorem
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Ambiguous type variable when using Data.Generic

2006-05-20 Thread Taral

On 5/20/06, Bas van Dijk <[EMAIL PROTECTED]> wrote:

  simplifyExp (HsLeftSection  e  op)= HsApp (opToExp op) e
  simplifyExp (HsRightSection op e) = HsApp (opToExp op) e


By the way, I think this looks wrong. One of these needs to create a
lambda expression.

--
Taral <[EMAIL PROTECTED]>
"You can't prove anything."
   -- Gödel's Incompetence Theorem
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


RE: [Haskell] Ambiguous type variable when using Data.Generic

2006-05-20 Thread Ralf Lammel
Bas,

There is a really easy (and intended) way to make this work.
See Sec. 6.4 SYB1 paper (TLDI 2003).

- You compose things as follows:
 simplify = id `extT` simplifyRhs `extT` simplifyExp `extT` ... 
- You apply everything right away to simplify.

There is no need to use a class in your case.
However, if you really want to you need to apply the pattern from the
SYB3 paper.

BTW, simplifications are often not of the kind that non-descending step
functions and recursion by everything does the right thing. Often you
need a more powerful schemes such as bottom-up innermost normalization
(some variation thereof). Please see the Stratego and Strafunski
literature for this purpose.

Best,
Ralf

> -Original Message-
> From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED]
On
> Behalf Of Bas van Dijk
> Sent: Saturday, May 20, 2006 7:50 AM
> To: haskell@haskell.org
> Subject: [Haskell] Ambiguous type variable when using Data.Generic
> 
> Hello,
> 
> I'm writing a function 'preProcess' that simplifies the AST that comes
out
> of
> Language.Haskell.Parser.parseModule. Simplifying means rewriting infix
> applications to normal prefix applications (in both patterns and
> expressions), removing parentheses, rewriting guards to if-then-else
> expressions, etc..
> 
> At the moment I use Data.Generic to traverse the AST and apply
> simplification
> functions to the different values. Like this:
> 
>

--
> -
> preProcess :: HsModule -> HsModule
> preProcess = em simplifyRhs . em simplifyPat . em simplifyExp
> where
>   em f = everywhere (mkT f)
> 
>   simplifyExp :: HsExp -> HsExp
>   simplifyExp (HsInfixApp e1 op e2) = HsApp (HsApp (opToExp op)
e1) e2
>   simplifyExp (HsLeftSection  e  op)= HsApp (opToExp op) e
>   simplifyExp (HsRightSection op e) = HsApp (opToExp op) e
>   simplifyExp (HsParen e) = e
>   simplifyExp e = e
> 
>   opToExp (HsQVarOp name) = HsVar name
>   opToExp (HsQConOp name) = HsCon name
> 
>   simplifyPat :: HsPat -> HsPat
>   simplifyPat (HsPInfixApp p1 consName p2) = HsPApp consName [p1,
p2]
>   simplifyPat (HsPParen p) = p
>   simplifyPat p = p
> 
>   simplifyRhs :: HsRhs -> HsRhs
>   simplifyRhs (HsGuardedRhss rhss) = HsUnGuardedRhs $ makeIf rhss
>   where
> makeIf :: [HsGuardedRhs] -> HsExp
> makeIf [] = nonExhaustivePatternError
> makeIf (HsGuardedRhs _ con exp : rhss) =
>  HsIf con exp $ makeIf rhss
> 
> nonExhaustivePatternError =
> HsApp (HsVar (UnQual (HsIdent "error")))
>   (HsLit (HsString "Non-exhaustive patterns"))
> 
>   simplifyRhs rhs = rhs
>

--
> -
> 
> This works, however I would like to have a single function 'simplify'
that
> can
> be applied to different values in the AST. This calls for a class
Simplify
> with instances for expressions, patterns, etc.:
> 
>

--
> -
> preProcess :: HsModule -> HsModule
> preProcess = everywhere (mkT simplify)
> 
> class Simplify a where
> simplify :: a -> a
> 
> instance Simplify HsExp where
> simplify (HsInfixApp e1 op e2) = HsApp (HsApp (opToExp op) e1) e2
> simplify (HsLeftSection  e  op)= HsApp (opToExp op) e
> simplify (HsRightSection op e) = HsApp (opToExp op) e
> simplify (HsParen e) = e
> simplify e = e
> 
> instance Simplify HsPat where
> simplify (HsPInfixApp p1 consName p2) = HsPApp consName [p1, p2]
> simplify (HsPParen p) = p
> simplify p = p
> 
> instance Simplify HsRhs where
>   simplify (HsGuardedRhss rhss) = HsUnGuardedRhs $ makeIf rhss
>   where
> makeIf :: [HsGuardedRhs] -> HsExp
> makeIf [] = nonExhaustivePatternError
> makeIf (HsGuardedRhs _ con exp : rhss) =
>   HsIf con exp $ makeIf rhss
> 
> nonExhaustivePatternError =
> HsApp (HsVar (UnQual (HsIdent "error")))
>   (HsLit (HsString "Non-exhaustive patterns"))
> 
>   simplify rhs = rhs
> 
> opToExp (HsQVarOp name) = HsVar name
> opToExp (HsQConOp name) = HsCon name
>

--
> -
> 
> However, compiling the above gives the following type error:
> 
> Ambiguous type variable `b' in the constraints:
>   `Typeable b' arising from use of `mkT' at Special.hs:145:25-27
>   `Simplify b' arising from use of `simplify' at
Special.hs:145:29-36
> Probable fix: add a type signature that fixes these type variable(s)
> 
> How can I make this work?
> 
> Greetings,
> 
> Bas van Dijk
> __