X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=ghc%2Fcompiler%2FhsSyn%2FHsDecls.lhs;h=8ff39857c610ab4d4af4e3ef09c914af3818651a;hb=f85903abe9103e545ea5b1dc6fdd6b672da4f3f2;hp=ddd11a662d86e1a4c240898f440a86e9a648bdc6;hpb=36436bc62a98f53e126ec02fe946337c4c766c3f;p=ghc-hetmet.git diff --git a/ghc/compiler/hsSyn/HsDecls.lhs b/ghc/compiler/hsSyn/HsDecls.lhs index ddd11a6..8ff3985 100644 --- a/ghc/compiler/hsSyn/HsDecls.lhs +++ b/ghc/compiler/hsSyn/HsDecls.lhs @@ -36,6 +36,7 @@ import HsBinds ( HsValBinds(..), HsBind, LHsBinds, plusHsValBinds, import HsPat ( HsConDetails(..), hsConArgs ) import HsImpExp ( pprHsVar ) import HsTypes +import NameSet ( NameSet ) import HscTypes ( DeprecTxt ) import CoreSyn ( RuleName ) import Kind ( Kind, pprKind ) @@ -110,7 +111,8 @@ emptyRnGroup = emptyGroup { hs_valds = emptyValBindsOut } emptyGroup = HsGroup { hs_tyclds = [], hs_instds = [], hs_fixds = [], hs_defds = [], hs_fords = [], - hs_depds = [] ,hs_ruleds = [] } + hs_depds = [], hs_ruleds = [], + hs_valds = error "emptyGroup hs_valds: Can't happen" } appendGroups :: HsGroup a -> HsGroup a -> HsGroup a appendGroups @@ -405,7 +407,7 @@ tyClDeclNames (TySynonym {tcdLName = name}) = [name] tyClDeclNames (ForeignType {tcdLName = name}) = [name] tyClDeclNames (ClassDecl {tcdLName = cls_name, tcdSigs = sigs}) - = cls_name : [n | L _ (Sig n _) <- sigs] + = cls_name : [n | L _ (TypeSig n _) <- sigs] tyClDeclNames (TyData {tcdLName = tc_name, tcdCons = cons}) = tc_name : conDeclsNames (map unLoc cons) @@ -500,6 +502,18 @@ instance Outputable NewOrData where \begin{code} type LConDecl name = Located (ConDecl name) +-- data T b = forall a. Eq a => MkT a b +-- MkT :: forall b a. Eq a => MkT a b + +-- data T b where +-- MkT1 :: Int -> T Int + +-- data T = Int `MkT` Int +-- | MkT2 + +-- data T a where +-- Int `MkT` Int :: T Int + data ConDecl name = ConDecl { con_name :: Located name -- Constructor name; this is used for the @@ -560,7 +574,6 @@ pprConDecl (ConDecl con expl tvs cxt details (ResTyGADT res_ty)) where ppr_details (PrefixCon arg_tys) = dcolon <+> ppr (foldr mk_fun_ty res_ty arg_tys) ppr_details (RecCon fields) = ppr fields <+> dcolon <+> ppr res_ty - ppr_details (PrefixCon _) = pprPanic "pprConDecl" (ppr con) mk_fun_ty a b = noLoc (HsFunTy a b) @@ -709,8 +722,8 @@ instance Outputable ForeignImport where ptext SLIT("dynamic") pprCEntity _ _ (CWrapper) = ptext SLIT("wrapper") -- - pprLib lib | nullFastString lib = empty - | otherwise = char '[' <> ppr lib <> char ']' + pprLib lib | nullFS lib = empty + | otherwise = char '[' <> ppr lib <> char ']' instance Outputable ForeignExport where ppr (CExport (CExportStatic lbl cconv)) = @@ -738,7 +751,9 @@ data RuleDecl name Activation [RuleBndr name] -- Forall'd vars; after typechecking this includes tyvars (Located (HsExpr name)) -- LHS + NameSet -- Free-vars from the LHS (Located (HsExpr name)) -- RHS + NameSet -- Free-vars from the RHS data RuleBndr name = RuleBndr (Located name) @@ -748,7 +763,7 @@ collectRuleBndrSigTys :: [RuleBndr name] -> [LHsType name] collectRuleBndrSigTys bndrs = [ty | RuleBndrSig _ ty <- bndrs] instance OutputableBndr name => Outputable (RuleDecl name) where - ppr (HsRule name act ns lhs rhs) + ppr (HsRule name act ns lhs fv_lhs rhs fv_rhs) = sep [text "{-# RULES" <+> doubleQuotes (ftext name) <+> ppr act, nest 4 (pp_forall <+> pprExpr (unLoc lhs)), nest 4 (equals <+> pprExpr (unLoc rhs) <+> text "#-}") ]