summaryrefslogtreecommitdiff
path: root/ghc/compiler
diff options
context:
space:
mode:
authorqrczak <unknown>2001-05-01 09:16:56 +0000
committerqrczak <unknown>2001-05-01 09:16:56 +0000
commitdf65fd0b7646ffa17ed553289a4cd0e806bef8b9 (patch)
treec3389d6dff99858ed1de9486ca693623d4dda54b /ghc/compiler
parent4af93602d4ff7b847e55c377604d3e42f401a099 (diff)
downloadhaskell-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')
-rw-r--r--ghc/compiler/hsSyn/HsBinds.lhs12
-rw-r--r--ghc/compiler/parser/Parser.y3
-rw-r--r--ghc/compiler/rename/RnBinds.lhs3
-rw-r--r--ghc/compiler/typecheck/TcInstDcls.lhs4
4 files changed, 4 insertions, 18 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}
diff --git a/ghc/compiler/parser/Parser.y b/ghc/compiler/parser/Parser.y
index 93c663d986..6f09c9f0b1 100644
--- a/ghc/compiler/parser/Parser.y
+++ b/ghc/compiler/parser/Parser.y
@@ -1,6 +1,6 @@
{-
-----------------------------------------------------------------------------
-$Id: Parser.y,v 1.57 2001/04/14 22:24:24 qrczak Exp $
+$Id: Parser.y,v 1.58 2001/05/01 09:16:55 qrczak Exp $
Haskell grammar.
@@ -388,7 +388,6 @@ decl :: { RdrBinding }
| valdef { $1 }
| '{-# INLINE' srcloc opt_phase qvar '#-}' { RdrSig (InlineSig $4 $3 $2) }
| '{-# NOINLINE' srcloc opt_phase qvar '#-}' { RdrSig (NoInlineSig $4 $3 $2) }
- | '{-# INLINE' srcloc 'instance' opt_phase '#-}' { RdrSig (InlineInstSig $4 $2) }
| '{-# SPECIALISE' srcloc qvar '::' sigtypes '#-}'
{ foldr1 RdrAndBindings
(map (\t -> RdrSig (SpecSig $3 t $2)) $5) }
diff --git a/ghc/compiler/rename/RnBinds.lhs b/ghc/compiler/rename/RnBinds.lhs
index 7b2cf88e7c..137e916192 100644
--- a/ghc/compiler/rename/RnBinds.lhs
+++ b/ghc/compiler/rename/RnBinds.lhs
@@ -524,9 +524,6 @@ renameSig (SpecInstSig ty src_loc)
rnHsType (text "A SPECIALISE instance pragma") ty `thenRn` \ new_ty ->
returnRn (SpecInstSig new_ty src_loc)
-renameSig (InlineInstSig p src_loc)
- = returnRn (InlineInstSig p src_loc)
-
renameSig (SpecSig v ty src_loc)
= pushSrcLocRn src_loc $
lookupSigOccRn v `thenRn` \ new_v ->
diff --git a/ghc/compiler/typecheck/TcInstDcls.lhs b/ghc/compiler/typecheck/TcInstDcls.lhs
index 95add917f6..9b478e01e2 100644
--- a/ghc/compiler/typecheck/TcInstDcls.lhs
+++ b/ghc/compiler/typecheck/TcInstDcls.lhs
@@ -52,7 +52,7 @@ import FunDeps ( checkInstFDs )
import Generics ( validGenericInstanceType )
import Module ( Module, foldModuleEnv )
import Name ( getSrcLoc )
-import NameSet ( emptyNameSet, mkNameSet, nameSetToList )
+import NameSet ( emptyNameSet, unitNameSet, nameSetToList )
import PrelInfo ( eRROR_ID )
import PprType ( pprClassPred, pprPred )
import TyCon ( TyCon, isSynTyCon )
@@ -601,7 +601,7 @@ tcInstDecl2 (InstInfo { iDFunId = dfun_id,
dict_constr = classDataCon clas
scs_and_meths = map instToId (sc_dicts ++ meth_insts)
this_dict_id = instToId this_dict
- inlines = mkNameSet [idName dfun_id | InlineInstSig _ _ <- uprags]
+ inlines = unitNameSet (idName dfun_id)
dict_rhs
| null scs_and_meths