X-Git-Url: http://git.megacz.com/?p=ghc-hetmet.git;a=blobdiff_plain;f=compiler%2FhsSyn%2FHsBinds.lhs;h=8847e62c10f3398458b3b70184fd20bfc94b45e1;hp=90442dfc99a0d4b34b1fe02be833b011bc408e94;hb=4385caba003064bb556f965b32fdc962ea19ea69;hpb=3787d9878e4d62829a555f01b2a4c5866f24f303 diff --git a/compiler/hsSyn/HsBinds.lhs b/compiler/hsSyn/HsBinds.lhs index 90442df..8847e62 100644 --- a/compiler/hsSyn/HsBinds.lhs +++ b/compiler/hsSyn/HsBinds.lhs @@ -7,7 +7,7 @@ Datatype for: @BindGroup@, @Bind@, @Sig@, @Bind@. \begin{code} -{-# OPTIONS -w #-} +{-# OPTIONS -fno-warn-incomplete-patterns #-} -- 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 +16,6 @@ Datatype for: @BindGroup@, @Bind@, @Sig@, @Bind@. module HsBinds where -#include "HsVersions.h" - import {-# SOURCE #-} HsExpr ( HsExpr, pprExpr, LHsExpr, MatchGroup, pprFunBind, GRHSs, pprPatBind ) @@ -35,6 +33,7 @@ import SrcLoc import Util import Var import Bag +import FastString \end{code} %************************************************************************ @@ -87,7 +86,7 @@ data HsBindLR idL idR -- Reason 1: Special case for type inference: see TcBinds.tcMonoBinds -- -- Reason 2: instance decls can only have FunBinds, which is convenient --- If you change this, you'll need tochange e.g. rnMethodBinds +-- If you change this, you'll need to change e.g. rnMethodBinds -- But note that the form f :: a->a = ... -- parses as a pattern binding, just like @@ -178,8 +177,8 @@ instance (OutputableBndr idL, OutputableBndr idR) => Outputable (HsValBindsLR id pprValBindsForUser (unionManyBags (map snd sccs)) sigs where ppr_scc (rec_flag, binds) = pp_rec rec_flag <+> pprLHsBinds binds - pp_rec Recursive = ptext SLIT("rec") - pp_rec NonRecursive = ptext SLIT("nonrec") + pp_rec Recursive = ptext (sLit "rec") + pp_rec NonRecursive = ptext (sLit "nonrec") -- *not* pprLHsBinds because we don't want braces; 'let' and -- 'where' include a list of HsBindGroups and we don't want @@ -275,7 +274,7 @@ ppr_monobind (FunBind { fun_id = fun, fun_infix = inf, ppr_monobind (AbsBinds { abs_tvs = tyvars, abs_dicts = dictvars, abs_exports = exports, abs_binds = val_binds }) - = sep [ptext SLIT("AbsBinds"), + = sep [ptext (sLit "AbsBinds"), brackets (interpp'SP tyvars), brackets (interpp'SP dictvars), brackets (sep (punctuate comma (map ppr_exp exports)))] @@ -285,7 +284,7 @@ ppr_monobind (AbsBinds { abs_tvs = tyvars, abs_dicts = dictvars, $$ pprLHsBinds val_binds ) where ppr_exp (tvs, gbl, lcl, prags) - = vcat [ppr gbl <+> ptext SLIT("<=") <+> ppr tvs <+> ppr lcl, + = vcat [ppr gbl <+> ptext (sLit "<=") <+> ppr tvs <+> ppr lcl, nest 2 (vcat (map (pprPrag gbl) prags))] \end{code} @@ -338,7 +337,7 @@ data HsWrapper | WpCompose HsWrapper HsWrapper -- (\a1..an. []) `WpCompose` (\x1..xn. []) -- = (\a1..an \x1..xn. []) - | WpCo Coercion -- A cast: [] `cast` co + | WpCast Coercion -- A cast: [] `cast` co -- Guaranteedn not the identity coercion | WpApp Var -- [] d the 'd' is a type-class dictionary @@ -353,20 +352,20 @@ data HsWrapper -- (would be nicer to be core bindings) instance Outputable HsWrapper where - ppr co_fn = pprHsWrapper (ptext SLIT("<>")) co_fn + ppr co_fn = pprHsWrapper (ptext (sLit "<>")) co_fn pprHsWrapper :: SDoc -> HsWrapper -> SDoc pprHsWrapper it wrap = let help it WpHole = it help it (WpCompose f1 f2) = help (help it f2) f1 - help it (WpCo co) = sep [it, nest 2 (ptext SLIT("`cast`") <+> pprParendType co)] + help it (WpCast co) = sep [it, nest 2 (ptext (sLit "`cast`") <+> pprParendType co)] help it (WpApp id) = sep [it, nest 2 (ppr id)] - help it (WpTyApp ty) = sep [it, ptext SLIT("@") <+> pprParendType ty] - help it (WpLam id) = sep [ptext SLIT("\\") <> pprBndr LambdaBind id <> dot, it] - help it (WpTyLam tv) = sep [ptext SLIT("/\\") <> pprBndr LambdaBind tv <> dot, it] - help it (WpLet binds) = sep [ptext SLIT("let") <+> braces (ppr binds), it] - help it WpInline = sep [ptext SLIT("_inline_me_"), it] + help it (WpTyApp ty) = sep [it, ptext (sLit "@") <+> pprParendType ty] + help it (WpLam id) = sep [ptext (sLit "\\") <> pprBndr LambdaBind id <> dot, it] + help it (WpTyLam tv) = sep [ptext (sLit "/\\") <> pprBndr LambdaBind tv <> dot, it] + help it (WpLet binds) = sep [ptext (sLit "let") <+> braces (ppr binds), it] + help it WpInline = sep [ptext (sLit "_inline_me_"), it] in -- in debug mode, print the wrapper -- otherwise just print what's inside @@ -397,7 +396,7 @@ idHsWrapper = WpHole isIdHsWrapper :: HsWrapper -> Bool isIdHsWrapper WpHole = True -isIdHsWrapper other = False +isIdHsWrapper _ = False \end{code} @@ -454,38 +453,34 @@ data Prag | SpecPrag (HsExpr Id) -- An expression, of the given specialised type, which PostTcType -- specialises the polymorphic function - [Id] -- Dicts mentioned free in the expression - -- Apr07: I think this is pretty useless - -- see Note [Const rule dicts] in DsBinds InlineSpec -- Inlining spec for the specialised function +isInlinePrag :: Prag -> Bool isInlinePrag (InlinePrag _) = True -isInlinePrag prag = False +isInlinePrag _ = False +isSpecPrag :: Prag -> Bool isSpecPrag (SpecPrag {}) = True -isSpecPrag prag = False +isSpecPrag _ = False \end{code} \begin{code} -okBindSig :: NameSet -> LSig Name -> Bool -okBindSig ns sig = sigForThisGroup ns sig +okBindSig :: Sig a -> Bool +okBindSig _ = True -okHsBootSig :: LSig Name -> Bool -okHsBootSig (L _ (TypeSig _ _)) = True -okHsBootSig (L _ (FixSig _)) = True -okHsBootSig sig = False +okHsBootSig :: Sig a -> Bool +okHsBootSig (TypeSig _ _) = True +okHsBootSig (FixSig _) = True +okHsBootSig _ = False -okClsDclSig :: LSig Name -> Bool -okClsDclSig (L _ (SpecInstSig _)) = False -okClsDclSig sig = True -- All others OK +okClsDclSig :: Sig a -> Bool +okClsDclSig (SpecInstSig _) = False +okClsDclSig _ = True -- All others OK -okInstDclSig :: NameSet -> LSig Name -> Bool -okInstDclSig ns lsig@(L _ sig) = ok ns sig - where - ok ns (TypeSig _ _) = False - ok ns (FixSig _) = False - ok ns (SpecInstSig _) = True - ok ns sig = sigForThisGroup ns lsig +okInstDclSig :: Sig a -> Bool +okInstDclSig (TypeSig _ _) = False +okInstDclSig (FixSig _) = False +okInstDclSig _ = True sigForThisGroup :: NameSet -> LSig Name -> Bool sigForThisGroup ns sig @@ -501,7 +496,7 @@ sigNameNoLoc (TypeSig n _) = Just (unLoc n) sigNameNoLoc (SpecSig n _ _) = Just (unLoc n) sigNameNoLoc (InlineSig n _) = Just (unLoc n) sigNameNoLoc (FixSig (FixitySig n _)) = Just (unLoc n) -sigNameNoLoc other = Nothing +sigNameNoLoc _ = Nothing isFixityLSig :: LSig name -> Bool isFixityLSig (L _ (FixSig {})) = True @@ -509,40 +504,42 @@ isFixityLSig _ = False isVanillaLSig :: LSig name -> Bool isVanillaLSig (L _(TypeSig {})) = True -isVanillaLSig sig = False +isVanillaLSig _ = False isSpecLSig :: LSig name -> Bool isSpecLSig (L _(SpecSig {})) = True -isSpecLSig sig = False +isSpecLSig _ = False +isSpecInstLSig :: LSig name -> Bool isSpecInstLSig (L _ (SpecInstSig {})) = True -isSpecInstLSig sig = False +isSpecInstLSig _ = False isPragLSig :: LSig name -> Bool -- Identifies pragmas isPragLSig (L _ (SpecSig {})) = True isPragLSig (L _ (InlineSig {})) = True -isPragLSig other = False +isPragLSig _ = False isInlineLSig :: LSig name -> Bool -- Identifies inline pragmas isInlineLSig (L _ (InlineSig {})) = True -isInlineLSig other = False - -hsSigDoc (TypeSig {}) = ptext SLIT("type signature") -hsSigDoc (SpecSig {}) = ptext SLIT("SPECIALISE pragma") -hsSigDoc (InlineSig _ spec) = ptext SLIT("INLINE pragma") -hsSigDoc (SpecInstSig {}) = ptext SLIT("SPECIALISE instance pragma") -hsSigDoc (FixSig {}) = ptext SLIT("fixity declaration") +isInlineLSig _ = False + +hsSigDoc :: Sig name -> SDoc +hsSigDoc (TypeSig {}) = ptext (sLit "type signature") +hsSigDoc (SpecSig {}) = ptext (sLit "SPECIALISE pragma") +hsSigDoc (InlineSig {}) = ptext (sLit "INLINE pragma") +hsSigDoc (SpecInstSig {}) = ptext (sLit "SPECIALISE instance pragma") +hsSigDoc (FixSig {}) = ptext (sLit "fixity declaration") \end{code} Signature equality is used when checking for duplicate signatures \begin{code} -eqHsSig :: LSig Name -> LSig Name -> Bool +eqHsSig :: Eq a => LSig a -> LSig a -> Bool eqHsSig (L _ (FixSig (FixitySig n1 _))) (L _ (FixSig (FixitySig n2 _))) = unLoc n1 == unLoc n2 eqHsSig (L _ (TypeSig n1 _)) (L _ (TypeSig n2 _)) = unLoc n1 == unLoc n2 -eqHsSig (L _ (InlineSig n1 s1)) (L _ (InlineSig n2 s2)) = unLoc n1 == unLoc n2 +eqHsSig (L _ (InlineSig n1 _)) (L _ (InlineSig n2 _)) = unLoc n1 == unLoc n2 -- For specialisations, we don't have equality over -- HsType, so it's not convenient to spot duplicate -- specialisations here. Check for this later, when we're in Type land @@ -558,22 +555,22 @@ ppr_sig (TypeSig var ty) = pprVarSig (unLoc var) ty ppr_sig (FixSig fix_sig) = ppr fix_sig ppr_sig (SpecSig var ty inl) = pragBrackets (pprSpec var ty inl) ppr_sig (InlineSig var inl) = pragBrackets (ppr inl <+> ppr var) -ppr_sig (SpecInstSig ty) = pragBrackets (ptext SLIT("SPECIALIZE instance") <+> ppr ty) +ppr_sig (SpecInstSig ty) = pragBrackets (ptext (sLit "SPECIALIZE instance") <+> ppr ty) instance Outputable name => Outputable (FixitySig name) where ppr (FixitySig name fixity) = sep [ppr fixity, ppr name] pragBrackets :: SDoc -> SDoc -pragBrackets doc = ptext SLIT("{-#") <+> doc <+> ptext SLIT("#-}") +pragBrackets doc = ptext (sLit "{-#") <+> doc <+> ptext (sLit "#-}") pprVarSig :: (Outputable id, Outputable ty) => id -> ty -> SDoc pprVarSig var ty = sep [ppr var <+> dcolon, nest 2 (ppr ty)] pprSpec :: (Outputable id, Outputable ty) => id -> ty -> InlineSpec -> SDoc -pprSpec var ty inl = sep [ptext SLIT("SPECIALIZE") <+> ppr inl <+> pprVarSig var ty] +pprSpec var ty inl = sep [ptext (sLit "SPECIALIZE") <+> ppr inl <+> pprVarSig var ty] pprPrag :: Outputable id => id -> LPrag -> SDoc -pprPrag var (L _ (InlinePrag inl)) = ppr inl <+> ppr var -pprPrag var (L _ (SpecPrag expr ty _ inl)) = pprSpec var ty inl +pprPrag var (L _ (InlinePrag inl)) = ppr inl <+> ppr var +pprPrag var (L _ (SpecPrag _expr ty inl)) = pprSpec var ty inl \end{code}