[project @ 1997-03-14 07:52:06 by simonpj]
[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 FastString       ( FastString )
8 import PreludeStdIO     ( Maybe )
9
10 import BinderInfo       ( BinderInfo )
11 import CoreSyn          ( CoreExpr(..), GenCoreExpr, GenCoreArg )
12 import CoreUnfold       ( Unfolding(..), UnfoldingGuidance(..), 
13                           SimpleUnfolding(..), FormSummary(..), noUnfolding  )
14 import CoreUtils        ( unTagBinders )
15 import Id               ( externallyVisibleId, isDataCon, isWorkerId, isWrapperId,
16                           unfoldingUnfriendlyId, getIdInfo, nmbrId,
17                           nullIdEnv, lookupIdEnv, IdEnv(..),
18                           Id(..), GenId
19                         )
20 import CostCentre       ( CostCentre,
21                           noCostCentre, subsumedCosts, cafifyCC,
22                           useCurrentCostCentre, dontCareCostCentre,
23                           overheadCostCentre, preludeCafsCostCentre,
24                           preludeDictsCostCentre, mkAllCafsCC,
25                           mkAllDictsCC, mkUserCC
26                         )
27 import IdInfo           ( IdInfo )
28 import SpecEnv          ( SpecEnv, nullSpecEnv, isNullSpecEnv )
29 import Literal          ( Literal )
30 import MagicUFs         ( mkMagicUnfoldingFun, MagicUnfoldingFun )
31 import OccurAnal        ( occurAnalyseGlobalExpr )
32 import Outputable       ( Outputable(..) )
33 import PprEnv           ( NmbrEnv )
34 import PprStyle         ( PprStyle )
35 import PprType          ( pprParendGenType )
36 import Pretty           ( PrettyRep )
37 import Type             ( GenType )
38 import TyVar            ( GenTyVar )
39 import UniqFM           ( UniqFM )
40 import Unique           ( Unique )
41 import Usage            ( GenUsage )
42 import Util             ( Ord3(..) )
43 import WwLib            ( mAX_WORKER_ARGS )
44 import StdIdInfo        ( addStandardIdInfo )   -- Used in Id, but StdIdInfo needs lots of stuff from Id
45
46 addStandardIdInfo :: Id -> Id
47
48 nullSpecEnv   :: SpecEnv
49 isNullSpecEnv :: SpecEnv -> Bool
50
51 -- 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
52 -- unTagBinders :: GenCoreExpr (GenId (GenType (GenTyVar (GenUsage Unique)) Unique), a) b c d -> GenCoreExpr (GenId (GenType (GenTyVar (GenUsage Unique)) Unique)) b c d
53
54 externallyVisibleId     :: Id       -> Bool
55 isDataCon               :: GenId ty -> Bool
56 isWorkerId              :: GenId ty -> Bool
57 isWrapperId             :: Id       -> Bool
58 unfoldingUnfriendlyId   :: Id       -> Bool
59 getIdInfo               :: Id       -> IdInfo
60 nullIdEnv               :: UniqFM a
61 lookupIdEnv             :: UniqFM b -> GenId a -> Maybe b
62 mAX_WORKER_ARGS         :: Int
63 nmbrId                  :: Id -> NmbrEnv -> (NmbrEnv, Id)
64 pprParendGenType        :: (Eq a, Outputable a, Eq b, Outputable b) => PprStyle -> GenType a b -> Int -> Bool -> PrettyRep
65 mkMagicUnfoldingFun     :: Unique -> MagicUnfoldingFun
66
67 type IdEnv a = UniqFM a
68 type CoreExpr = GenCoreExpr (GenId (GenType (GenTyVar (GenUsage Unique)) Unique))
69                             (GenId (GenType (GenTyVar (GenUsage Unique)) Unique))
70                             (GenTyVar (GenUsage Unique)) Unique
71
72 instance Outputable UnfoldingGuidance
73 instance Eq         Unique
74 instance Outputable Unique
75 instance Eq         (GenTyVar a)
76 instance Ord3       (GenTyVar a)
77 instance Outputable (GenTyVar a)
78 instance (Outputable a) => Outputable (GenId a)
79 instance (Eq a, Outputable a, Eq b, Outputable b) => Outputable (GenType a b)
80
81 data SpecEnv
82 data NmbrEnv
83 data MagicUnfoldingFun
84 data FormSummary = VarForm | ValueForm | BottomForm | OtherForm
85
86 -- data Unfolding
87 --  = NoUnfolding
88 --  | CoreUnfolding SimpleUnfolding
89 --  | MagicUnfolding Unique MagicUnfoldingFun
90
91 data Unfolding
92 noUnfolding :: Unfolding
93
94 -- data SimpleUnfolding = SimpleUnfolding FormSummary UnfoldingGuidance (GenCoreExpr (GenId (GenType (GenTyVar (GenUsage Unique)) Unique), BinderInfo) (GenId (GenType (GenTyVar (GenUsage Unique)) Unique)) (GenTyVar (GenUsage Unique)) Unique) 
95
96
97 data UnfoldingGuidance
98   = UnfoldNever
99   | UnfoldAlways
100   | UnfoldIfGoodArgs Int Int [Bool] Int
101
102 data CostCentre
103
104 noCostCentre           :: CostCentre
105 subsumedCosts          :: CostCentre
106 useCurrentCostCentre   :: CostCentre
107 dontCareCostCentre     :: CostCentre
108 overheadCostCentre     :: CostCentre
109 preludeCafsCostCentre  :: CostCentre
110 preludeDictsCostCentre :: Bool -> CostCentre
111 mkAllCafsCC            :: FastString -> FastString -> CostCentre
112 mkAllDictsCC           :: FastString -> FastString -> Bool -> CostCentre
113 mkUserCC               :: FastString -> FastString -> FastString -> CostCentre
114 cafifyCC               :: CostCentre -> CostCentre
115 \end{code}