X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=compiler%2Fparser%2FParser.y.pp;h=a72b47b27d62373ee328ae7fe74df233dcb4e610;hb=3ad8f84f6a75f240383e62a14472d14eb372dcd1;hp=3fb6cb1eceacf1b18bddbebbd1ffe3b53a267c8f;hpb=bb106f283663e9c16a4c72ec9ca57109ae57a0ed;p=ghc-hetmet.git diff --git a/compiler/parser/Parser.y.pp b/compiler/parser/Parser.y.pp index 3fb6cb1..a72b47b 100644 --- a/compiler/parser/Parser.y.pp +++ b/compiler/parser/Parser.y.pp @@ -159,6 +159,7 @@ incorrect. 'deriving' { L _ ITderiving } 'do' { L _ ITdo } 'else' { L _ ITelse } + 'for' { L _ ITfor } 'hiding' { L _ IThiding } 'if' { L _ ITif } 'import' { L _ ITimport } @@ -255,7 +256,6 @@ incorrect. QCONSYM { L _ (ITqconsym _) } IPDUPVARID { L _ (ITdupipvarid _) } -- GHC extension - IPSPLITVARID { L _ (ITsplitipvarid _) } -- GHC extension CHAR { L _ (ITchar _) } STRING { L _ (ITstring _) } @@ -456,9 +456,8 @@ topdecl :: { OrdList (LHsDecl RdrName) } : cl_decl { unitOL (L1 (TyClD (unLoc $1))) } | ty_decl { unitOL (L1 (TyClD (unLoc $1))) } | 'instance' inst_type where - { let (binds, sigs, ats) = cvBindsAndSigs (unLoc $3) - in unitOL (L (comb3 $1 $2 $3) - (InstD (InstDecl $2 binds sigs ats))) } + { let (binds,sigs) = cvBindsAndSigs (unLoc $3) + in unitOL (L (comb3 $1 $2 $3) (InstD (InstDecl $2 binds sigs))) } | 'default' '(' comma_types0 ')' { unitOL (LL $ DefD (DefaultDecl $3)) } | 'foreign' fdecl { unitOL (LL (unLoc $2)) } | '{-# DEPRECATED' deprecations '#-}' { $2 } @@ -502,13 +501,16 @@ ty_decl :: { LTyClDecl RdrName } } } -- type family declarations - | 'type' 'family' opt_iso type '::' kind + | 'type' 'family' type opt_kind_sig -- Note the use of type for the head; this allows -- infix type constructors to be declared -- - {% do { (tc, tvs, _) <- checkSynHdr $4 False - ; return (L (comb3 $1 $4 $6) - (TyFunction tc tvs $3 (unLoc $6))) + {% do { (tc, tvs, _) <- checkSynHdr $3 False + ; let kind = case unLoc $4 of + Nothing -> liftedTypeKind + Just ki -> ki + ; return (L (comb3 $1 $3 $4) + (TyFunction tc tvs False kind)) } } -- type instance declarations @@ -540,17 +542,20 @@ ty_decl :: { LTyClDecl RdrName } ; checkTyVars tparms -- can have type pats ; return $ L (comb4 $1 $2 $4 $5) - (mkTyData (unLoc $1) (ctxt, tc, tvs, Nothing) $3 - (reverse (unLoc $5)) (unLoc $6)) } } + (mkTyData (unLoc $1) (ctxt, tc, tvs, Nothing) + (unLoc $3) (reverse (unLoc $5)) (unLoc $6)) } } -- data/newtype family - | data_or_newtype 'family' tycl_hdr '::' kind + | data_or_newtype 'family' tycl_hdr opt_kind_sig {% do { let {(ctxt, tc, tvs, tparms) = unLoc $3} ; checkTyVars tparms -- no type pattern + ; let kind = case unLoc $4 of + Nothing -> liftedTypeKind + Just ki -> ki ; return $ - L (comb3 $1 $2 $5) + L (comb3 $1 $2 $4) (mkTyData (unLoc $1) (ctxt, tc, tvs, Nothing) - (Just (unLoc $5)) [] Nothing) } } + (Just kind) [] Nothing) } } -- data/newtype instance declaration | data_or_newtype 'instance' tycl_hdr constrs deriving @@ -572,31 +577,32 @@ ty_decl :: { LTyClDecl RdrName } ; return $ L (comb4 $1 $3 $6 $7) (mkTyData (unLoc $1) (ctxt, tc, tvs, Just tparms) - $4 (reverse (unLoc $6)) (unLoc $7)) } } + (unLoc $4) (reverse (unLoc $6)) (unLoc $7)) } } -- Associate type declarations -- at_decl :: { LTyClDecl RdrName } -- type family declarations - : 'type' opt_iso type '::' kind + : 'type' type opt_kind_sig -- Note the use of type for the head; this allows -- infix type constructors to be declared -- - {% do { (tc, tvs, _) <- checkSynHdr $3 False - ; return (L (comb3 $1 $3 $5) - (TyFunction tc tvs $2 (unLoc $5))) + {% do { (tc, tvs, _) <- checkSynHdr $2 False + ; let kind = case unLoc $3 of + Nothing -> liftedTypeKind + Just ki -> ki + ; return (L (comb3 $1 $2 $3) + (TyFunction tc tvs False kind)) } } -- type instance declarations - | 'type' opt_iso type '=' ctype + | 'type' type '=' ctype -- Note the use of type for the head; this allows -- infix type constructors and type patterns -- - {% do { when $2 $ - parseError (comb2 $1 $>) "Misplaced iso keyword" - ; (tc, tvs, typats) <- checkSynHdr $3 True - ; return (L (comb2 $1 $5) - (TySynonym tc tvs (Just typats) $5)) + {% do { (tc, tvs, typats) <- checkSynHdr $2 True + ; return (L (comb2 $1 $4) + (TySynonym tc tvs (Just typats) $4)) } } -- data/newtype family @@ -628,7 +634,7 @@ at_decl :: { LTyClDecl RdrName } ; return $ L (comb4 $1 $2 $5 $6) (mkTyData (unLoc $1) (ctxt, tc, tvs, Just tparms) - $3 (reverse (unLoc $5)) (unLoc $6)) } } + (unLoc $3) (reverse (unLoc $5)) (unLoc $6)) } } opt_iso :: { Bool } : { False } @@ -638,9 +644,9 @@ data_or_newtype :: { Located NewOrData } : 'data' { L1 DataType } | 'newtype' { L1 NewType } -opt_kind_sig :: { Maybe Kind } - : { Nothing } - | '::' kind { Just (unLoc $2) } +opt_kind_sig :: { Located (Maybe Kind) } + : { noLoc Nothing } + | '::' kind { LL (Just (unLoc $2)) } -- tycl_hdr parses the header of a class or data type decl, -- which takes the form @@ -657,6 +663,16 @@ tycl_hdr :: { Located (LHsContext RdrName, | type {% checkTyClHdr (noLoc []) $1 >>= return.L1 } ----------------------------------------------------------------------------- +-- Stand-alone deriving + +-- Glasgow extension: stand-alone deriving declarations +stand_alone_deriving :: { LDerivDecl RdrName } + : 'deriving' qtycon 'for' qtycon {% do { p <- checkInstType (fmap HsTyVar $2) + ; checkDerivDecl (LL (DerivDecl p $4)) } } + + | 'deriving' '(' inst_type ')' 'for' qtycon {% checkDerivDecl (LL (DerivDecl $3 $6)) } + +----------------------------------------------------------------------------- -- Nested declarations -- Type declaration or value declaration @@ -1375,8 +1391,7 @@ dbind :: { LIPBind RdrName } dbind : ipvar '=' exp { LL (IPBind (unLoc $1) $3) } ipvar :: { Located (IPName RdrName) } - : IPDUPVARID { L1 (Dupable (mkUnqual varName (getIPDUPVARID $1))) } - | IPSPLITVARID { L1 (Linear (mkUnqual varName (getIPSPLITVARID $1))) } + : IPDUPVARID { L1 (IPName (mkUnqual varName (getIPDUPVARID $1))) } ----------------------------------------------------------------------------- -- Deprecations @@ -1641,7 +1656,6 @@ getQCONID (L _ (ITqconid x)) = x getQVARSYM (L _ (ITqvarsym x)) = x getQCONSYM (L _ (ITqconsym x)) = x getIPDUPVARID (L _ (ITdupipvarid x)) = x -getIPSPLITVARID (L _ (ITsplitipvarid x)) = x getCHAR (L _ (ITchar x)) = x getSTRING (L _ (ITstring x)) = x getINTEGER (L _ (ITinteger x)) = x