[project @ 1997-03-14 07:52:06 by simonpj]
[ghc-hetmet.git] / ghc / compiler / utils / Ubiq.lhi
1 Things which are ubiquitous in the GHC compiler.
2
3 \begin{code}
4 interface Ubiq where
5
6 --import PreludePS(_PackedString)
7 import FastString(FastString)
8
9 import Bag              ( Bag )
10 import BinderInfo       ( BinderInfo )
11 import CgBindery        ( CgIdInfo )
12 import CharSeq          ( CSeq )
13 import CLabel           ( CLabel )
14 import Class            ( GenClass, GenClassOp, Class(..), ClassOp )
15 import ClosureInfo      ( ClosureInfo, LambdaFormInfo )
16 import CmdLineOpts      ( SimplifierSwitch, SwitchResult )
17 import CoreSyn          ( GenCoreArg, GenCoreBinder, GenCoreBinding, GenCoreExpr,
18                           GenCoreCaseAlts, GenCoreCaseDefault, Coercion
19                         )
20 import CoreUnfold       ( Unfolding, UnfoldingGuidance )
21 import CostCentre       ( CostCentre )
22 import FieldLabel       ( FieldLabel )
23 import FiniteMap        ( FiniteMap )
24 import HeapOffs         ( HeapOffset )
25 import HsPat            ( OutPat )
26 import HsPragmas        ( ClassOpPragmas, ClassPragmas, DataPragmas, GenPragmas, InstancePragmas )
27 import Id               ( StrictnessMark, GenId, Id(..) )
28 import IdInfo           ( IdInfo, ArityInfo, DeforestInfo, StrictnessInfo, UpdateInfo )
29 import Demand           ( Demand )
30 import Kind             ( Kind )
31 import Literal          ( Literal )
32 import MachRegs         ( Reg )
33 import Maybes           ( MaybeErr )
34 import MatchEnv         ( MatchEnv )
35 import Name             ( Module(..), OccName, Name, ExportFlag, NamedThing(..) )
36 import Outputable       ( Outputable(..) )
37 import PprStyle         ( PprStyle )
38 import PragmaInfo       ( PragmaInfo )
39 import Pretty           ( PrettyRep )
40 import PrimOp           ( PrimOp )
41 import PrimRep          ( PrimRep )
42 import SMRep            ( SMRep )
43 import SrcLoc           ( SrcLoc )
44 import TcType           ( TcMaybe )
45 import TyCon            ( TyCon, Arity(..) )
46 import TyVar            ( GenTyVar, TyVar(..) )
47 import Type             ( GenType, Type(..) )
48 import UniqFM           ( UniqFM, Uniquable(..) )
49 import UniqSupply       ( UniqSupply )
50 import Unique           ( Unique )
51 import Usage            ( GenUsage, Usage(..) )
52 import Util             ( Ord3(..) )
53
54 -- All the classes in GHC go; life is just too short
55 -- to try to contain their visibility.
56
57 class NamedThing a where
58         getOccName :: a -> OccName
59         getName    :: a -> Name
60
61 class Ord3 a where
62         cmp :: a -> a -> Int#
63 class Outputable a where
64         ppr :: PprStyle -> a -> Int -> Bool -> PrettyRep
65 class Uniquable a where
66         uniqueOf :: a -> Unique
67
68 -- For datatypes, we ubiquitize those types that (a) are
69 -- used everywhere and (b) the compiler doesn't lose much
70 -- optimisation-wise by not seeing their pragma-gunk.
71
72 data ArityInfo
73 data Bag a
74 data BinderInfo
75 data CgIdInfo
76 data CLabel
77 data ClassOpPragmas a
78 data ClassPragmas a
79 data ClosureInfo
80 data Coercion
81 data CostCentre
82 data CSeq
83 data DataPragmas a
84 data DeforestInfo
85 data Demand
86 data ExportFlag
87 data FieldLabel
88 data FiniteMap a b
89 data GenClass a b
90 data GenClassOp a
91 data GenCoreArg a b c
92 data GenCoreBinder a b c
93 data GenCoreBinding a b c d
94 data GenCoreCaseAlts a b c d
95 data GenCoreCaseDefault a b c d
96 data GenCoreExpr a b c d
97 data GenId a    -- NB: fails the optimisation criterion
98 data GenPragmas a
99 data GenTyVar a -- NB: fails the optimisation criterion
100 data GenType  a b
101 data GenUsage a
102 data HeapOffset
103 data IdInfo
104 data InstancePragmas a
105 data Kind
106 data LambdaFormInfo
107 data Literal
108 data MaybeErr a b
109 data MatchEnv a b
110 data Name
111 data OccName
112 data Reg
113 data OutPat a b c
114 data PprStyle
115 data PragmaInfo
116 data PrettyRep
117 data PrimOp
118 data PrimRep    -- NB: an enumeration
119 data SimplifierSwitch
120 data SMRep
121 data SrcLoc
122 data StrictnessInfo bdee
123 data StrictnessMark
124 data SwitchResult
125 data TcMaybe s
126 data TyCon
127 data UniqFM a
128 data UpdateInfo
129 data UniqSupply
130 data Unfolding
131 data UnfoldingGuidance
132 data Unique     -- NB: fails the optimisation criterion
133
134 -- don't get clever and unexpand some of these synonyms
135 -- (GHC 0.26 will barf)
136 type Module = FastString
137 type Arity = Int
138 type Class = GenClass (GenTyVar (GenUsage Unique)) Unique
139 type ClassOp = GenClassOp (GenType (GenTyVar (GenUsage Unique)) Unique)
140 type Id    = GenId (GenType (GenTyVar (GenUsage Unique)) Unique)
141 type Type  = GenType (GenTyVar (GenUsage Unique)) Unique
142 type TyVar = GenTyVar (GenUsage Unique)
143 type Usage = GenUsage Unique
144
145 -- These are here only for SPECIALIZing in FiniteMap (ToDo:move?)
146 instance Ord Reg
147 instance Ord CLabel
148 instance Ord TyCon
149 instance Eq Reg
150 instance Eq CLabel
151 instance Eq TyCon
152 -- specializing in UniqFM, UniqSet
153 instance Uniquable Unique
154 instance Uniquable Name
155 -- specializing in Name
156 \end{code}