X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=ghc%2Fcompiler%2Fparser%2FParser.y;h=11dc6dc7a42f93046854971e1e94e0b140f1b957;hb=d28ba8c800901bea01f70c4719278c2a364cf9fc;hp=d09226a9b700576ff761608dec82b3730cfb86e2;hpb=d61d6aea2c567a76629984f532022a11bc7fbe21;p=ghc-hetmet.git diff --git a/ghc/compiler/parser/Parser.y b/ghc/compiler/parser/Parser.y index d09226a..11dc6dc 100644 --- a/ghc/compiler/parser/Parser.y +++ b/ghc/compiler/parser/Parser.y @@ -1,6 +1,6 @@ {- -*-haskell-*- ----------------------------------------------------------------------------- -$Id: Parser.y,v 1.108 2002/10/10 15:14:37 sof Exp $ +$Id: Parser.y,v 1.119 2003/06/23 10:35:22 simonpj Exp $ Haskell grammar. @@ -17,17 +17,18 @@ import HsSyn import HsTypes ( mkHsTupCon ) import RdrHsSyn -import HscTypes ( ParsedIface(..), IsBootInterface ) +import HscTypes ( ParsedIface(..), IsBootInterface, noDependencies ) import Lex import RdrName import PrelNames ( mAIN_Name, funTyConName, listTyConName, - parrTyConName, consDataConName, nilDataConName ) -import TysWiredIn ( unitTyCon, unitDataCon, tupleTyCon, tupleCon ) + parrTyConName, consDataConName ) +import TysWiredIn ( unitTyCon, unitDataCon, tupleTyCon, tupleCon, nilDataCon ) import ForeignCall ( Safety(..), CExportSpec(..), CCallConv(..), CCallTarget(..), defaultCCallConv, ) import OccName ( UserFS, varName, tcName, dataName, tcClsName, tvName ) import TyCon ( DataConDetails(..) ) +import DataCon ( DataCon, dataConName ) import SrcLoc ( SrcLoc ) import Module import CmdLineOpts ( opt_SccProfilingOn, opt_InPackage ) @@ -139,6 +140,7 @@ Conflicts: 29 shift/reduce, [SDM 19/9/2002] '{-# INLINE' { ITinline_prag } '{-# NOINLINE' { ITnoinline_prag } '{-# RULES' { ITrules_prag } + '{-# CORE' { ITcore_prag } -- hdaume: annotated core '{-# SCC' { ITscc_prag } '{-# DEPRECATED' { ITdeprecated_prag } '#-}' { ITclose_prag } @@ -236,8 +238,11 @@ Conflicts: 29 shift/reduce, [SDM 19/9/2002] '[t|' { ITopenTypQuote } '[d|' { ITopenDecQuote } '|]' { ITcloseQuote } -ID_SPLICE { ITidEscape $$ } -- $x -'$(' { ITparenEscape } -- $( exp ) +ID_SPLICE { ITidEscape $$ } -- $x +'$(' { ITparenEscape } -- $( exp ) +REIFY_TYPE { ITreifyType } +REIFY_DECL { ITreifyDecl } +REIFY_FIXITY { ITreifyFixity } %monad { P } { thenP } { returnP } %lexer { lexer } { ITeof } @@ -260,10 +265,9 @@ ID_SPLICE { ITidEscape $$ } -- $x module :: { RdrNameHsModule } : srcloc 'module' modid maybemoddeprec maybeexports 'where' body - { HsModule (mkHomeModule $3) Nothing $5 (fst $7) (snd $7) $4 $1 } + { HsModule (Just (mkHomeModule $3)) $5 (fst $7) (snd $7) $4 $1 } | srcloc body - { HsModule (mkHomeModule mAIN_Name) Nothing Nothing - (fst $2) (snd $2) Nothing $1 } + { HsModule Nothing Nothing (fst $2) (snd $2) Nothing $1 } maybemoddeprec :: { Maybe DeprecTxt } : '{-# DEPRECATED' STRING '#-}' { Just $2 } @@ -292,6 +296,7 @@ iface :: { ParsedIface } pi_vers = 1, -- Module version pi_orphan = False, pi_exports = (1,[($2,mkIfaceExports $4)]), + pi_deps = noDependencies, pi_usages = [], pi_fixity = [], pi_insts = [], @@ -413,7 +418,7 @@ topdecl :: { RdrBinding } in RdrHsDecl (InstD (InstDecl $3 binds sigs Nothing $1)) } | srcloc 'default' '(' comma_types0 ')' { RdrHsDecl (DefD (DefaultDecl $4 $1)) } | 'foreign' fdecl { RdrHsDecl $2 } - | '{-# DEPRECATED' deprecations '#-}' { RdrBindings $2 } + | '{-# DEPRECATED' deprecations '#-}' { RdrBindings (reverse $2) } | '{-# RULES' rules '#-}' { RdrBindings (reverse $2) } | srcloc '$(' exp ')' { RdrHsDecl (SpliceD (SpliceDecl $3 $1)) } | decl { $1 } @@ -437,7 +442,7 @@ tycl_decl :: { RdrNameTyClDecl } { let (binds,sigs) = cvMonoBindsAndSigs $5 in - mkClassDecl $3 $4 (map cvClassOpSig sigs) (Just binds) $1 } + mkClassDecl $3 $4 sigs (Just binds) $1 } syn_hdr :: { (RdrName, [RdrNameHsTyVar]) } -- We don't retain the syntax of an infix -- type synonym declaration. Oh well. @@ -466,28 +471,30 @@ decls :: { [RdrBinding] } -- Reversed | {- empty -} { [] } -wherebinds :: { RdrNameHsBinds } - : where { cvBinds $1 } +decllist :: { [RdrBinding] } -- Reversed + : '{' decls '}' { $2 } + | layout_on decls close { $2 } where :: { [RdrBinding] } -- Reversed + -- No implicit parameters : 'where' decllist { $2 } | {- empty -} { [] } -decllist :: { [RdrBinding] } -- Reversed - : '{' decls '}' { $2 } - | layout_on decls close { $2 } +binds :: { RdrNameHsBinds } -- May have implicit parameters + : decllist { cvBinds $1 } + | '{' dbinds '}' { IPBinds $2 False{-not with-} } + | layout_on dbinds close { IPBinds $2 False{-not with-} } -letbinds :: { RdrNameHsExpr -> RdrNameHsExpr } - : decllist { HsLet (cvBinds $1) } - | '{' dbinds '}' { \e -> HsWith e $2 False{-not with-} } - | layout_on dbinds close { \e -> HsWith e $2 False{-not with-} } +wherebinds :: { RdrNameHsBinds } -- May have implicit parameters + : 'where' binds { $2 } + | {- empty -} { EmptyBinds } ----------------------------------------------------------------------------- -- Transformation Rules -rules :: { [RdrBinding] } +rules :: { [RdrBinding] } -- Reversed : rules ';' rule { $3 : $1 } | rules ';' { $1 } | rule { [$1] } @@ -522,10 +529,11 @@ rule_var :: { RdrNameRuleBndr } | '(' varid '::' ctype ')' { RuleBndrSig $2 $4 } ----------------------------------------------------------------------------- --- Deprecations +-- Deprecations (c.f. rules) -deprecations :: { [RdrBinding] } - : deprecation ';' deprecations { $1 : $3 } +deprecations :: { [RdrBinding] } -- Reversed + : deprecations ';' deprecation { $3 : $1 } + | deprecations ';' { $1 } | deprecation { [$1] } | {- empty -} { [] } @@ -918,7 +926,7 @@ sigdecl :: { RdrBinding } exp :: { RdrNameHsExpr } : infixexp '::' sigtype { ExprWithTySig $1 $3 } - | infixexp 'with' dbinding { HsWith $1 $3 True{-not a let-} } + | infixexp 'with' dbinding { HsLet (IPBinds $3 True{-not a let-}) $1 } | infixexp { $1 } infixexp :: { RdrNameHsExpr } @@ -932,7 +940,7 @@ exp10 :: { RdrNameHsExpr } returnP (HsLam (Match ps $5 (GRHSs (unguardedRHS $8 $7) EmptyBinds placeHolderType))) } - | 'let' letbinds 'in' exp { $2 $4 } + | 'let' binds 'in' exp { HsLet $2 $4 } | 'if' srcloc exp 'then' exp 'else' exp { HsIf $3 $5 $7 $2 } | 'case' srcloc exp 'of' altslist { HsCase $3 $5 $2 } | '-' fexp { mkHsNegApp $2 } @@ -950,6 +958,9 @@ exp10 :: { RdrNameHsExpr } then HsSCC $1 $2 else HsPar $2 } + | '{-# CORE' STRING '#-}' exp { HsCoreAnn $2 $4 } -- hdaume: core annotation + + | reifyexp { HsReify $1 } | fexp { $1 } scc_annot :: { FastString } @@ -964,6 +975,12 @@ fexp :: { RdrNameHsExpr } : fexp aexp { (HsApp $1 $2) } | aexp { $1 } +reifyexp :: { HsReify RdrName } + : REIFY_DECL gtycon { Reify ReifyDecl $2 } + | REIFY_DECL qvar { Reify ReifyDecl $2 } + | REIFY_TYPE qcname { Reify ReifyType $2 } + | REIFY_FIXITY qcname { Reify ReifyFixity $2 } + aexps0 :: { [RdrNameHsExpr] } : aexps { reverse $1 } @@ -1007,8 +1024,11 @@ aexp2 :: { RdrNameHsExpr } | srcloc '[t|' ctype '|]' { HsBracket (TypBr $3) $1 } | srcloc '[p|' infixexp '|]' {% checkPattern $1 $3 `thenP` \p -> returnP (HsBracket (PatBr p) $1) } - | srcloc '[d|' cvtopdecls '|]' { HsBracket (DecBr (mkGroup $3)) $1 } + | srcloc '[d|' cvtopbody '|]' { HsBracket (DecBr (mkGroup $3)) $1 } +cvtopbody :: { [RdrNameHsDecl] } + : '{' cvtopdecls '}' { $2 } + | layout_on cvtopdecls close { $2 } texps :: { [RdrNameHsExpr] } : texps ',' exp { $3 : $1 } @@ -1145,7 +1165,7 @@ stmt :: { RdrNameStmt } : srcloc infixexp '<-' exp {% checkPattern $1 $2 `thenP` \p -> returnP (BindStmt p $4 $1) } | srcloc exp { ExprStmt $2 placeHolderType $1 } - | srcloc 'let' decllist { LetStmt (cvBinds $3) } + | srcloc 'let' binds { LetStmt $3 } ----------------------------------------------------------------------------- -- Record Field Update/Construction @@ -1192,14 +1212,14 @@ deprec_var : var { $1 } | tycon { $1 } gcon :: { RdrName } -- Data constructor namespace - : sysdcon { $1 } + : sysdcon { nameRdrName (dataConName $1) } | qcon { $1 } -- the case of '[:' ':]' is part of the production `parr' -sysdcon :: { RdrName } -- Data constructor namespace - : '(' ')' { getRdrName unitDataCon } - | '(' commas ')' { getRdrName (tupleCon Boxed $2) } - | '[' ']' { nameRdrName nilDataConName } +sysdcon :: { DataCon } -- Wired in data constructors + : '(' ')' { unitDataCon } + | '(' commas ')' { tupleCon Boxed $2 } + | '[' ']' { nilDataCon } var :: { RdrName } : varid { $1 } @@ -1377,8 +1397,10 @@ qconsym :: { RdrName } -- Qualified or unqualified consym :: { RdrName } : CONSYM { mkUnqual dataName $1 } - | ':' { nameRdrName consDataConName } + -- ':' means only list cons + | ':' { nameRdrName consDataConName } + -- NB: SrcName because we are reading source -----------------------------------------------------------------------------