[project @ 1997-05-18 04:49:53 by sof]
[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 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           ( Doc )
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 -> Doc
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 DataPragmas a
82 data DeforestInfo
83 data Demand
84 data ExportFlag
85 data FieldLabel
86 data FiniteMap a b
87 data GenClass a b
88 data GenClassOp a
89 data GenCoreArg a b c
90 data GenCoreBinder a b c
91 data GenCoreBinding a b c d
92 data GenCoreCaseAlts a b c d
93 data GenCoreCaseDefault a b c d
94 data GenCoreExpr a b c d
95 data GenId a    -- NB: fails the optimisation criterion
96 data GenPragmas a
97 data GenTyVar a -- NB: fails the optimisation criterion
98 data GenType  a b
99 data GenUsage a
100 data HeapOffset
101 data IdInfo
102 data InstancePragmas a
103 data Kind
104 data LambdaFormInfo
105 data Literal
106 data MaybeErr a b
107 data MatchEnv a b
108 data Name
109 data OccName
110 data Reg
111 data OutPat a b c
112 data PprStyle
113 data PragmaInfo
114 data Doc
115 data PrimOp
116 data PrimRep    -- NB: an enumeration
117 data SimplifierSwitch
118 data SMRep
119 data SrcLoc
120 data StrictnessInfo bdee
121 data StrictnessMark
122 data SwitchResult
123 data TcMaybe s
124 data TyCon
125 data UniqFM a
126 data UpdateInfo
127 data UniqSupply
128 data Unfolding
129 data UnfoldingGuidance
130 data Unique     -- NB: fails the optimisation criterion
131
132 -- don't get clever and unexpand some of these synonyms
133 -- (GHC 0.26 will barf)
134 type Module = FastString
135 type Arity = Int
136 type Class = GenClass (GenTyVar (GenUsage Unique)) Unique
137 type ClassOp = GenClassOp (GenType (GenTyVar (GenUsage Unique)) Unique)
138 type Id    = GenId (GenType (GenTyVar (GenUsage Unique)) Unique)
139 type Type  = GenType (GenTyVar (GenUsage Unique)) Unique
140 type TyVar = GenTyVar (GenUsage Unique)
141 type Usage = GenUsage Unique
142
143 -- These are here only for SPECIALIZing in FiniteMap (ToDo:move?)
144 instance Ord Reg
145 instance Ord CLabel
146 instance Ord TyCon
147 instance Eq Reg
148 instance Eq CLabel
149 instance Eq TyCon
150 -- specializing in UniqFM, UniqSet
151 instance Uniquable Unique
152 instance Uniquable Name
153 -- specializing in Name
154 \end{code}