97c7b3193fa02e4cd1087037e270d4e7a6423ed9
[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
8 import Bag              ( Bag )
9 import BinderInfo       ( BinderInfo )
10 import CgBindery        ( CgIdInfo )
11 import CharSeq          ( CSeq )
12 import CLabel           ( CLabel )
13 import Class            ( GenClass, GenClassOp, Class(..), ClassOp )
14 import ClosureInfo      ( ClosureInfo, LambdaFormInfo )
15 import CmdLineOpts      ( SimplifierSwitch, SwitchResult )
16 import CoreSyn          ( GenCoreArg, GenCoreBinder, GenCoreBinding, GenCoreExpr,
17                           GenCoreCaseAlts, GenCoreCaseDefault, Coercion
18                         )
19 import CoreUnfold       ( UnfoldingDetails, UnfoldingGuidance )
20 import CostCentre       ( CostCentre )
21 import FieldLabel       ( FieldLabel )
22 import FiniteMap        ( FiniteMap )
23 import HeapOffs         ( HeapOffset )
24 import HsCore           ( UnfoldingCoreExpr )
25 import HsPat            ( OutPat )
26 import HsPragmas        ( ClassOpPragmas, ClassPragmas, DataPragmas, GenPragmas, InstancePragmas )
27 import Id               ( StrictnessMark, GenId, Id(..) )
28 import IdInfo           ( IdInfo, OptIdInfo(..), ArityInfo, DeforestInfo, Demand, StrictnessInfo, UpdateInfo )
29 import Kind             ( Kind )
30 import Literal          ( Literal )
31 import MachRegs         ( Reg )
32 import Maybes           ( MaybeErr )
33 import MatchEnv         ( MatchEnv )
34 import Name             ( Module(..), OrigName, RdrName, Name, ExportFlag, NamedThing(..) )
35 import Outputable       ( Outputable(..) )
36 import PprStyle         ( PprStyle )
37 import PragmaInfo       ( PragmaInfo )
38 import Pretty           ( PrettyRep )
39 import PrimOp           ( PrimOp )
40 import PrimRep          ( PrimRep )
41 import RnHsSyn          ( RnName )
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         getName :: a -> Name
59 class OptIdInfo a where
60         noInfo  :: a
61         getInfo :: IdInfo -> a
62         addInfo :: IdInfo -> a -> IdInfo
63         ppInfo  :: PprStyle -> (Id -> Id) -> a -> Int -> Bool -> PrettyRep
64 class Ord3 a where
65         cmp :: a -> a -> Int#
66 class Outputable a where
67         ppr :: PprStyle -> a -> Int -> Bool -> PrettyRep
68 class Uniquable a where
69         uniqueOf :: a -> Unique
70
71 -- For datatypes, we ubiquitize those types that (a) are
72 -- used everywhere and (b) the compiler doesn't lose much
73 -- optimisation-wise by not seeing their pragma-gunk.
74
75 data ArityInfo
76 data Bag a
77 data BinderInfo
78 data CgIdInfo
79 data CLabel
80 data ClassOpPragmas a
81 data ClassPragmas a
82 data ClosureInfo
83 data Coercion
84 data CostCentre
85 data CSeq
86 data DataPragmas a
87 data DeforestInfo
88 data Demand
89 data ExportFlag
90 data FieldLabel
91 data FiniteMap a b
92 data GenClass a b
93 data GenClassOp a
94 data GenCoreArg a b c
95 data GenCoreBinder a b c
96 data GenCoreBinding a b c d
97 data GenCoreCaseAlts a b c d
98 data GenCoreCaseDefault a b c d
99 data GenCoreExpr a b c d
100 data GenId a    -- NB: fails the optimisation criterion
101 data GenPragmas a
102 data GenTyVar a -- NB: fails the optimisation criterion
103 data GenType  a b
104 data GenUsage a
105 data HeapOffset
106 data IdInfo
107 data InstancePragmas a
108 data Kind
109 data LambdaFormInfo
110 data Literal
111 data MaybeErr a b
112 data MatchEnv a b
113 data Name
114 data OrigName = OrigName _PackedString _PackedString
115 data RdrName = Unqual _PackedString | Qual _PackedString _PackedString
116 data Reg
117 data OutPat a b c
118 data PprStyle
119 data PragmaInfo
120 data PrettyRep
121 data PrimOp
122 data PrimRep    -- NB: an enumeration
123 data RnName
124 data SimplifierSwitch
125 data SMRep
126 data SrcLoc
127 data StrictnessInfo
128 data StrictnessMark
129 data SwitchResult
130 data TcMaybe s
131 data TyCon
132 data UnfoldingCoreExpr a
133 data UniqFM a
134 data UpdateInfo
135 data UniqSupply
136 data UnfoldingDetails
137 data UnfoldingGuidance
138 data Unique     -- NB: fails the optimisation criterion
139
140 -- don't get clever and unexpand some of these synonyms
141 -- (GHC 0.26 will barf)
142 type Module = _PackedString
143 type Arity = Int
144 type Class = GenClass (GenTyVar (GenUsage Unique)) Unique
145 type ClassOp = GenClassOp (GenType (GenTyVar (GenUsage Unique)) Unique)
146 type Id    = GenId (GenType (GenTyVar (GenUsage Unique)) Unique)
147 type Type  = GenType (GenTyVar (GenUsage Unique)) Unique
148 type TyVar = GenTyVar (GenUsage Unique)
149 type Usage = GenUsage Unique
150
151 -- These are here only for SPECIALIZing in FiniteMap (ToDo:move?)
152 instance Ord Reg
153 instance Ord OrigName
154 instance Ord RdrName
155 instance Ord CLabel
156 instance Ord TyCon
157 instance Eq Reg
158 instance Eq OrigName
159 instance Eq RdrName
160 instance Eq CLabel
161 instance Eq TyCon
162 -- specializing in UniqFM, UniqSet
163 instance Uniquable Unique
164 instance Uniquable RnName
165 instance Uniquable Name
166 -- specializing in Name
167 instance NamedThing RnName
168 \end{code}