X-Git-Url: http://git.megacz.com/?p=ghc-hetmet.git;a=blobdiff_plain;f=compiler%2Fparser%2FParserCore.y;h=3f2b32a8b3e614ac0783a03ff24b89c44fa0a31e;hp=6d302fb03acf1d1cb54f5ff14cbadece99d8a91f;hb=2d4d636af091b8da27466b5cf90011395a9c2f66;hpb=5eb542caabfca8c719be507998aee8cebdf8d505 diff --git a/compiler/parser/ParserCore.y b/compiler/parser/ParserCore.y index 6d302fb..3f2b32a 100644 --- a/compiler/parser/ParserCore.y +++ b/compiler/parser/ParserCore.y @@ -1,5 +1,6 @@ { -{-# OPTIONS -w #-} +{-# LANGUAGE BangPatterns #-} -- required for versions of Happy before 1.18.6 +{-# OPTIONS -Wwarn -w #-} -- The above warning supression flag is a temporary kludge. -- While working on this module you are encouraged to remove it and fix -- any warnings in the module. See @@ -16,8 +17,9 @@ import RdrName import OccName import Type ( Kind, liftedTypeKindTyCon, openTypeKindTyCon, unliftedTypeKindTyCon, - argTypeKindTyCon, ubxTupleKindTyCon, mkArrowKind, mkTyConApp + argTypeKindTyCon, ubxTupleKindTyCon, mkTyConApp ) +import Coercion( mkArrowKind ) import Name( Name, nameOccName, nameModule, mkExternalName ) import Module import ParserCoreUtils @@ -29,7 +31,7 @@ import TysPrim( wordPrimTyCon, intPrimTyCon, charPrimTyCon, import TyCon ( TyCon, tyConName ) import FastString import Outputable -import Char +import Data.Char import Unique #include "../HsVersions.h" @@ -37,6 +39,7 @@ import Unique } %name parseCore +%expect 0 %tokentype { Token } %token @@ -123,18 +126,18 @@ tdefs :: { [TyClDecl RdrName] } tdef :: { TyClDecl RdrName } : '%data' q_tc_name tv_bndrs '=' '{' cons '}' ';' - { mkTyData DataType ( noLoc [] - , noLoc (ifaceExtRdrName $2) - , map toHsTvBndr $3 - , Nothing - ) Nothing $6 Nothing } + { TyData { tcdND = DataType, tcdCtxt = noLoc [] + , tcdLName = noLoc (ifaceExtRdrName $2) + , tcdTyVars = map toHsTvBndr $3 + , tcdTyPats = Nothing, tcdKindSig = Nothing + , tcdCons = $6, tcdDerivs = Nothing } } | '%newtype' q_tc_name tv_bndrs trep ';' { let tc_rdr = ifaceExtRdrName $2 in - mkTyData NewType ( noLoc [] - , noLoc tc_rdr - , map toHsTvBndr $3 - , Nothing - ) Nothing ($4 (rdrNameOcc tc_rdr)) Nothing } + TyData { tcdND = NewType, tcdCtxt = noLoc [] + , tcdLName = noLoc tc_rdr + , tcdTyVars = map toHsTvBndr $3 + , tcdTyPats = Nothing, tcdKindSig = Nothing + , tcdCons = $4 (rdrNameOcc tc_rdr), tcdDerivs = Nothing } } -- For a newtype we have to invent a fake data constructor name -- It doesn't matter what it is, because it won't be used @@ -142,8 +145,8 @@ trep :: { OccName -> [LConDecl RdrName] } : {- empty -} { (\ tc_occ -> []) } | '=' ty { (\ tc_occ -> let { dc_name = mkRdrUnqual (setOccNameSpace dataName tc_occ) ; con_info = PrefixCon [toHsType $2] } - in [noLoc $ ConDecl (noLoc dc_name) Explicit [] - (noLoc []) con_info ResTyH98 Nothing]) } + in [noLoc $ mkSimpleConDecl (noLoc dc_name) [] + (noLoc []) con_info]) } cons :: { [LConDecl RdrName] } : {- empty -} { [] } -- 20060420 Empty data types allowed. jds @@ -152,15 +155,8 @@ cons :: { [LConDecl RdrName] } con :: { LConDecl RdrName } : d_pat_occ attv_bndrs hs_atys - { noLoc $ ConDecl (noLoc (mkRdrUnqual $1)) Explicit $2 (noLoc []) (PrefixCon $3) ResTyH98 Nothing } - | d_pat_occ '::' ty - -- XXX - audreyt - $3 needs to be split into argument and return types! - -- also not sure whether the [] below (quantified vars) appears. - -- also the "PrefixCon []" is wrong. - -- also we want to munge $3 somehow. - -- extractWhatEver to unpack ty into the parts to ConDecl - -- XXX - define it somewhere in RdrHsSyn - { noLoc $ ConDecl (noLoc (mkRdrUnqual $1)) Explicit [] (noLoc []) (PrefixCon []) (undefined $3) Nothing } + { noLoc $ mkSimpleConDecl (noLoc (mkRdrUnqual $1)) $2 (noLoc []) (PrefixCon $3) } +-- ToDo: parse record-style declarations attv_bndrs :: { [LHsTyVarBndr RdrName] } : {- empty -} { [] } @@ -273,15 +269,16 @@ exp :: { IfaceExpr } | '%let' let_bind '%in' exp { IfaceLet $2 $4 } -- gaw 2004 | '%case' '(' ty ')' aexp '%of' id_bndr - '{' alts1 '}' { IfaceCase $5 (fst $7) $3 $9 } + '{' alts1 '}' { IfaceCase $5 (fst $7) $9 } | '%cast' aexp aty { IfaceCast $2 $3 } - | '%note' STRING exp - { case $2 of - --"SCC" -> IfaceNote (IfaceSCC "scc") $3 - "InlineMe" -> IfaceNote IfaceInlineMe $3 - } +-- No InlineMe any more +-- | '%note' STRING exp +-- { case $2 of +-- --"SCC" -> IfaceNote (IfaceSCC "scc") $3 +-- "InlineMe" -> IfaceNote IfaceInlineMe $3 +-- } | '%external' STRING aty { IfaceFCall (ForeignCall.CCall - (CCallSpec (StaticTarget (mkFastString $2)) + (CCallSpec (StaticTarget (mkFastString $2) Nothing) CCallConv (PlaySafe False))) $3 }