2 module ParserCore ( parseCore ) where
10 import Kind( Kind(..) )
11 import Name( nameOccName, nameModule )
13 import ParserCoreUtils
17 import TysPrim( wordPrimTyCon, intPrimTyCon, charPrimTyCon,
18 floatPrimTyCon, doublePrimTyCon, addrPrimTyCon )
19 import TyCon ( TyCon, tyConName )
24 #include "../HsVersions.h"
32 '%module' { TKmodule }
34 '%newtype' { TKnewtype }
35 '%forall' { TKforall }
41 '%coerce' { TKcoerce }
43 '%external' { TKexternal }
61 INTEGER { TKinteger $$ }
62 RATIONAL { TKrational $$ }
63 STRING { TKstring $$ }
66 %monad { P } { thenP } { returnP }
67 %lexer { lexer } { TKEOF }
71 module :: { HsExtCore RdrName }
72 : '%module' modid tdefs vdefgs { HsExtCore $2 $3 $4 }
75 : CNAME { mkSysModuleFS (mkFastString $1) }
77 -------------------------------------------------------------
78 -- Type and newtype declarations are in HsSyn syntax
80 tdefs :: { [TyClDecl RdrName] }
82 | tdef ';' tdefs {$1:$3}
84 tdef :: { TyClDecl RdrName }
85 : '%data' q_tc_name tv_bndrs '=' '{' cons1 '}'
86 { mkTyData DataType (noLoc (noLoc [], noLoc (ifaceExtRdrName $2), map toHsTvBndr $3)) Nothing $6 Nothing }
87 | '%newtype' q_tc_name tv_bndrs trep
88 { let tc_rdr = ifaceExtRdrName $2 in
89 mkTyData NewType (noLoc (noLoc [], noLoc tc_rdr, map toHsTvBndr $3)) Nothing ($4 (rdrNameOcc tc_rdr)) Nothing }
91 -- For a newtype we have to invent a fake data constructor name
92 -- It doesn't matter what it is, because it won't be used
93 trep :: { OccName -> [LConDecl RdrName] }
94 : {- empty -} { (\ tc_occ -> []) }
95 | '=' ty { (\ tc_occ -> let { dc_name = mkRdrUnqual (setOccNameSpace dataName tc_occ) ;
96 con_info = PrefixCon [toHsType $2] }
97 in [noLoc $ ConDecl (noLoc dc_name) []
98 (noLoc []) con_info]) }
100 cons1 :: { [LConDecl RdrName] }
102 | con ';' cons1 { $1:$3 }
104 con :: { LConDecl RdrName }
105 : d_pat_occ attv_bndrs hs_atys
106 { noLoc $ ConDecl (noLoc (mkRdrUnqual $1)) $2 (noLoc []) (PrefixCon $3)}
108 { noLoc $ GadtDecl (noLoc (mkRdrUnqual $1)) (toHsType $3) }
110 attv_bndrs :: { [LHsTyVarBndr RdrName] }
112 | '@' tv_bndr attv_bndrs { toHsTvBndr $2 : $3 }
114 hs_atys :: { [LHsType RdrName] }
115 : atys { map toHsType $1 }
118 ---------------------------------------
120 ---------------------------------------
122 atys :: { [IfaceType] }
127 : tv_occ { IfaceTyVar $1 }
128 | q_tc_name { IfaceTyConApp (IfaceTc $1) [] }
132 : tv_occ atys { foldl IfaceAppTy (IfaceTyVar $1) $2 }
133 | q_tc_name atys { IfaceTyConApp (IfaceTc $1) $2 }
137 | bty '->' ty { IfaceFunTy $1 $3 }
138 | '%forall' tv_bndrs '.' ty { foldr IfaceForAllTy $4 $2 }
140 ----------------------------------------------
141 -- Bindings are in Iface syntax
143 vdefgs :: { [IfaceBinding] }
145 | let_bind ';' vdefgs { $1 : $3 }
147 let_bind :: { IfaceBinding }
148 : '%rec' '{' vdefs1 '}' { IfaceRec $3 }
149 | vdef { let (b,r) = $1
152 vdefs1 :: { [(IfaceIdBndr, IfaceExpr)] }
154 | vdef ';' vdefs1 { $1:$3 }
156 vdef :: { (IfaceIdBndr, IfaceExpr) }
157 : qd_occ '::' ty '=' exp { (($1, $3), $5) }
158 -- NB: qd_occ includes data constructors, because
159 -- we allow data-constructor wrappers at top level
160 -- But we discard the module name, because it must be the
161 -- same as the module being compiled, and Iface syntax only
162 -- has OccNames in binding positions
164 qd_occ :: { OccName }
168 ---------------------------------------
170 bndr :: { IfaceBndr }
171 : '@' tv_bndr { IfaceTvBndr $2 }
172 | id_bndr { IfaceIdBndr $1 }
174 bndrs :: { [IfaceBndr] }
176 | bndr bndrs { $1:$2 }
178 id_bndr :: { IfaceIdBndr }
179 : '(' var_occ '::' ty ')' { ($2,$4) }
181 id_bndrs :: { [IfaceIdBndr] }
183 | id_bndr id_bndrs { $1:$2 }
185 tv_bndr :: { IfaceTvBndr }
186 : tv_occ { ($1, LiftedTypeKind) }
187 | '(' tv_occ '::' akind ')' { ($2, $4) }
189 tv_bndrs :: { [IfaceTvBndr] }
191 | tv_bndr tv_bndrs { $1:$2 }
193 akind :: { IfaceKind }
194 : '*' { LiftedTypeKind }
195 | '#' { UnliftedTypeKind }
196 | '?' { OpenTypeKind }
197 | '(' kind ')' { $2 }
199 kind :: { IfaceKind }
201 | akind '->' kind { FunKind $1 $3 }
203 -----------------------------------------
206 aexp :: { IfaceExpr }
207 : var_occ { IfaceLcl $1 }
208 | modid '.' qd_occ { IfaceExt (ExtPkg $1 $3) }
209 | lit { IfaceLit $1 }
212 fexp :: { IfaceExpr }
213 : fexp aexp { IfaceApp $1 $2 }
214 | fexp '@' aty { IfaceApp $1 (IfaceType $3) }
219 | '\\' bndrs '->' exp { foldr IfaceLam $4 $2 }
220 | '%let' let_bind '%in' exp { IfaceLet $2 $4 }
222 | '%case' '(' ty ')' aexp '%of' id_bndr
223 '{' alts1 '}' { IfaceCase $5 (fst $7) $3 $9 }
224 | '%coerce' aty exp { IfaceNote (IfaceCoerce $2) $3 }
227 --"SCC" -> IfaceNote (IfaceSCC "scc") $3
228 "InlineCall" -> IfaceNote IfaceInlineCall $3
229 "InlineMe" -> IfaceNote IfaceInlineMe $3
231 | '%external' STRING aty { IfaceFCall (ForeignCall.CCall
232 (CCallSpec (StaticTarget (mkFastString $2))
233 CCallConv (PlaySafe False)))
236 alts1 :: { [IfaceAlt] }
238 | alt ';' alts1 { $1:$3 }
241 : modid '.' d_pat_occ bndrs '->' exp
242 { (IfaceDataAlt $3, map ifaceBndrName $4, $6) }
243 -- The external syntax currently includes the types of the
244 -- the args, but they aren't needed internally
245 -- Nor is the module qualifier
247 { (IfaceLitAlt $1, [], $3) }
249 { (IfaceDefault, [], $3) }
252 : '(' INTEGER '::' aty ')' { convIntLit $2 $4 }
253 | '(' RATIONAL '::' aty ')' { convRatLit $2 $4 }
254 | '(' CHAR '::' aty ')' { MachChar $2 }
255 | '(' STRING '::' aty ')' { MachStr (mkFastString $2) }
257 tv_occ :: { OccName }
258 : NAME { mkSysOcc tvName $1 }
260 var_occ :: { OccName }
261 : NAME { mkSysOcc varName $1 }
265 q_tc_name :: { IfaceExtName }
266 : modid '.' CNAME { ExtPkg $1 (mkSysOcc tcName $3) }
268 -- Data constructor in a pattern or data type declaration; use the dataName,
269 -- because that's what we expect in Core case patterns
270 d_pat_occ :: { OccName }
271 : CNAME { mkSysOcc dataName $1 }
273 -- Data constructor occurrence in an expression;
274 -- use the varName because that's the worker Id
276 : CNAME { mkSysOcc varName $1 }
280 ifaceBndrName (IfaceIdBndr (n,_)) = n
281 ifaceBndrName (IfaceTvBndr (n,_)) = n
283 convIntLit :: Integer -> IfaceType -> Literal
284 convIntLit i (IfaceTyConApp tc [])
285 | tc `eqTc` intPrimTyCon = MachInt i
286 | tc `eqTc` wordPrimTyCon = MachWord i
287 | tc `eqTc` charPrimTyCon = MachChar (chr (fromInteger i))
288 | tc `eqTc` addrPrimTyCon && i == 0 = MachNullAddr
290 = pprPanic "Unknown integer literal type" (ppr aty)
292 convRatLit :: Rational -> IfaceType -> Literal
293 convRatLit r (IfaceTyConApp tc [])
294 | tc `eqTc` floatPrimTyCon = MachFloat r
295 | tc `eqTc` doublePrimTyCon = MachDouble r
297 = pprPanic "Unknown rational literal type" (ppr aty)
299 eqTc :: IfaceTyCon -> TyCon -> Bool -- Ugh!
300 eqTc (IfaceTc (ExtPkg mod occ)) tycon
301 = mod == nameModule nm && occ == nameOccName nm
305 -- Tiresomely, we have to generate both HsTypes (in type/class decls)
306 -- and IfaceTypes (in Core expressions). So we parse them as IfaceTypes,
307 -- and convert to HsTypes here. But the IfaceTypes we can see here
308 -- are very limited (see the productions for 'ty', so the translation
310 toHsType :: IfaceType -> LHsType RdrName
311 toHsType (IfaceTyVar v) = noLoc $ HsTyVar (mkRdrUnqual v)
312 toHsType (IfaceAppTy t1 t2) = noLoc $ HsAppTy (toHsType t1) (toHsType t2)
313 toHsType (IfaceFunTy t1 t2) = noLoc $ HsFunTy (toHsType t1) (toHsType t2)
314 toHsType (IfaceTyConApp (IfaceTc tc) ts) = foldl mkHsAppTy (noLoc $ HsTyVar (ifaceExtRdrName tc)) (map toHsType ts)
315 toHsType (IfaceForAllTy tv t) = add_forall (toHsTvBndr tv) (toHsType t)
317 toHsTvBndr :: IfaceTvBndr -> LHsTyVarBndr RdrName
318 toHsTvBndr (tv,k) = noLoc $ KindedTyVar (mkRdrUnqual tv) k
320 ifaceExtRdrName :: IfaceExtName -> RdrName
321 ifaceExtRdrName (ExtPkg mod occ) = mkOrig mod occ
322 ifaceExtRdrName other = pprPanic "ParserCore.ifaceExtRdrName" (ppr other)
324 add_forall tv (L _ (HsForAllTy exp tvs cxt t))
325 = noLoc $ HsForAllTy exp (tv:tvs) cxt t
327 = noLoc $ HsForAllTy Explicit [tv] (noLoc []) t
330 happyError s l = failP (show l ++ ": Parse error\n") (take 100 s) l