[project @ 1998-12-18 17:40:31 by simonpj]
[ghc-hetmet.git] / ghc / compiler / basicTypes / DataCon.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1998
3 %
4 \section[Literal]{@Literal@: Machine literals (unboxed, of course)}
5
6 \begin{code}
7 module DataCon (
8         DataCon,
9         ConTag, fIRST_TAG,
10         mkDataCon,
11         dataConType, dataConSig, dataConName, dataConTag,
12         dataConArgTys, dataConRawArgTys, dataConTyCon,
13         dataConFieldLabels, dataConStrictMarks, dataConSourceArity,
14         dataConNumFields, dataConNumInstArgs, dataConId,
15         isNullaryDataCon, isTupleCon, isUnboxedTupleCon,
16         isExistentialDataCon
17     ) where
18
19 #include "HsVersions.h"
20
21 import CmdLineOpts      ( opt_DictsStrict )
22 import TysPrim
23 import Type             ( Type, ThetaType, TauType,
24                           mkSigmaTy, mkFunTys, mkTyConApp, 
25                           mkTyVarTys, mkDictTy, substTy
26                         )
27 import TyCon            ( TyCon, tyConDataCons, isDataTyCon,
28                           isTupleTyCon, isUnboxedTupleTyCon )
29 import Class            ( classTyCon )
30 import Name             ( Name, NamedThing(..), nameUnique )
31 import Var              ( TyVar, Id )
32 import VarEnv
33 import FieldLabel       ( FieldLabel )
34 import BasicTypes       ( StrictnessMark(..), Arity )
35 import Outputable
36 import Unique           ( Unique, Uniquable(..) )
37 import Util             ( assoc )
38 \end{code}
39
40
41 %************************************************************************
42 %*                                                                      *
43 \subsection{Data constructors}
44 %*                                                                      *
45 %************************************************************************
46
47 \begin{code}
48 data DataCon
49   = MkData {                    -- Used for data constructors only;
50                                 -- there *is* no constructor for a newtype
51         dcName   :: Name,
52         dcUnique :: Unique,             -- Cached from Name
53         dcTag    :: ConTag,
54
55         -- Running example:
56         --
57         --      data Eq a => T a = forall b. Ord b => MkT a [b]
58
59         dcType   :: Type,       -- Type of the constructor 
60                                 --      forall ab . Ord b => a -> [b] -> MkT a
61                                 -- (this is *not* of the constructor Id: 
62                                 --  see notes after this data type declaration)
63
64         -- The next six fields express the type of the constructor, in pieces
65         -- e.g.
66         --
67         --      dcTyVars   = [a]
68         --      dcTheta    = [Eq a]
69         --      dcExTyVars = [b]
70         --      dcExTheta  = [Ord b]
71         --      dcArgTys   = [a,List b]
72         --      dcTyCon    = T
73
74         dcTyVars :: [TyVar],            -- Type vars and context for the data type decl
75         dcTheta  ::  ThetaType,
76
77         dcExTyVars :: [TyVar],          -- Ditto for the context of the constructor, 
78         dcExTheta  :: ThetaType,        -- the existentially quantified stuff
79                                         
80         dcArgTys :: [Type],             -- Argument types
81         dcTyCon  :: TyCon,              -- Result tycon 
82
83         -- Now the strictness annotations and field labels of the constructor
84         dcStricts :: [StrictnessMark],  -- Strict args, in the same order as the argument types;
85                                         -- length = dataConNumFields dataCon
86
87         dcFields  :: [FieldLabel],      -- Field labels for this constructor, in the
88                                         -- same order as the argument types; 
89                                         -- length = 0 (if not a record) or dataConSourceArity.
90
91         -- Finally, the curried function that corresponds to the constructor
92         --      mkT :: forall a b. (Eq a, Ord b) => a -> [b] -> T a
93         --      mkT = /\ab. \deq dord p qs. Con MkT [a, b, dord, p, qs]
94         -- This unfolding is built in MkId.mkDataConId
95
96         dcId :: Id                      -- The corresponding Id
97   }
98
99 type ConTag = Int
100
101 fIRST_TAG :: ConTag
102 fIRST_TAG =  1  -- Tags allocated from here for real constructors
103 \end{code}
104
105 The dcType field contains the type of the representation of a contructor
106 This may differ from the type of the contructor *Id* (built
107 by MkId.mkDataConId) for two reasons:
108         a) the constructor Id may be overloaded, but the dictionary isn't stored
109            e.g.    data Eq a => T a = MkT a a
110
111         b) the constructor may store an unboxed version of a strict field.
112
113 Here's an example illustrating both:
114         data Ord a => T a = MkT Int! a
115 Here
116         T :: Ord a => Int -> a -> T a
117 but the rep type is
118         Trep :: Int# -> a -> T a
119 Actually, the unboxed part isn't implemented yet!
120
121
122 \begin{code}
123 instance Eq DataCon where
124     a == b = getUnique a == getUnique b
125     a /= b = getUnique a /= getUnique b
126
127 instance Ord DataCon where
128     a <= b = getUnique a <= getUnique b
129     a <  b = getUnique a <  getUnique b
130     a >= b = getUnique a >= getUnique b
131     a >  b = getUnique a > getUnique b
132     compare a b = getUnique a `compare` getUnique b
133
134 instance Uniquable DataCon where
135     getUnique = dcUnique
136
137 instance NamedThing DataCon where
138     getName = dcName
139
140 instance Outputable DataCon where
141     ppr con = ppr (dataConName con)
142
143 instance Show DataCon where
144     showsPrec p con = showsPrecSDoc p (ppr con)
145 \end{code}
146
147 \begin{code}
148 mkDataCon :: Name
149           -> [StrictnessMark] -> [FieldLabel]
150           -> [TyVar] -> ThetaType
151           -> [TyVar] -> ThetaType
152           -> [TauType] -> TyCon
153           -> Id
154           -> DataCon
155   -- Can get the tag from the TyCon
156
157 mkDataCon name arg_stricts fields tyvars theta ex_tyvars ex_theta arg_tys tycon id
158   = ASSERT(length arg_stricts == length arg_tys)
159         -- The 'stricts' passed to mkDataCon are simply those for the
160         -- source-language arguments.  We add extra ones for the
161         -- dictionary arguments right here.
162     con
163   where
164     con = MkData {dcName = name, dcUnique = nameUnique name,
165                   dcTyVars = tyvars, dcTheta = theta, dcArgTys = arg_tys,
166                   dcExTyVars = ex_tyvars, dcExTheta = ex_theta,
167                   dcStricts = all_stricts, dcFields = fields,
168                   dcTag = tag, dcTyCon = tycon, dcType = ty,
169                   dcId = id}
170
171     all_stricts = (map mk_dict_strict_mark ex_theta) ++ arg_stricts
172         -- Add a strictness flag for the existential dictionary arguments
173
174     tag = assoc "mkDataCon" (tyConDataCons tycon `zip` [fIRST_TAG..]) con
175     ty  = mkSigmaTy (tyvars ++ ex_tyvars) 
176                     ex_theta
177                     (mkFunTys arg_tys (mkTyConApp tycon (mkTyVarTys tyvars)))
178
179 mk_dict_strict_mark (clas,tys)
180   | opt_DictsStrict &&
181     isDataTyCon (classTyCon clas) = MarkedStrict        -- Don't mark newtype things as strict!
182   | otherwise                     = NotMarkedStrict
183 \end{code}
184
185
186 \begin{code}
187 dataConName :: DataCon -> Name
188 dataConName = dcName
189
190 dataConTag :: DataCon -> ConTag
191 dataConTag  = dcTag
192
193 dataConTyCon :: DataCon -> TyCon
194 dataConTyCon = dcTyCon
195
196 dataConType :: DataCon -> Type
197 dataConType = dcType
198
199 dataConId :: DataCon -> Id
200 dataConId = dcId
201
202
203 dataConFieldLabels :: DataCon -> [FieldLabel]
204 dataConFieldLabels = dcFields
205
206 dataConStrictMarks :: DataCon -> [StrictnessMark]
207 dataConStrictMarks = dcStricts
208
209 dataConRawArgTys :: DataCon -> [TauType] -- a function of convenience
210 dataConRawArgTys = dcArgTys
211
212 dataConSourceArity :: DataCon -> Arity
213         -- Source-level arity of the data constructor
214 dataConSourceArity dc = length (dcArgTys dc)
215
216 dataConSig :: DataCon -> ([TyVar], ThetaType, 
217                           [TyVar], ThetaType, 
218                           [TauType], TyCon)
219
220 dataConSig (MkData {dcTyVars = tyvars, dcTheta = theta,
221                      dcExTyVars = ex_tyvars, dcExTheta = ex_theta,
222                      dcArgTys = arg_tys, dcTyCon = tycon})
223   = (tyvars, theta, ex_tyvars, ex_theta, arg_tys, tycon)
224
225 dataConArgTys :: DataCon 
226               -> [Type]         -- Instantiated at these types
227                                 -- NB: these INCLUDE the existentially quantified arg types
228               -> [Type]         -- Needs arguments of these types
229                                 -- NB: these INCLUDE the existentially quantified dict args
230                                 --     but EXCLUDE the data-decl context which is discarded
231
232 dataConArgTys (MkData {dcArgTys = arg_tys, dcTyVars = tyvars, 
233                        dcExTyVars = ex_tyvars, dcExTheta = ex_theta}) inst_tys
234  = map (substTy (zipVarEnv (tyvars ++ ex_tyvars) inst_tys)) 
235        ([mkDictTy cls tys | (cls,tys) <- ex_theta] ++ arg_tys)
236 \end{code}
237
238 dataConNumFields gives the number of actual fields in the
239 {\em representation} of the data constructor.  This may be more than appear
240 in the source code; the extra ones are the existentially quantified
241 dictionaries
242
243 \begin{code}
244 -- Number of type-instantiation arguments
245 -- All the remaining arguments of the DataCon are (notionally)
246 -- stored in the DataCon, and are matched in a case expression
247 dataConNumInstArgs (MkData {dcTyVars = tyvars}) = length tyvars
248
249 dataConNumFields (MkData {dcExTheta = theta, dcArgTys = arg_tys})
250   = length theta + length arg_tys
251
252 isNullaryDataCon con
253   = dataConNumFields con == 0 -- function of convenience
254
255 isTupleCon :: DataCon -> Bool
256 isTupleCon (MkData {dcTyCon = tc}) = isTupleTyCon tc
257         
258 isUnboxedTupleCon :: DataCon -> Bool
259 isUnboxedTupleCon (MkData {dcTyCon = tc}) = isUnboxedTupleTyCon tc
260
261 isExistentialDataCon :: DataCon -> Bool
262 isExistentialDataCon (MkData {dcExTyVars = tvs}) = not (null tvs)
263 \end{code}