summaryrefslogtreecommitdiff
path: root/ghc/docs/state_interface/state-interface.verb
diff options
context:
space:
mode:
Diffstat (limited to 'ghc/docs/state_interface/state-interface.verb')
-rw-r--r--ghc/docs/state_interface/state-interface.verb313
1 files changed, 148 insertions, 165 deletions
diff --git a/ghc/docs/state_interface/state-interface.verb b/ghc/docs/state_interface/state-interface.verb
index c51193aa97..291d5f0109 100644
--- a/ghc/docs/state_interface/state-interface.verb
+++ b/ghc/docs/state_interface/state-interface.verb
@@ -4,7 +4,7 @@
\renewcommand{\dblfloatpagefraction}{0.9}
\sloppy
-
+\renewcommand{\today}{July 1996}
\begin{document}
@@ -15,7 +15,7 @@
\tableofcontents
This ``state interface document'' corresponds to Glasgow Haskell
-version~0.23.
+version~2.01.
\section{Really primitive stuff}
@@ -81,45 +81,45 @@ negateInt# :: Int# -> Int#
@
NB: No error/overflow checking!
-\subsubsection{Unboxed-@Float@ and @Double@ operations}
-@
-{plus,minus,times,divide}Float# :: Float# -> Float# -> Float#
-negateFloat# :: Float# -> Float#
-
-float2Int# :: Float# -> Int# -- just a cast, no checking!
-int2Float# :: Int# -> Float#
-
-expFloat# :: Float# -> Float#
-logFloat# :: Float# -> Float#
-sqrtFloat# :: Float# -> Float#
-sinFloat# :: Float# -> Float#
-cosFloat# :: Float# -> Float#
-tanFloat# :: Float# -> Float#
-asinFloat# :: Float# -> Float#
-acosFloat# :: Float# -> Float#
-atanFloat# :: Float# -> Float#
-sinhFloat# :: Float# -> Float#
-coshFloat# :: Float# -> Float#
-tanhFloat# :: Float# -> Float#
-powerFloat# :: Float# -> Float# -> Float#
-@
-There's an exactly-matching set of unboxed-@Double@ ops; replace
-@Float#@ with @Double#@ in the list above. There are two
+\subsubsection{Unboxed-@Double@ and @Float@ operations}
+@
+{plus,minus,times,divide}Double# :: Double# -> Double# -> Double#
+negateDouble# :: Double# -> Double#
+
+float2Int# :: Double# -> Int# -- just a cast, no checking!
+int2Double# :: Int# -> Double#
+
+expDouble# :: Double# -> Double#
+logDouble# :: Double# -> Double#
+sqrtDouble# :: Double# -> Double#
+sinDouble# :: Double# -> Double#
+cosDouble# :: Double# -> Double#
+tanDouble# :: Double# -> Double#
+asinDouble# :: Double# -> Double#
+acosDouble# :: Double# -> Double#
+atanDouble# :: Double# -> Double#
+sinhDouble# :: Double# -> Double#
+coshDouble# :: Double# -> Double#
+tanhDouble# :: Double# -> Double#
+powerDouble# :: Double# -> Double# -> Double#
+@
+There's an exactly-matching set of unboxed-@Float@ ops; replace
+@Double#@ with @Float#@ in the list above. There are two
coercion functions for @Float#@/@Double#@:
@
float2Double# :: Float# -> Double#
double2Float# :: Double# -> Float#
@
-The primitive versions of @encodeFloat@/@decodeFloat@:
+The primitive versions of @encodeDouble@/@decodeDouble@:
@
-encodeFloat# :: Int# -> Int# -> ByteArray# -- Integer mantissa
+encodeDouble# :: Int# -> Int# -> ByteArray# -- Integer mantissa
-> Int# -- Int exponent
- -> Float#
+ -> Double#
-decodeFloat# :: Float#
- -> _ReturnIntAndGMP
+decodeDouble# :: Double#
+ -> GHCbase.ReturnIntAndGMP
@
-(And the same for @Double#@s.)
+(And the same for @Float#@s.)
\subsection{Operations on/for @Integers@ (interface to GMP)}
\label{sect:horrid-Integer-pairing-types}
@@ -127,6 +127,8 @@ decodeFloat# :: Float#
We implement @Integers@ (arbitrary-precision integers) using the GNU
multiple-precision (GMP) package.
+NB: some of this might change if we upgrade to using GMP~2.x.
+
The data type for @Integer@ must mirror that for @MP_INT@ in @gmp.h@
(see @gmp.info@). It comes out as:
@
@@ -138,11 +140,8 @@ collection of primitive types.
The operations in the GMP return other combinations of
GMP-plus-something, so we need ``pairing'' types for those, too:
@
-type _ReturnGMP = Integer -- synonym
-data _Return2GMPs = _Return2GMPs Int# Int# ByteArray#
- Int# Int# ByteArray#
-data _ReturnIntAndGMP = _ReturnIntAndGMP Int#
- Int# Int# ByteArray#
+data Return2GMPs = Return2GMPs Int# Int# ByteArray# Int# Int# ByteArray#
+data ReturnIntAndGMP = ReturnIntAndGMP Int# Int# Int# ByteArray#
-- ????? something to return a string of bytes (in the heap?)
@
@@ -162,7 +161,7 @@ cmpInteger# :: Int# -> Int# -> ByteArray#
divModInteger#, quotRemInteger#
:: Int# -> Int# -> ByteArray#
-> Int# -> Int# -> ByteArray#
- -> _Return2GMPs
+ -> GHCbase.Return2GMPs
integer2Int# :: Int# -> Int# -> ByteArray#
-> Int#
@@ -298,7 +297,7 @@ object! This is a pain: primitive ops aren't supposed to do
complicated things like enter objects. The current solution is to
return a lifted value, but I don't like it!
@
-indexArray# :: Array# elt -> Int# -> _Lift elt -- Yuk!
+indexArray# :: Array# elt -> Int# -> GHCbase.Lift elt -- Yuk!
@
\subsubsection{The state type}
@@ -314,20 +313,20 @@ code, and allocate no registers etc, for primitive states.
type State# s
@
-The type @_RealWorld@ is truly opaque: there are no values defined
+The type @GHCbuiltins.RealWorld@ is truly opaque: there are no values defined
of this type, and no operations over it. It is ``primitive'' in that
sense---but it is {\em not unboxed!} Its only role in life is to be the type
which distinguishes the @PrimIO@ state transformer (see
Section~\ref{sect:io-spec}).
@
-data _RealWorld
+data RealWorld
@
\subsubsection{States}
-A single, primitive, value of type @State# _RealWorld@ is provided.
+A single, primitive, value of type @State# RealWorld@ is provided.
@
-realWorld# :: State# _RealWorld
+realWorld# :: State# GHCbuiltins.RealWorld
@
(Note: in the compiler, not a @PrimOp@; just a mucho magic @Id@.)
@@ -455,9 +454,9 @@ The @makeStablePointer@ function converts a value into a stable pointer.
It is part of the @PrimIO@ monad, because we want to be sure we don't
allocate one twice by accident, and then only free one of the copies.
@
-makeStablePointer# :: a -> State# _RealWorld -> StateAndStablePtr# _RealWorld a
-freeStablePointer# :: StablePtr# a -> State# _RealWorld -> State# _RealWorld
-deRefStablePointer# :: StablePtr# a -> State# _RealWorld -> StateAndPtr _RealWorld a
+makeStablePointer# :: a -> State# RealWorld -> StateAndStablePtr# RealWorld a
+freeStablePointer# :: StablePtr# a -> State# RealWorld -> State# RealWorld
+deRefStablePointer# :: StablePtr# a -> State# RealWorld -> StateAndPtr RealWorld a
@
There is also a C procedure @FreeStablePtr@ which frees a stable pointer.
@@ -466,20 +465,20 @@ There is also a C procedure @FreeStablePtr@ which frees a stable pointer.
%
\subsubsection{Foreign objects}
-A \tr{ForeignObj} is a reference to an object outside the Haskell
+A @ForeignObj@ is a reference to an object outside the Haskell
world (i.e., from the C world, or a reference to an object on another
machine completely.), where the Haskell world has been told ``Let me
know when you're finished with this ...''.
-The \tr{ForeignObj} type is just a special @Addr#@ ({\em not} parameterised).
+The @ForeignObj@ type is just a special @Addr#@ ({\em not} parameterised).
@
type ForeignObj#
@
-A typical use of \tr{ForeignObj} is in constructing Haskell bindings
+A typical use of @ForeignObj@ is in constructing Haskell bindings
to external libraries. A good example is that of writing a binding to
an image-processing library (which was actually the main motivation
-for implementing \tr{ForeignObj}'s precursor, \tr{MallocPtr}). The
+for implementing @ForeignObj@'s precursor, @MallocPtr@). The
images manipulated are not stored in the Haskell heap, either because
the library insist on allocating them internally or we (sensibly)
decide to spare the GC from having to heave heavy images around.
@@ -487,12 +486,12 @@ decide to spare the GC from having to heave heavy images around.
@
data Image = Image ForeignObj#
-instance _CCallable Image
+instance CCallable Image
@
-The \tr{ForeignObj#} type is then used to refer to the externally
+The @ForeignObj#@ type is then used to refer to the externally
allocated image, and to acheive some type safety, the Haskell binding
-defines the @Image@ data type. So, a value of type \tr{ForeignObj#} is
+defines the @Image@ data type. So, a value of type @ForeignObj#@ is
used to ``box'' up an external reference into a Haskell heap object
that we can then indirectly reference:
@@ -500,23 +499,23 @@ that we can then indirectly reference:
createImage :: (Int,Int) -> PrimIO Image
@
-So far, this looks just like an @Addr#@ type, but \tr{ForeignObj#}
+So far, this looks just like an @Addr#@ type, but @ForeignObj#@
offers a bit more, namely that we can specify a {\em finalisation
-routine} to invoke when the \tr{ForeignObj#} is discarded by the
+routine} to invoke when the @ForeignObj#@ is discarded by the
GC. The garbage collector invokes the finalisation routine associated
-with the \tr{ForeignObj#}, saying `` Thanks, I'm through with this
+with the @ForeignObj#@, saying `` Thanks, I'm through with this
now..'' For the image-processing library, the finalisation routine could for
the images free up memory allocated for them. The finalisation routine has
currently to be written in C (the finalisation routine can in turn call on
@FreeStablePtr@ to deallocate a stable pointer.).
Associating a finalisation routine with an external object is done by
-\tr{makeForeignObj#}:
+@makeForeignObj#@:
@
makeForeignObj# :: Addr# -- foreign reference
-> Addr# -- pointer to finalisation routine
- -> StateAndForeignObj# _RealWorld ForeignObj#
+ -> StateAndForeignObj# RealWorld ForeignObj#
@
(Implementation: a linked list of all @ForeignObj#@s is maintained to allow the
@@ -568,11 +567,11 @@ of space recovered.
\subsection{The @errorIO#@ primitive operation}
-The @errorIO#@ primitive takes an argument of type @PrimIO@. It aborts execution of
-the current program, and continues instead by performing the given @PrimIO@ value
+The @errorIO#@ primitive takes an argument much like @PrimIO@. It aborts execution of
+the current program, and continues instead by performing the given @PrimIO@-like value
on the current state of the world.
@
-errorIO# :: PrimIO () -> a
+errorIO# :: (State RealWorld -> ((), State RealWorld)) -> a
@
\subsection{C Calls}
@@ -583,7 +582,7 @@ argument not last argument.
The @ccall#@ primitive can't be given an ordinary type, because it has
a variable number of arguments. The nearest we can get is:
@
-ccall# :: CRoutine -> a1# -> ... -> an# -> State# _RealWorld -> StateAndR# _RealWorld
+ccall# :: CRoutine -> a1# -> ... -> an# -> State# RealWorld -> StateAndR# RealWorld
@
where the type variables @a1#@\ldots@an#@ and @r#@ can be instantiated by any
primitive type, and @StateAndR#@ is the appropriate pairing type from
@@ -601,7 +600,7 @@ identifier. The only way it is possible to generate a @ccall#@ is via the
All this applies equally to @casm#@:
@
-casm# :: CAsmString -> a1# -> ... -> an# -> State# _RealWorld -> StateAndR# _RealWorld
+casm# :: CAsmString -> a1# -> ... -> an# -> State# RealWorld -> StateAndR# RealWorld
@
%------------------------------------------------------------
@@ -614,50 +613,50 @@ casm# :: CAsmString -> a1# -> ... -> an# -> State# _RealWorld -> StateAndR# _Re
A state transformer is a function from a state to a pair of a result and a new
state.
@
-type _ST s a = _State s -> (a, _State s)
+newtype ST s a = ST (State s -> (a, State s))
@
-The @_ST@ type is {\em abstract}, so that the programmer cannot see its
+The @ST@ type is {\em abstract}, so that the programmer cannot see its
representation. If he could, he could write bad things like:
@
-bad :: _ST s a
-bad = \s -> ...(f s)...(g s)...
+bad :: ST s a
+bad = ST $ \ s -> ...(f s)...(g s)...
@
Here, @s@ is duplicated, which would be bad news.
A state is represented by a primitive state value, of type @State# s@,
-wrapped up in a @_State@ constructor. The reason for boxing it in this
+wrapped up in a @State@ constructor. The reason for boxing it in this
way is so that we can be strict or lazy in the state. (Remember, all
primitive types are unboxed, and hence can't be bottom; but types built
with @data@ are all boxed.)
@
-data _State s = S# (State# s)
-@
+data State s = S# (State# s)
+@
\subsubsection{The state transformer combinators}
-Now for the combinators, all of which live inside the @_ST@
+Now for the combinators, all of which live inside the @ST@
abstraction. Notice that @returnST@ and @thenST@ are lazy in the
state.
@
-returnST :: a -> _ST s a
+returnST :: a -> ST s a
returnST a s = (a, s)
-thenST :: _ST s a -> (a -> _ST s b) -> _ST s b
+thenST :: ST s a -> (a -> ST s b) -> ST s b
thenST m k s = let (r,new_s) = m s
in
k r new_s
-fixST :: (a -> _ST s a) -> _ST s a
+fixST :: (a -> ST s a) -> ST s a
fixST k s = let ans = k r s
(r,new_s) = ans
in
ans
@
-The interesting one is, of course, @_runST@. We can't infer its type!
+The interesting one is, of course, @runST@. We can't infer its type!
(It has a funny name because it must be wired into the compiler.)
@
--- _runST :: forall a. (forall s. _ST s a) -> a
-_runST m = case m (S# realWorld#) of
+-- runST :: forall a. (forall s. ST s a) -> a
+runST m = case m (S# realWorld#) of
(r,_) -> r
@
@@ -668,7 +667,7 @@ fundamental combinators above. The @seqST@ combinator is like
@thenST@, except that it discards the result of the first state
transformer:
@
-seqST :: _ST s a -> _ST s b -> _ST s b
+seqST :: ST s a -> ST s b -> ST s b
seqST m1 m2 = m1 `thenST` (\_ -> m2)
@
@@ -687,7 +686,7 @@ seqStrictlyST m k = ... ditto, for seqST ...
The combinator @listST@ takes a list of state transformers, and
composes them in sequence, returning a list of their results:
@
-listST :: [_ST s a] -> _ST s [a]
+listST :: [ST s a] -> ST s [a]
listST [] = returnST []
listST (m:ms) = m `thenST` \ r ->
listST ms `thenST` \ rs ->
@@ -696,13 +695,13 @@ listST (m:ms) = m `thenST` \ r ->
The @mapST@ combinator ``lifts'' a function from a value to state
transformers to one which works over a list of values:
@
-mapST :: (a -> _ST s b) -> [a] -> _ST s [b]
+mapST :: (a -> ST s b) -> [a] -> ST s [b]
mapST f ms = listST (map f ms)
@
The @mapAndUnzipST@ combinator is similar to @mapST@, except that here the
function returns a pair:
@
-mapAndUnzipST :: (a -> _ST s (b,c)) -> [a] -> _ST s ([b],[c])
+mapAndUnzipST :: (a -> ST s (b,c)) -> [a] -> ST s ([b],[c])
mapAndUnzipST f (m:ms)
= f m `thenST` \ ( r1, r2) ->
mapAndUnzipST f ms `thenST` \ (rs1, rs2) ->
@@ -713,15 +712,15 @@ mapAndUnzipST f (m:ms)
\label{sect:io-spec}
The @PrimIO@ type is defined in as a state transformer which manipulates the
-@_RealWorld@.
+@RealWorld@.
@
-type PrimIO a = _ST _RealWorld a -- Transparent
+type PrimIO a = ST RealWorld a -- Transparent
@
The @PrimIO@ type is an ordinary type synonym, transparent to the programmer.
-The type @_RealWorld@ and value @realWorld#@ do not need to be hidden (although
+The type @RealWorld@ and value @realWorld#@ do not need to be hidden (although
there is no particular point in exposing them). Even having a value of type
-@realWorld#@ does not compromise safety, since the type @_ST@ is hidden.
+@realWorld#@ does not compromise safety, since the type @ST@ is hidden.
It is type-correct to use @returnST@ in an I/O context, but it is a
bit more efficient to use @returnPrimIO@. The latter is strict in the
@@ -766,11 +765,11 @@ mapAndUnzipPrimIO f (m:ms)
\subsubsection{Types}
@
-data Array ix elt = _Array (ix,ix) (Array# elt)
-data _ByteArray ix = _ByteArray (ix,ix) ByteArray#
+data Array ix elt = Array (ix,ix) (Array# elt)
+data ByteArray ix = ByteArray (ix,ix) ByteArray#
-data _MutableArray s ix elt = _MutableArray (ix,ix) (MutableArray# s elt)
-data _MutableByteArray s ix = _MutableByteArray (ix,ix) (MutableByteArray# s)
+data MutableArray s ix elt = MutableArray (ix,ix) (MutableArray# s elt)
+data MutableByteArray s ix = MutableByteArray (ix,ix) (MutableByteArray# s)
@
\subsubsection{Operations on immutable arrays}
@@ -779,14 +778,14 @@ Ordinary array indexing is straightforward.
@
(!) :: Ix ix => Array ix elt -> ix -> elt
@
-QUESTIONs: should @_ByteArray@s be indexed by Ints or ix? With byte offsets
+QUESTIONs: should @ByteArray@s be indexed by Ints or ix? With byte offsets
or sized ones? (sized ones [WDP])
@
-indexCharArray :: Ix ix => _ByteArray ix -> ix -> Char
-indexIntArray :: Ix ix => _ByteArray ix -> ix -> Int
-indexAddrArray :: Ix ix => _ByteArray ix -> ix -> _Addr
-indexFloatArray :: Ix ix => _ByteArray ix -> ix -> Float
-indexDoubleArray :: Ix ix => _ByteArray ix -> ix -> Double
+indexCharArray :: Ix ix => ByteArray ix -> ix -> Char
+indexIntArray :: Ix ix => ByteArray ix -> ix -> Int
+indexAddrArray :: Ix ix => ByteArray ix -> ix -> Addr
+indexFloatArray :: Ix ix => ByteArray ix -> ix -> Float
+indexDoubleArray :: Ix ix => ByteArray ix -> ix -> Double
@
@Addr@s are indexed straightforwardly by @Int@s. Unlike the primitive
operations, though, the offsets assume that the array consists entirely of the
@@ -805,45 +804,45 @@ indexStaticArray :: Addr -> Int -> Addr
\subsubsection{Operations on mutable arrays}
@
-newArray :: Ix ix => (ix,ix) -> elt -> _ST s (_MutableArray s ix elt)
-newCharArray :: Ix ix => (ix,ix) -> _ST s (_MutableByteArray s ix)
+newArray :: Ix ix => (ix,ix) -> elt -> ST s (MutableArray s ix elt)
+newCharArray :: Ix ix => (ix,ix) -> ST s (MutableByteArray s ix)
...
@
@
-readArray :: Ix ix => _MutableArray s ix elt -> ix -> _ST s elt
-readCharArray :: Ix ix => _MutableByteArray s ix -> ix -> _ST s Char
+readArray :: Ix ix => MutableArray s ix elt -> ix -> ST s elt
+readCharArray :: Ix ix => MutableByteArray s ix -> ix -> ST s Char
...
@
@
-writeArray :: Ix ix => _MutableArray s ix elt -> ix -> elt -> _ST s ()
-writeCharArray :: Ix ix => _MutableByteArray s ix -> ix -> Char -> _ST s ()
+writeArray :: Ix ix => MutableArray s ix elt -> ix -> elt -> ST s ()
+writeCharArray :: Ix ix => MutableByteArray s ix -> ix -> Char -> ST s ()
...
@
@
-freezeArray :: Ix ix => _MutableArray s ix elt -> _ST s (Array ix elt)
-freezeCharArray :: Ix ix => _MutableByteArray s ix -> _ST s (_ByteArray ix)
+freezeArray :: Ix ix => MutableArray s ix elt -> ST s (Array ix elt)
+freezeCharArray :: Ix ix => MutableByteArray s ix -> ST s (ByteArray ix)
...
@
We have no need on one-function-per-type for unsafe freezing:
@
-unsafeFreezeArray :: Ix ix => _MutableArray s ix elt -> _ST s (Array ix elt)
-unsafeFreezeByteArray :: Ix ix => _MutableByteArray s ix -> _ST s (_ByteArray ix)
+unsafeFreezeArray :: Ix ix => MutableArray s ix elt -> ST s (Array ix elt)
+unsafeFreezeByteArray :: Ix ix => MutableByteArray s ix -> ST s (ByteArray ix)
@
Sometimes we want to snaffle the bounds of one of these beasts:
@
-boundsOfArray :: Ix ix => _MutableArray s ix elt -> (ix, ix)
-boundsOfByteArray :: Ix ix => _MutableByteArray s ix -> (ix, ix)
+boundsOfArray :: Ix ix => MutableArray s ix elt -> (ix, ix)
+boundsOfByteArray :: Ix ix => MutableByteArray s ix -> (ix, ix)
@
Lastly, ``equality'':
@
-sameMutableArray :: _MutableArray s ix elt -> _MutableArray s ix elt -> Bool
-sameMutableByteArray :: _MutableByteArray s ix -> _MutableByteArray s ix -> Bool
+sameMutableArray :: MutableArray s ix elt -> MutableArray s ix elt -> Bool
+sameMutableByteArray :: MutableByteArray s ix -> MutableByteArray s ix -> Bool
@
@@ -854,14 +853,14 @@ sameMutableByteArray :: _MutableByteArray s ix -> _MutableByteArray s ix -> Bool
Mutable variables are (for now anyway) implemented as arrays. The @MutableVar@ type
is opaque, so we can change the implementation later if we want.
@
-type MutableVar s a = _MutableArray s Int a
+type MutableVar s a = MutableArray s Int a
@
\subsubsection{Operations}
@
-newVar :: a -> _ST s (MutableVar s a)
-readVar :: MutableVar s a -> _ST s a
-writeVar :: MutableVar s a -> a -> _ST s ()
+newVar :: a -> ST s (MutableVar s a)
+readVar :: MutableVar s a -> ST s a
+writeVar :: MutableVar s a -> a -> ST s ()
sameVar :: MutableVar s a -> MutableVar s a -> Bool
@
@@ -869,19 +868,19 @@ sameVar :: MutableVar s a -> MutableVar s a -> Bool
Nothing exciting here, just simple boxing up.
@
-data _StablePtr a = _StablePtr (StablePtr# a)
+data StablePtr a = StablePtr (StablePtr# a)
-makeStablePointer :: a -> _StablePtr a
-freeStablePointer :: _StablePtr a -> PrimIO ()
+makeStablePointer :: a -> StablePtr a
+freeStablePointer :: StablePtr a -> PrimIO ()
@
\subsection{Foreign objects}
Again, just boxing up.
@
-data _ForeignObj = _ForeignObj ForeignObj#
+data ForeignObj = ForeignObj ForeignObj#
-makeForeignObj :: _Addr -> _Addr -> PrimIO _ForeignObj
+makeForeignObj :: Addr -> Addr -> PrimIO ForeignObj
@
\subsection{C calls}
@@ -919,34 +918,34 @@ data Screen = S# CHeapPtr#
There are other types that can be passed to C (C-callable). This
table summarises (including the standard boxed-primitive types):
@
-Boxed Type of transferd Corresp. Which is
-Type Prim. component C type *probably*...
------- --------------- ------ -------------
-Char Char# StgChar unsigned char
-Int Int# StgInt long int
-_Word Word# StgWord unsigned long int
-_Addr Addr# StgAddr char *
-Float Float# StgFloat float
-Double Double# StgDouble double
-
-Array Array# StgArray StgPtr
-_ByteArray ByteArray# StgByteArray StgPtr
-_MutableArray MutableArray# StgArray StgPtr
-_MutableByteArray MutableByteArray# StgByteArray StgPtr
-
-_State State# nothing!
-
-_StablePtr StablePtr# StgStablePtr StgPtr
-_ForeignObj ForeignObj# StgForeignObj StgPtr
+Boxed Type of transferd Corresp. Which is
+Type Prim. component C type *probably*...
+------ --------------- ------ -------------
+Char Char# StgChar unsigned char
+Int Int# StgInt long int
+Word Word# StgWord unsigned long int
+Addr Addr# StgAddr char *
+Float Float# StgFloat float
+Double Double# StgDouble double
+
+Array Array# StgArray StgPtr
+ByteArray ByteArray# StgByteArray StgPtr
+MutableArray MutableArray# StgArray StgPtr
+MutableByteArray MutableByteArray# StgByteArray StgPtr
+
+State State# nothing!
+
+StablePtr StablePtr# StgStablePtr StgPtr
+ForeignObj ForeignObj# StgForeignObj StgPtr
@
All of the above are {\em C-returnable} except:
@
- Array, _ByteArray, _MutableArray, _MutableByteArray
+ Array, ByteArray, MutableArray, MutableByteArray
@
-{\bf ToDo:} I'm pretty wary of @Array@ and @_MutableArray@ being in
-this list, and not too happy about @_State@ [WDP].
+{\bf ToDo:} I'm pretty wary of @Array@ and @MutableArray@ being in
+this list, and not too happy about @State@ [WDP].
{\bf ToDo:} Can code generator pass all the primitive types? Should this be
extended to include {\tt Bool\/} (or any enumeration type?)
@@ -993,29 +992,24 @@ are stored on the heap.
@
data Char = C# Char#
data Int = I# Int#
-data _Word = W# Word#
-data _Addr = A# Addr#
+data Word = W# Word#
+data Addr = A# Addr#
data Float = F# Float#
data Double = D# Double#
data Integer = J# Int# Int# ByteArray#
-- and the other boxed-primitive types:
- Array, _ByteArray, _MutableArray, _MutableByteArray,
- _StablePtr, _ForeignObj
+ Array, ByteArray, MutableArray, MutableByteArray,
+ StablePtr, ForeignObj
data Bool = False | True
-data CMP_TAG# = LT# | EQ# | GT# -- used in derived comparisons
+data Ordering = LT | EQ | GT -- used in derived comparisons
data List a = [] | a : (List a)
-- tuples...
-data Ratio a = a :% a
-type Rational = Ratio Integer
-
-data {Request,Response,etc} -- so we can check the type of "main"
-
-data _Lift a = _Lift a -- used Yukkily as described elsewhere
+data Lift a = Lift a -- used Yukkily as described elsewhere
type String = [Char] -- convenience, only
@
@@ -1032,16 +1026,13 @@ for you, and if you don't use any weird flags (notably
Haskell report says, and the full user namespaces should be available
to you.
-Exception: until we burn in the new names @_scc_@ and @_ccall_@, the
-names @scc@ and @ccall@ are still available.
-
\subsection{If you mess about with @import Prelude@...}
-Innocent renaming and hiding, e.g.,
+Innocent hiding, e.g.,
@
-import Prelude hiding ( fromIntegral ) renaming (map to mop)
+import Prelude hiding ( fromIntegral )
@
-should work just fine (even it {\em is} atrocious programming practice).
+should work just fine.
There are some things you can do that will make GHC crash, e.g.,
hiding a standard class:
@@ -1059,13 +1050,5 @@ It is possible that some name conflicts between your code and the
wired-in things might spring to life (though we doubt it...).
Change your names :-)
-\subsection{@import PreludeGlaST@}
-
-@
-type ST s a = _ST s a -- so you don't need -fglasgow-exts...
-@
-
-\subsection{@import PreludeGlaMisc@}
-
\end{document}