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