[project @ 1999-05-11 16:37:29 by keithw]
[ghc-hetmet.git] / ghc / compiler / prelude / PrelVals.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
3 %
4 \section[PrelVals]{Prelude values the compiler ``knows about''}
5
6 \begin{code}
7 module PrelVals where
8
9 #include "HsVersions.h"
10
11 import {-# SOURCE #-} CoreUnfold ( mkUnfolding )
12
13 import Id               ( Id, mkVanillaId, setIdInfo, mkTemplateLocals  )
14
15 -- friends:
16 import PrelMods
17 import TysPrim
18 import TysWiredIn
19
20 -- others:
21 import CoreSyn          -- quite a bit
22 import IdInfo           -- quite a bit
23 import PrimOp           ( PrimOp(..) )
24 import Const            ( Con(..) )
25 import Module           ( Module )
26 import Name             ( mkWiredInIdName, mkSrcVarOcc )
27 import Type             
28 import Var              ( TyVar )
29 import Demand           ( wwStrict )
30 import Unique           -- lots of *Keys
31
32 import IOExts
33 \end{code}
34
35 %************************************************************************
36 %*                                                                      *
37 \subsection{Un-definable}
38 %*                                                                      *
39 %************************************************************************
40
41 These two can't be defined in Haskell.
42
43
44 unsafeCoerce# isn't so much a PrimOp as a phantom identifier, that
45 just gets expanded into a type coercion wherever it occurs.  Hence we
46 add it as a built-in Id with an unfolding here.
47
48 The type variables we use here are "open" type variables: this means
49 they can unify with both unlifted and lifted types.  Hence we provide
50 another gun with which to shoot yourself in the foot.
51
52 \begin{code}
53 unsafeCoerceId
54   = pcMiscPrelId unsafeCoerceIdKey pREL_GHC SLIT("unsafeCoerce#") ty
55         (mk_inline_unfolding template)
56   where
57     (alphaTyVar:betaTyVar:_) = openAlphaTyVars
58     alphaTy  = mkTyVarTy alphaTyVar
59     betaTy   = mkTyVarTy betaTyVar
60     ty = mkForAllTys [alphaTyVar,betaTyVar] (mkFunTy alphaTy betaTy)
61     [x] = mkTemplateLocals [alphaTy]
62     template = mkLams [alphaTyVar,betaTyVar,x] $
63                Note (Coerce betaTy alphaTy) (Var x)
64 \end{code}
65
66 @getTag#@ is another function which can't be defined in Haskell.  It needs to
67 evaluate its argument and call the dataToTag# primitive.
68
69 \begin{code}
70 getTagId
71   = pcMiscPrelId getTagIdKey pREL_GHC SLIT("getTag#") ty 
72         (mk_inline_unfolding template)
73   where
74     ty = mkForAllTys [alphaTyVar] (mkFunTy alphaTy intPrimTy)
75     [x,y] = mkTemplateLocals [alphaTy,alphaTy]
76     template = mkLams [alphaTyVar,x] $
77                Case (Var x) y [ (DEFAULT, [], 
78                    Con (PrimOp DataToTagOp) [Type alphaTy, Var y]) ]
79 \end{code}
80
81
82 @realWorld#@ used to be a magic literal, \tr{void#}.  If things get
83 nasty as-is, change it back to a literal (@Literal@).
84
85 \begin{code}
86 realWorldPrimId
87   = pcMiscPrelId realWorldPrimIdKey pREL_GHC SLIT("realWorld#")
88         realWorldStatePrimTy
89         noCafIdInfo
90 \end{code}
91
92
93 %************************************************************************
94 %*                                                                      *
95 \subsection[PrelVals-error-related]{@error@ and friends; @trace@}
96 %*                                                                      *
97 %************************************************************************
98
99 GHC randomly injects these into the code.
100
101 @patError@ is just a version of @error@ for pattern-matching
102 failures.  It knows various ``codes'' which expand to longer
103 strings---this saves space!
104
105 @absentErr@ is a thing we put in for ``absent'' arguments.  They jolly
106 well shouldn't be yanked on, but if one is, then you will get a
107 friendly message from @absentErr@ (rather than a totally random
108 crash).
109
110 @parError@ is a special version of @error@ which the compiler does
111 not know to be a bottoming Id.  It is used in the @_par_@ and @_seq_@
112 templates, but we don't ever expect to generate code for it.
113
114 \begin{code}
115 pc_bottoming_Id key mod name ty
116  = pcMiscPrelId key mod name ty bottoming_info
117  where
118     bottoming_info = mkStrictnessInfo ([wwStrict], True) `setStrictnessInfo` noCafIdInfo
119         -- these "bottom" out, no matter what their arguments
120
121 eRROR_ID
122   = pc_bottoming_Id errorIdKey pREL_ERR SLIT("error") errorTy
123
124 generic_ERROR_ID u n
125   = pc_bottoming_Id u pREL_ERR n errorTy
126
127 rEC_SEL_ERROR_ID
128   = generic_ERROR_ID recSelErrIdKey SLIT("patError")
129 pAT_ERROR_ID
130   = generic_ERROR_ID patErrorIdKey SLIT("patError")
131 rEC_CON_ERROR_ID
132   = generic_ERROR_ID recConErrorIdKey SLIT("recConError")
133 rEC_UPD_ERROR_ID
134   = generic_ERROR_ID recUpdErrorIdKey SLIT("recUpdError")
135 iRREFUT_PAT_ERROR_ID
136   = generic_ERROR_ID irrefutPatErrorIdKey SLIT("irrefutPatError")
137 nON_EXHAUSTIVE_GUARDS_ERROR_ID
138   = generic_ERROR_ID nonExhaustiveGuardsErrorIdKey SLIT("nonExhaustiveGuardsError")
139 nO_METHOD_BINDING_ERROR_ID
140   = generic_ERROR_ID noMethodBindingErrorIdKey SLIT("noMethodBindingError")
141
142 aBSENT_ERROR_ID
143   = pc_bottoming_Id absentErrorIdKey pREL_ERR SLIT("absentErr")
144         (mkSigmaTy [openAlphaTyVar] [] openAlphaTy)
145
146 pAR_ERROR_ID
147   = pcMiscPrelId parErrorIdKey pREL_ERR SLIT("parError")
148     (mkSigmaTy [openAlphaTyVar] [] openAlphaTy) noCafIdInfo
149
150 openAlphaTy = mkTyVarTy openAlphaTyVar
151
152 errorTy  :: Type
153 errorTy  = mkUsgTy UsMany $
154            mkSigmaTy [openAlphaTyVar] [] (mkFunTys [mkUsgTy UsOnce (mkListTy charTy)] 
155                                                    (mkUsgTy UsMany openAlphaTy))
156     -- Notice the openAlphaTyVar.  It says that "error" can be applied
157     -- to unboxed as well as boxed types.  This is OK because it never
158     -- returns, so the return type is irrelevant.
159 \end{code}
160
161
162 %************************************************************************
163 %*                                                                      *
164 \subsection{Utilities}
165 %*                                                                      *
166 %************************************************************************
167
168 Note IMustBeINLINEd below.  These things have the same status as
169 constructor functions, i.e. they will *always* be inlined, wherever
170 they occur.
171
172 \begin{code}
173 mk_inline_unfolding expr = setUnfoldingInfo (mkUnfolding expr)  $
174                            setInlinePragInfo IMustBeINLINEd  noIdInfo
175
176 exactArityInfo n = exactArity n `setArityInfo` noIdInfo
177
178 pcMiscPrelId :: Unique{-IdKey-} -> Module -> FAST_STRING -> Type -> IdInfo -> Id
179
180 pcMiscPrelId key mod str ty info
181   = let
182         name = mkWiredInIdName key mod (mkSrcVarOcc str) imp
183         imp  = mkVanillaId name ty `setIdInfo` info -- the usual case...
184     in
185     imp
186     -- We lie and say the thing is imported; otherwise, we get into
187     -- a mess with dependency analysis; e.g., core2stg may heave in
188     -- random calls to GHCbase.unpackPS__.  If GHCbase is the module
189     -- being compiled, then it's just a matter of luck if the definition
190     -- will be in "the right place" to be in scope.
191
192 -- very useful...
193 noCafIdInfo = NoCafRefs `setCafInfo` noIdInfo
194 \end{code}
195