summaryrefslogtreecommitdiff
path: root/ghc/compiler/prelude/PrimRep.lhs
blob: 94ab0c50f2f731e60ad766d157317d288e980076 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
%
% (c) The GRASP Project, Glasgow University, 1992-1996
%
\section[PrimRep]{Primitive machine-level kinds of things.}

At various places in the back end, we want to be to tag things with a
``primitive kind''---i.e., the machine-manipulable implementation
types.

\begin{code}
#include "HsVersions.h"

module PrimRep (
	PrimRep(..),

	separateByPtrFollowness, isFollowableRep, isFloatingRep,
	getPrimRepSize, retPrimRepSize,
	showPrimRep,
	guessPrimRep
    ) where

IMP_Ubiq()

import Pretty		-- pretty-printing code
import Util

#include "../../includes/GhcConstants.h"
\end{code}

%************************************************************************
%*									*
\subsection[PrimRep-datatype]{The @PrimRep@ datatype}
%*									*
%************************************************************************

\begin{code}
data PrimRep
  = -- These pointer-kinds are all really the same, but we keep
    -- them separate for documentation purposes.
    PtrRep		-- Pointer to a closure; a ``word''.
  | CodePtrRep		-- Pointer to code
  | DataPtrRep		-- Pointer to data
  | RetRep 	    	-- Pointer to code or data (return vector or code pointer)
  | CostCentreRep	-- Pointer to a cost centre

  | CharRep		-- Machine characters
  | IntRep		--	   integers (at least 32 bits)
  | WordRep		--	   ditto (but *unsigned*)
  | AddrRep		--	   addresses ("C pointers")
  | FloatRep		--	   floats
  | DoubleRep		--	   doubles

  | ForeignObjRep	-- This has to be a special kind because ccall
			-- generates special code when passing/returning
			-- one of these. [ADR]

  | StablePtrRep	-- We could replace this with IntRep but maybe
			-- there's some documentation gain from having
			-- it special? [ADR]

  | ArrayRep		-- Primitive array of Haskell pointers
  | ByteArrayRep	-- Primitive array of bytes (no Haskell pointers)

  | VoidRep		-- Occupies no space at all!
			-- (Primitive states are mapped onto this)
  deriving (Eq, Ord)
	-- Kinds are used in PrimTyCons, which need both Eq and Ord
\end{code}

%************************************************************************
%*									*
\subsection[PrimRep-predicates]{Follow-ness, sizes, and such---on @PrimitiveKinds@}
%*									*
%************************************************************************

Whether or not the thing is a pointer that the garbage-collector
should follow.

Or, to put it another (less confusing) way, whether the object in
question is a heap object.

\begin{code}
isFollowableRep :: PrimRep -> Bool

isFollowableRep PtrRep        = True
isFollowableRep ArrayRep      = True
isFollowableRep ByteArrayRep  = True
-- why is a MallocPtr followable? 4/96 SOF
-- isFollowableRep ForeignObjRep  = True

isFollowableRep StablePtrRep  = False
-- StablePtrs aren't followable because they are just indices into a
-- table for which explicit allocation/ deallocation is required.

isFollowableRep other	    	= False

separateByPtrFollowness :: (a -> PrimRep) -> [a] -> ([a], [a])

separateByPtrFollowness kind_fun things
  = sep_things kind_fun things [] []
    -- accumulating params for follow-able and don't-follow things...
  where
    sep_things kfun []     bs us = (reverse bs, reverse us)
    sep_things kfun (t:ts) bs us
      = if (isFollowableRep . kfun) t then
	    sep_things kfun ts (t:bs) us
	else
	    sep_things kfun ts bs (t:us)
\end{code}

@isFloatingRep@ is used to distinguish @Double@ and @Float@ which
cause inadvertent numeric conversions if you aren't jolly careful.
See codeGen/CgCon:cgTopRhsCon.

\begin{code}
isFloatingRep :: PrimRep -> Bool

isFloatingRep DoubleRep = True
isFloatingRep FloatRep  = True
isFloatingRep other     = False
\end{code}

\begin{code}
getPrimRepSize :: PrimRep -> Int

getPrimRepSize DoubleRep  = DOUBLE_SIZE	-- "words", of course
--getPrimRepSize FloatRep = 1
--getPrimRepSize CharRep  = 1	-- ToDo: count in bytes?
--getPrimRepSize ArrayRep = 1	-- Listed specifically for *documentation*
--getPrimRepSize ByteArrayRep = 1
getPrimRepSize VoidRep	  = 0
getPrimRepSize other	  = 1

retPrimRepSize = getPrimRepSize RetRep
\end{code}

%************************************************************************
%*									*
\subsection[PrimRep-instances]{Boring instance decls for @PrimRep@}
%*									*
%************************************************************************

\begin{code}
instance Outputable PrimRep where
    ppr sty kind = ppStr (showPrimRep kind)

showPrimRep  :: PrimRep -> String
guessPrimRep :: String -> PrimRep	-- a horrible "inverse" function

showPrimRep PtrRep	    = "P_"	-- short for StgPtr

showPrimRep CodePtrRep    = "P_"	-- DEATH to StgFunPtr! (94/02/22 WDP)
    -- but aren't code pointers and function pointers different sizes
    -- on some machines (eg 80x86)? ADR
    -- Are you trying to ruin my life, or what? (WDP)

showPrimRep DataPtrRep    = "D_"
showPrimRep RetRep        = "StgRetAddr"
showPrimRep CostCentreRep = "CostCentre"
showPrimRep CharRep	  = "StgChar"
showPrimRep IntRep	  = "I_"	-- short for StgInt
showPrimRep WordRep	  = "W_"	-- short for StgWord
showPrimRep AddrRep	  = "StgAddr"
showPrimRep FloatRep	  = "StgFloat"
showPrimRep DoubleRep	  = "StgDouble"
showPrimRep ArrayRep	  = "StgArray" -- see comment below
showPrimRep ByteArrayRep  = "StgByteArray"
showPrimRep StablePtrRep  = "StgStablePtr"
showPrimRep ForeignObjRep  = "StgPtr" -- see comment below
showPrimRep VoidRep	  = "!!VOID_KIND!!"

guessPrimRep "D_"	     = DataPtrRep
guessPrimRep "StgRetAddr"   = RetRep
guessPrimRep "StgChar"	     = CharRep
guessPrimRep "I_"	     = IntRep
guessPrimRep "W_"	     = WordRep
guessPrimRep "StgAddr"	     = AddrRep
guessPrimRep "StgFloat"     = FloatRep
guessPrimRep "StgDouble"    = DoubleRep
guessPrimRep "StgArray"     = ArrayRep
guessPrimRep "StgByteArray" = ByteArrayRep
guessPrimRep "StgStablePtr" = StablePtrRep
\end{code}

All local C variables of @ArrayRep@ are declared in C as type
@StgArray@.  The coercion to a more precise C type is done just before
indexing (by the relevant C primitive-op macro).

Nota Bene. There are three types associated with @ForeignObj@ (MallocPtr++): 
\begin{itemize}
\item
@StgForeignObjClosure@ is the type of the thing the prim. op @mkForeignObj@ returns.
{- old comment for MallocPtr
(This typename is hardwired into @ppr_casm_results@ in
@PprAbsC.lhs@.)
-}

\item
@StgForeignObj@ is the type of the thing we give the C world.

\item
@StgPtr@ is the type of the (pointer to the) heap object which we
pass around inside the STG machine.
\end{itemize}

It is really easy to confuse the two.  (I'm not sure this choice of
type names helps.) [ADR]