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