diff options
author | qrczak <unknown> | 2001-05-01 09:16:56 +0000 |
---|---|---|
committer | qrczak <unknown> | 2001-05-01 09:16:56 +0000 |
commit | df65fd0b7646ffa17ed553289a4cd0e806bef8b9 (patch) | |
tree | c3389d6dff99858ed1de9486ca693623d4dda54b /ghc/compiler/hsSyn/HsBinds.lhs | |
parent | 4af93602d4ff7b847e55c377604d3e42f401a099 (diff) | |
download | haskell-df65fd0b7646ffa17ed553289a4cd0e806bef8b9.tar.gz |
[project @ 2001-05-01 09:16:55 by qrczak]
Inline instance dictionary functions.
Remove {-# INLINE instance #-} support and uses.
Diffstat (limited to 'ghc/compiler/hsSyn/HsBinds.lhs')
-rw-r--r-- | ghc/compiler/hsSyn/HsBinds.lhs | 12 |
1 files changed, 1 insertions, 11 deletions
diff --git a/ghc/compiler/hsSyn/HsBinds.lhs b/ghc/compiler/hsSyn/HsBinds.lhs index 13f6047462..9576c6d601 100644 --- a/ghc/compiler/hsSyn/HsBinds.lhs +++ b/ghc/compiler/hsSyn/HsBinds.lhs @@ -261,9 +261,6 @@ data Sig name -- current instance decl SrcLoc - | InlineInstSig (Maybe Int) -- phase - SrcLoc - | FixSig (FixitySig name) -- Fixity declaration @@ -286,7 +283,6 @@ okInstDclSig :: NameSet -> Sig Name -> Bool okInstDclSig ns (Sig _ _ _) = False okInstDclSig ns (FixSig _) = False okInstDclSig ns (SpecInstSig _ _) = True -okInstDclSig ns (InlineInstSig _ _) = True okInstDclSig ns sig = sigForThisGroup ns sig sigForThisGroup ns sig @@ -318,7 +314,6 @@ isPragSig (SpecSig _ _ _) = True isPragSig (InlineSig _ _ _) = True isPragSig (NoInlineSig _ _ _) = True isPragSig (SpecInstSig _ _) = True -isPragSig (InlineInstSig _ _) = True isPragSig other = False \end{code} @@ -329,7 +324,6 @@ hsSigDoc (SpecSig _ _ loc) = (SLIT("SPECIALISE pragma"),loc) hsSigDoc (InlineSig _ _ loc) = (SLIT("INLINE pragma"),loc) hsSigDoc (NoInlineSig _ _ loc) = (SLIT("NOINLINE pragma"),loc) hsSigDoc (SpecInstSig _ loc) = (SLIT("SPECIALISE instance pragma"),loc) -hsSigDoc (InlineInstSig _ loc) = (SLIT("INLINE instance pragma"),loc) hsSigDoc (FixSig (FixitySig _ _ loc)) = (SLIT("fixity declaration"), loc) \end{code} @@ -363,9 +357,6 @@ ppr_sig (NoInlineSig var phase _) ppr_sig (SpecInstSig ty _) = hsep [text "{-# SPECIALIZE instance", ppr ty, text "#-}"] -ppr_sig (InlineInstSig phase _) - = hsep [text "{-# INLINE instance", ppr_phase phase, text "#-}"] - ppr_sig (FixSig fix_sig) = ppr fix_sig @@ -391,7 +382,6 @@ eqHsSig (SpecSig n1 ty1 _) (SpecSig n2 ty2 _) = -- may have many specialisations for one value; -- but not ones that are exactly the same... (n1 == n2) && (ty1 == ty2) -eqHsSig (InlineInstSig _ _) (InlineInstSig _ _) = True -eqHsSig other_1 other_2 = False +eqHsSig _other1 _other2 = False \end{code} |