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