summaryrefslogtreecommitdiff
path: root/ghc/compiler/hsSyn/Convert.lhs
diff options
context:
space:
mode:
authorigloo <unknown>2004-06-01 23:22:33 +0000
committerigloo <unknown>2004-06-01 23:22:33 +0000
commit5ca86c67873a146c859cac04a76ee35260a4cf0a (patch)
tree461a8e46781c8ed69eec8ec6290944dfd6af52f2 /ghc/compiler/hsSyn/Convert.lhs
parent41fc1d1564ab6ecd767c1c1f3b378a433d64a954 (diff)
downloadhaskell-5ca86c67873a146c859cac04a76ee35260a4cf0a.tar.gz
[project @ 2004-06-01 23:22:30 by igloo]
Add missing functions to TH export list (mostly spotted by Duncan Coutts). Update TH test output. Add TH support for patterns with type signatures, and test for same (requested by Isaac Jones). Add TH support for pattern guards, and tests for same (requested by Isaac Jones). Add infix patterns to TH datatypes. Added Lift instances for 2- to 7-tuples (requested by Duncan Coutts).
Diffstat (limited to 'ghc/compiler/hsSyn/Convert.lhs')
-rw-r--r--ghc/compiler/hsSyn/Convert.lhs12
1 files changed, 8 insertions, 4 deletions
diff --git a/ghc/compiler/hsSyn/Convert.lhs b/ghc/compiler/hsSyn/Convert.lhs
index 8c30abbd35..2d7c85add9 100644
--- a/ghc/compiler/hsSyn/Convert.lhs
+++ b/ghc/compiler/hsSyn/Convert.lhs
@@ -10,7 +10,7 @@ module Convert( convertToHsExpr, convertToHsDecls, convertToHsType ) where
#include "HsVersions.h"
-import Language.Haskell.TH as TH
+import Language.Haskell.TH as TH hiding (sigP)
import Language.Haskell.TH.Syntax as TH
import HsSyn as Hs
@@ -262,9 +262,10 @@ cvtguard :: TH.Body -> [LGRHS RdrName]
cvtguard (GuardedB pairs) = map cvtpair pairs
cvtguard (NormalB e) = [noLoc (GRHS [ nlResultStmt (cvtl e) ])]
-cvtpair :: (TH.Exp,TH.Exp) -> LGRHS RdrName
-cvtpair (x,y) = noLoc (GRHS [nlBindStmt truePat (cvtl x),
- nlResultStmt (cvtl y)])
+cvtpair :: (TH.Guard,TH.Exp) -> LGRHS RdrName
+cvtpair (NormalG x,y) = noLoc (GRHS [nlBindStmt truePat (cvtl x),
+ nlResultStmt (cvtl y)])
+cvtpair (PatG x,y) = noLoc (GRHS (cvtstmts x ++ [nlResultStmt (cvtl y)]))
cvtOverLit :: Lit -> HsOverLit
cvtOverLit (IntegerL i) = mkHsIntegral i
@@ -292,11 +293,14 @@ cvtp (TH.VarP s) = Hs.VarPat(vName s)
cvtp (TupP [p]) = cvtp p
cvtp (TupP ps) = TuplePat (map cvtlp ps) Boxed
cvtp (ConP s ps) = ConPatIn (noLoc (cName s)) (PrefixCon (map cvtlp ps))
+cvtp (InfixP p1 s p2)
+ = ConPatIn (noLoc (cName s)) (InfixCon (cvtlp p1) (cvtlp p2))
cvtp (TildeP p) = LazyPat (cvtlp p)
cvtp (TH.AsP s p) = AsPat (noLoc (vName s)) (cvtlp p)
cvtp TH.WildP = WildPat void
cvtp (RecP c fs) = ConPatIn (noLoc (cName c)) $ Hs.RecCon (map (\(s,p) -> (noLoc (vName s),cvtlp p)) fs)
cvtp (ListP ps) = ListPat (map cvtlp ps) void
+cvtp (SigP p t) = SigPatIn (cvtlp p) (cvtType t)
-----------------------------------------------------------
-- Types and type variables