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