91541f8e25d2247bf79f9f176f024bd7696feed2
[clean-tests.git] / datatype / Language / Quote.hs
1 {-# LANGUAGE TemplateHaskell #-}
2 {-# LANGUAGE QuasiQuotes #-}
3 {-# LANGUAGE TupleSections #-}
4 {-# LANGUAGE ParallelListComp #-}
5 module Language.Quote (dsl) where
6
7 import Data.Char
8 import Data.Functor.Identity
9
10 import Language.Haskell.TH.Syntax
11 import Language.Haskell.TH.Quote
12
13 import Text.Parsec
14 import Text.Parsec.String
15 import Text.Parsec.Expr as E
16 import qualified Text.Parsec.Token as P
17 import Text.Parsec.Language (haskell)
18 --
19 import Language.GenDSL
20
21 dsl :: QuasiQuoter
22 dsl = QuasiQuoter
23 { quoteExp = \s->location >>= parseExpr s
24 , quotePat = undefined
25 , quoteType = undefined
26 , quoteDec = undefined
27 }
28 where
29 parseExpr :: MonadFail m => String -> Loc -> m Exp
30 parseExpr s loc =
31 case runParser p () "" s of
32 Left err -> fail $ show err
33 Right e -> return e
34 where
35 file = loc_filename loc
36 (line, col) = loc_start loc
37 p = getPosition >>= setPosition . mPos >> expr <* eof
38 mPos = (flip setSourceName) file .
39 (flip setSourceLine) line .
40 (flip setSourceColumn) col
41
42 -- Lexer
43 identifier,operator :: Parser String
44 identifier = P.identifier haskell
45 operator = P.operator haskell
46
47 parens,braces :: Parser a -> Parser a
48 braces = P.braces haskell
49 parens = P.parens haskell
50
51 commaSep :: Parser a -> Parser [a]
52 commaSep = P.commaSep haskell
53
54 symbol :: String -> Parser String
55 symbol = P.symbol haskell
56
57 reserved,reservedOp :: String -> Parser ()
58 reserved = P.reserved haskell
59 reservedOp = P.reservedOp haskell
60
61 -- Parser
62 pat :: Parser Pat
63 pat
64 = try (RecP <$> con <*> braces (commaSep $ (,) <$> var <* reservedOp "=" <*> pat))
65 <|> ConP <$> con <*> many pat
66 <|> try (AsP <$> var <* reservedOp "@" <*> pat)
67 <|> VarP <$> var
68 <|> WildP <$ symbol "_"
69 <|> LitP <$> lit
70 <|> parens pat
71
72 expr :: Parser Exp
73 expr = buildExpressionParser
74 [ [bin "^" AssocRight]
75 , [bin "*" AssocLeft, bin "/" AssocLeft]
76 , [bin "+" AssocLeft, bin "-" AssocLeft]
77 , [bin o AssocNone | o <- ["==", "/=", "<", ">", "<=", ">="]]
78 , [bin "&&" AssocRight]
79 , [bin "||" AssocRight]
80 , [E.Infix (fmap ifx $ P.lexeme haskell $ char '`' *> identifier <* char '`') AssocRight]
81 ] basic
82 where
83 bin :: String -> Assoc -> Operator String () Identity Exp
84 bin str = E.Infix $ ifx (str++".") <$ sat operator (str==)
85 (("Expected operator " ++ str ++ " but got ")++)
86
87 basic :: Parser Exp
88 basic
89 = try (AppE . VarE <$> var <*> (TupE <$> parens (commaSep expr)))
90 <|> VarE <$> var
91 <|> mkCase <$ reserved "case" <*> expr <* reserved "of" <*> many1 ((,) <$> pat <* reservedOp "->" <*> expr)
92 <|> (\i t e->VarE (mkName "if'") `AppE` i `AppE` t `AppE` e) <$ reserved "if" <*> expr <* reserved "then" <*> expr <* reserved "else" <*> expr
93 <|> parens expr
94 <|> mkLit . LitE <$> lit
95 <|> mkLit . ConE . mkName <$> sat identifier ("True"==) ("Expected True but got: "++)
96 <|> mkLit . ConE . mkName <$> sat identifier ("False"==) ("Expected False but got: "++)
97
98 sat :: Parser a -> (a -> Bool) -> (a -> String) -> Parser a
99 sat p f msg = try (p >>= \a->if f a then pure a else fail (msg a))
100
101 lit :: Parser Lit
102 lit
103 = CharL <$> P.charLiteral haskell
104 <|> IntegerL <$> P.natural haskell
105
106 mkLit :: Exp -> Exp
107 mkLit = AppE $ VarE $ mkName "lit"
108
109 con,var :: Parser Name
110 con = mkName <$> sat identifier (isUpper . head) ("Not a data constructor: "++)
111 var = mkName <$> sat identifier (isLower . head) ("Not a variable identifier: "++)
112
113 -- Convert case to if statements
114 mkCase :: Exp -> [(Pat, Exp)] -> Exp
115 mkCase name cases = foldr (uncurry mkCaseMatch) (VarE (mkName "bottom") `AppE` LitE (StringL "Exhausted case")) cases
116 where
117 mkCaseMatch :: Pat -> Exp -> Exp -> Exp
118 mkCaseMatch a e rest = case mkCasePred name a of
119 [] -> mkCaseLets (mkCaseBinding name a) e
120 ps -> VarE (mkName "if'") `AppE` foldl1 (ifx "&.") ps `AppE` (mkCaseLets (mkCaseBinding name a) e) `AppE` rest
121
122 mkCaseLets :: [Dec] -> Exp -> Exp
123 mkCaseLets [] e = e
124 mkCaseLets defs e = LetE defs e
125
126 conPtoRecP :: Name -> [Pat] -> Pat
127 conPtoRecP consName = RecP consName . zip (map (adtFieldName consName) [0..])
128
129 mkCasePred :: Exp -> Pat -> [Exp]
130 mkCasePred e (LitP l) = [ifx "==." (VarE (mkName "lit") `AppE` LitE l) e]
131 mkCasePred _ (VarP _) = []
132 mkCasePred e (ConP cons fs) = mkCasePred e $ conPtoRecP cons fs
133 mkCasePred e (InfixP l cons r) = mkCasePred e (ConP cons [l,r])
134 mkCasePred e (UInfixP l cons r) = mkCasePred e (ConP cons [l,r])
135 mkCasePred e (ParensP p) = mkCasePred e p
136 mkCasePred e (TildeP p) = mkCasePred e p
137 mkCasePred e (BangP p) = mkCasePred e p
138 mkCasePred e (AsP _ p) = mkCasePred e p
139 mkCasePred _ WildP = []
140 mkCasePred e (RecP cons fs) = VarE (predicateName cons) `AppE` e
141 : concatMap (\(n, p)->mkCasePred (VarE (selectorName n) `AppE` e) p) fs
142 mkCasePred _ p = error $ "Unsupported pat: " ++ show p
143
144 mkCaseBinding :: Exp -> Pat -> [Dec]
145 mkCaseBinding _ (LitP _) = []
146 mkCaseBinding e (VarP v) = [FunD v [Clause [] (NormalB $ e) []]]
147 mkCaseBinding e (ConP cons fs) = mkCaseBinding e $ conPtoRecP cons fs
148 mkCaseBinding e (InfixP l cons r) = mkCaseBinding e (ConP cons [l,r])
149 mkCaseBinding e (UInfixP l cons r) = mkCaseBinding e (ConP cons [l,r])
150 mkCaseBinding e (ParensP p) = mkCaseBinding e p
151 mkCaseBinding e (TildeP p) = mkCaseBinding e p
152 mkCaseBinding e (BangP p) = mkCaseBinding e p
153 mkCaseBinding e (AsP n p) = FunD n [Clause [] (NormalB $ e) []]:mkCaseBinding e p
154 mkCaseBinding _ WildP = []
155 mkCaseBinding e (RecP _ fs) = concatMap (\(n, p)->mkCaseBinding (VarE (selectorName n) `AppE` e) p) fs
156 mkCaseBinding _ p = error $ "Unsupported pat: " ++ show p