diff options
author | sof <unknown> | 1997-07-05 02:48:31 +0000 |
---|---|---|
committer | sof <unknown> | 1997-07-05 02:48:31 +0000 |
commit | 9649365acad43e7da35a372bb6b2c21c4ef24e6f (patch) | |
tree | 4e55d2b7e6ce45bd1e7a5a49cd73cfb80d10b7ca /ghc/compiler | |
parent | 5a823880ee5767fc173665925c889dff677b9346 (diff) | |
download | haskell-9649365acad43e7da35a372bb6b2c21c4ef24e6f.tar.gz |
[project @ 1997-07-05 02:46:26 by sof]
Diffstat (limited to 'ghc/compiler')
-rw-r--r-- | ghc/compiler/specialise/Specialise.lhs | 2 | ||||
-rw-r--r-- | ghc/compiler/stgSyn/CoreToStg.lhs | 5 | ||||
-rw-r--r-- | ghc/compiler/stranal/SaLib.lhs | 2 | ||||
-rw-r--r-- | ghc/compiler/stranal/StrictAnal.lhs | 2 |
4 files changed, 6 insertions, 5 deletions
diff --git a/ghc/compiler/specialise/Specialise.lhs b/ghc/compiler/specialise/Specialise.lhs index 433d8afc88..803e4a49e9 100644 --- a/ghc/compiler/specialise/Specialise.lhs +++ b/ghc/compiler/specialise/Specialise.lhs @@ -30,7 +30,7 @@ import FiniteMap ( addListToFM_C, FiniteMap ) import Kind ( mkBoxedTypeKind, isBoxedTypeKind ) import Id ( idType, isDefaultMethodId_maybe, toplevelishId, isSuperDictSelId_maybe, isBottomingId, - isConstMethodId_maybe, isDataCon, + isDataCon, isImportedId, mkIdWithNewUniq, dataConTyCon, applyTypeEnvToId, nullIdEnv, addOneToIdEnv, growIdEnvList, diff --git a/ghc/compiler/stgSyn/CoreToStg.lhs b/ghc/compiler/stgSyn/CoreToStg.lhs index 4fda0268f6..16ab5e5fea 100644 --- a/ghc/compiler/stgSyn/CoreToStg.lhs +++ b/ghc/compiler/stgSyn/CoreToStg.lhs @@ -42,7 +42,9 @@ import Type ( getAppDataTyConExpandingDicts, SYN_IE(Type) ) import TysWiredIn ( stringTy ) import Unique ( integerTyConKey, ratioTyConKey, Unique{-instance Eq-} ) import UniqSupply -- all of it, really -import Util ( zipLazy, panic, assertPanic{-, pprTrace ToDo:rm-} ) +import Util ( zipLazy, panic, assertPanic, pprTrace {-TEMP-} ) +import Pretty +import Outputable isLeakFreeType x y = False -- safe option; ToDo \end{code} @@ -293,7 +295,6 @@ coreExprToStg env expr@(App _ _) coreExprToStg env non_var_fun other -> -- A non-variable applied to things; better let-bind it. --- pprTrace "coreExprToStg" (ppr PprDebug expr) $ newStgVar (coreExprType fun) `thenUs` \ fun_id -> coreExprToStg env fun `thenUs` \ (stg_fun) -> let diff --git a/ghc/compiler/stranal/SaLib.lhs b/ghc/compiler/stranal/SaLib.lhs index d31d892e3e..485b597f10 100644 --- a/ghc/compiler/stranal/SaLib.lhs +++ b/ghc/compiler/stranal/SaLib.lhs @@ -107,7 +107,7 @@ lookupAbsValEnv (AbsValEnv idenv) y \end{code} \begin{code} -absValFromStrictness :: AnalysisKind -> StrictnessInfo bdee -> AbsVal +absValFromStrictness :: AnalysisKind -> StrictnessInfo -> AbsVal absValFromStrictness anal NoStrictnessInfo = AbsTop diff --git a/ghc/compiler/stranal/StrictAnal.lhs b/ghc/compiler/stranal/StrictAnal.lhs index 751b671cef..d0ea862b10 100644 --- a/ghc/compiler/stranal/StrictAnal.lhs +++ b/ghc/compiler/stranal/StrictAnal.lhs @@ -394,7 +394,7 @@ addStrictnessInfoToId str_val abs_val binder body = case (collectBinders body) of (_, _, [], rhs) -> binder (_, _, lambda_bounds, rhs) -> binder `addIdStrictness` - mkStrictnessInfo strictness Nothing + mkStrictnessInfo strictness False where tys = map idType lambda_bounds strictness = findStrictness tys str_val abs_val |