[Haskell] Ambiguous type variable when using Data.Generic
Bas van Dijk
basvandijk at home.nl
Sat May 20 10:50:16 EDT 2006
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
More information about the Haskell
mailing list