[project @ 1996-07-15 16:16:46 by partain]
[ghc-hetmet.git] / ghc / compiler / basicTypes / IdLoop.lhi
1 Breaks the IdInfo/<everything> loops.
2
3 \begin{code}
4 interface IdLoop where
5
6 import PreludePS        ( _PackedString )
7 import PreludeStdIO     ( Maybe )
8
9 import BinderInfo       ( BinderInfo )
10 import CoreSyn          ( CoreExpr(..), GenCoreExpr, GenCoreArg )
11 import CoreUnfold       ( Unfolding(..), UnfoldingGuidance(..), 
12                           SimpleUnfolding(..), FormSummary(..)  )
13 import CoreUtils        ( unTagBinders )
14 import Id               ( externallyVisibleId, isDataCon, isWorkerId, isWrapperId,
15                           unfoldingUnfriendlyId, getIdInfo, nmbrId,
16                           nullIdEnv, lookupIdEnv, IdEnv(..),
17                           Id(..), GenId
18                         )
19 import CostCentre       ( CostCentre )
20 import IdInfo           ( IdInfo )
21 import SpecEnv          ( SpecEnv, nullSpecEnv, isNullSpecEnv )
22 import Literal          ( Literal )
23 import MagicUFs         ( mkMagicUnfoldingFun, MagicUnfoldingFun )
24 import OccurAnal        ( occurAnalyseGlobalExpr )
25 import Outputable       ( Outputable(..) )
26 import PprEnv           ( NmbrEnv )
27 import PprStyle         ( PprStyle )
28 import PprType          ( pprParendGenType )
29 import Pretty           ( PrettyRep )
30 import Type             ( GenType )
31 import TyVar            ( GenTyVar )
32 import UniqFM           ( UniqFM )
33 import Unique           ( Unique )
34 import Usage            ( GenUsage )
35 import Util             ( Ord3(..) )
36 import WwLib            ( mAX_WORKER_ARGS )
37
38 nullSpecEnv   :: SpecEnv
39 isNullSpecEnv :: SpecEnv -> Bool
40
41 occurAnalyseGlobalExpr  :: GenCoreExpr (GenId (GenType (GenTyVar (GenUsage Unique)) Unique)) (GenId (GenType (GenTyVar (GenUsage Unique)) Unique)) (GenTyVar (GenUsage Unique)) Unique -> GenCoreExpr (GenId (GenType (GenTyVar (GenUsage Unique)) Unique), BinderInfo) (GenId (GenType (GenTyVar (GenUsage Unique)) Unique)) (GenTyVar (GenUsage Unique)) Unique
42 externallyVisibleId     :: Id       -> Bool
43 isDataCon               :: GenId ty -> Bool
44 isWorkerId              :: GenId ty -> Bool
45 isWrapperId             :: Id       -> Bool
46 unfoldingUnfriendlyId   :: Id       -> Bool
47 getIdInfo               :: Id       -> IdInfo
48 nullIdEnv               :: UniqFM a
49 lookupIdEnv             :: UniqFM b -> GenId a -> Maybe b
50 mAX_WORKER_ARGS         :: Int
51 nmbrId                  :: Id -> NmbrEnv -> (NmbrEnv, Id)
52 pprParendGenType                :: (Eq a, Outputable a, Eq b, Outputable b) => PprStyle -> GenType a b -> Int -> Bool -> PrettyRep
53 unTagBinders :: GenCoreExpr (GenId (GenType (GenTyVar (GenUsage Unique)) Unique), a) b c d -> GenCoreExpr (GenId (GenType (GenTyVar (GenUsage Unique)) Unique)) b c d
54
55 mkMagicUnfoldingFun     :: Unique -> MagicUnfoldingFun
56
57 type IdEnv a = UniqFM a
58 type CoreExpr = GenCoreExpr (GenId (GenType (GenTyVar (GenUsage Unique)) Unique))
59                             (GenId (GenType (GenTyVar (GenUsage Unique)) Unique))
60                             (GenTyVar (GenUsage Unique)) Unique
61
62 instance Outputable UnfoldingGuidance
63 instance Eq         Unique
64 instance Outputable Unique
65 instance Eq         (GenTyVar a)
66 instance Ord3       (GenTyVar a)
67 instance Outputable (GenTyVar a)
68 instance (Outputable a) => Outputable (GenId a)
69 instance (Eq a, Outputable a, Eq b, Outputable b) => Outputable (GenType a b)
70
71 data SpecEnv
72 data NmbrEnv
73 data MagicUnfoldingFun
74 data FormSummary = VarForm | ValueForm | BottomForm | OtherForm
75
76 data Unfolding
77   = NoUnfolding
78   | CoreUnfolding SimpleUnfolding
79   | MagicUnfolding Unique MagicUnfoldingFun
80
81
82 data SimpleUnfolding = SimpleUnfolding FormSummary UnfoldingGuidance (GenCoreExpr (GenId (GenType (GenTyVar (GenUsage Unique)) Unique), BinderInfo) (GenId (GenType (GenTyVar (GenUsage Unique)) Unique)) (GenTyVar (GenUsage Unique)) Unique) 
83
84
85 data UnfoldingGuidance
86   = UnfoldNever
87   | UnfoldAlways
88   | UnfoldIfGoodArgs Int Int [Bool] Int
89
90 data CostCentre
91 \end{code}
92
93
94
95