Skip to content
Snippets Groups Projects
Commit 6bfd2f54 authored by Simon Marlow's avatar Simon Marlow
Browse files

[project @ 1998-05-22 15:57:05 by simonm]

- Add NOINLINE pragmas to the unsafe things (unsafe*IO, unsafe*ST, runST etc.)
- Move unsafe function back into the proper modules
- Remove PrelUnsafe*.lhs
parent 7f1ab1dd
No related merge requests found
......@@ -19,7 +19,6 @@ import PrelNum
import PrelAddr
import PrelIOBase
import IO
import PrelUnsafe ( unsafePerformIO )
import PrelST
import Ratio
......
......@@ -42,7 +42,6 @@ module Directory
import PrelBase
import PrelIOBase
import PrelST
import PrelUnsafe ( unsafePerformIO )
import PrelArr
import PrelPack ( unpackNBytesST )
import PrelForeign ( Word(..) )
......
......@@ -33,7 +33,6 @@ module IO (
) where
import PrelST
import PrelUnsafe ( unsafePerformIO, unsafeInterleaveIO )
import PrelIOBase
import PrelArr ( MutableByteArray(..), newCharArray )
import PrelHandle -- much of the real stuff is in here
......
......@@ -54,12 +54,6 @@ Time_HC_OPTS += -monly-3-regs -H16m
# Far too much heap is needed to compile PrelNum with -O at the
# moment, but there you go..
PrelNum_HC_OPTS += -H30m
# Note: this option has to go in the Makefile rather than in an
# OPTIONS line in the source file. The reason being that we want
# to override the SRC_HC_OPTS of -O, and anything option coming
# from the Makefile overrides what's in OPTIONS lines. (mumble_HC_OPTS
# does override SRC_HC_OPTS settings)
PrelUnsafe_HC_OPTS += -Onot
PrelBase_HC_OPTS += -H12m
PrelRead_HC_OPTS += -H13m
......
......@@ -18,7 +18,6 @@ import PrelST
import PrelBase
import PrelCCall
import PrelAddr
import PrelUnsafeST ( runST )
import PrelGHC
infixl 9 !, //
......
......@@ -24,7 +24,6 @@ module PrelForeign (
import PrelIOBase
import PrelST
import PrelUnsafe
import PrelBase
import PrelCCall
import PrelAddr
......
......@@ -19,7 +19,6 @@ import PrelArr ( ByteArray(..), newVar, readVar, writeVar )
import PrelRead ( Read )
import PrelList ( span )
import PrelIOBase
import PrelUnsafe ( unsafePerformIO )
import PrelTup
import PrelMaybe
import PrelBase
......
......@@ -393,3 +393,37 @@ data BufferMode
performGC :: IO ()
performGC = _ccall_GC_ StgPerformGarbageCollection
\end{code}
%*********************************************************
%* *
\subsection{Unsafe @IO@ operations}
%* *
%*********************************************************
\begin{code}
{-# NOINLINE unsafePerformIO #-}
unsafePerformIO :: IO a -> a
unsafePerformIO (IO m)
= case m realWorld# of
IOok _ r -> r
IOfail _ e -> error ("unsafePerformIO: I/O error: " ++ show e ++ "\n")
{-# NOINLINE unsafeInterleaveIO #-}
unsafeInterleaveIO :: IO a -> IO a
unsafeInterleaveIO (IO m) = IO ( \ s ->
let
IOok _ r = m s
in
IOok s r)
{-# NOINLINE trace #-}
trace :: String -> a -> a
trace string expr
= unsafePerformIO (
((_ccall_ PreTraceHook sTDERR{-msg-}):: IO ()) >>
fputs sTDERR string >>
((_ccall_ PostTraceHook sTDERR{-msg-}):: IO ()) >>
return expr )
where
sTDERR = (``stderr'' :: Addr)
\end{code}
......@@ -26,7 +26,7 @@ import PrelList
import PrelMaybe
import PrelArr ( Array, array, (!) )
import PrelUnsafe ( unsafePerformIO )
import PrelIOBase ( unsafePerformIO )
import Ix ( Ix(..) )
import PrelCCall () -- we need the definitions of CCallable and
-- CReturnable for the _ccall_s herein.
......
......@@ -52,7 +52,6 @@ import PrelList ( length )
import PrelST
import PrelArr
import PrelAddr
import PrelUnsafeST ( runST )
\end{code}
......
......@@ -55,8 +55,56 @@ fixST k = ST $ \ s ->
in
ans
{-# NOINLINE unsafeInterleaveST #-}
unsafeInterleaveST :: ST s a -> ST s a
unsafeInterleaveST (ST m) = ST ( \ s ->
let
STret _ r = m s
in
STret s r)
\end{code}
Definition of runST
~~~~~~~~~~~~~~~~~~~
SLPJ 95/04: Why @runST@ must not have an unfolding; consider:
\begin{verbatim}
f x =
runST ( \ s -> let
(a, s') = newArray# 100 [] s
(_, s'') = fill_in_array_or_something a x s'
in
freezeArray# a s'' )
\end{verbatim}
If we inline @runST@, we'll get:
\begin{verbatim}
f x = let
(a, s') = newArray# 100 [] realWorld#{-NB-}
(_, s'') = fill_in_array_or_something a x s'
in
freezeArray# a s''
\end{verbatim}
And now the @newArray#@ binding can be floated to become a CAF, which
is totally and utterly wrong:
\begin{verbatim}
f = let
(a, s') = newArray# 100 [] realWorld#{-NB-} -- YIKES!!!
in
\ x ->
let (_, s'') = fill_in_array_or_something a x s' in
freezeArray# a s''
\end{verbatim}
All calls to @f@ will share a {\em single} array! End SLPJ 95/04.
\begin{code}
{-# NOINLINE runST #-}
runST :: (All s => ST s a) -> a
runST st =
case st of
ST m -> case m realWorld# of
STret _ r -> r
\end{code}
%*********************************************************
%* *
......
%
% (c) The AQUA Project, Glasgow University, 1994-1996
%
\section[PrelUnsafe]{Module @PrelUnsafe@}
These functions have their own module because we definitely don't want
them to be inlined. The reason is that we may end up turning an action
into a constant when it is not:
new :: IORef Int
new =
let
foo = unsafePerformIO getNextValue
in
newIORef foo
If unsafePerformIO is inlined here, the application of getNextValue to the realWorld#
token might be floated out, leaving us with
foo' = getNextValue realWorld#
new :: IORef Int
new = newIORef foo'
which is not what we want.
\begin{code}
{-# OPTIONS -fno-implicit-prelude #-}
module PrelUnsafe
( unsafePerformIO,
unsafeInterleaveIO,
trace,
) where
\end{code}
\begin{code}
import PrelBase
import PrelIOBase
import PrelAddr
import {-# SOURCE #-} PrelErr ( error )
\end{code}
%*********************************************************
%* *
\subsection{Unsafe @IO@ operations}
%* *
%*********************************************************
\begin{code}
unsafePerformIO :: IO a -> a
unsafePerformIO (IO m)
= case m realWorld# of
IOok _ r -> r
IOfail _ e -> error ("unsafePerformIO: I/O error: " ++ show e ++ "\n")
unsafeInterleaveIO :: IO a -> IO a
unsafeInterleaveIO (IO m) = IO ( \ s ->
let
res =
case m s of
IOok _ r -> r
IOfail _ e -> error ("unsafeInterleaveIO: I/O error: " ++ show e ++ "\n")
in
IOok s res
)
trace :: String -> a -> a
trace string expr
= unsafePerformIO (
((_ccall_ PreTraceHook sTDERR{-msg-}):: IO ()) >>
fputs sTDERR string >>
((_ccall_ PostTraceHook sTDERR{-msg-}):: IO ()) >>
return expr )
where
sTDERR = (``stderr'' :: Addr)
\end{code}
%
% (c) The AQUA Project, Glasgow University, 1994-1996
%
\section[UnsafeST]{Module @UnsafeST@}
These functions have their own module because we definitely don't want
them to be inlined.
\begin{code}
{-# OPTIONS -fno-implicit-prelude #-}
module PrelUnsafeST (unsafeInterleaveST, runST) where
import PrelST
import PrelBase
\end{code}
\begin{code}
unsafeInterleaveST :: ST s a -> ST s a
unsafeInterleaveST (ST m) = ST ( \ s ->
let
STret _ r = m s
in
STret s r)
\end{code}
Definition of runST
~~~~~~~~~~~~~~~~~~~
SLPJ 95/04: Why @runST@ must not have an unfolding; consider:
\begin{verbatim}
f x =
runST ( \ s -> let
(a, s') = newArray# 100 [] s
(_, s'') = fill_in_array_or_something a x s'
in
freezeArray# a s'' )
\end{verbatim}
If we inline @runST@, we'll get:
\begin{verbatim}
f x = let
(a, s') = newArray# 100 [] realWorld#{-NB-}
(_, s'') = fill_in_array_or_something a x s'
in
freezeArray# a s''
\end{verbatim}
And now the @newArray#@ binding can be floated to become a CAF, which
is totally and utterly wrong:
\begin{verbatim}
f = let
(a, s') = newArray# 100 [] realWorld#{-NB-} -- YIKES!!!
in
\ x ->
let (_, s'') = fill_in_array_or_something a x s' in
freezeArray# a s''
\end{verbatim}
All calls to @f@ will share a {\em single} array! End SLPJ 95/04.
\begin{code}
runST :: (All s => ST s a) -> a
runST st =
case st of
ST m -> case m realWorld# of
STret _ r -> r
\end{code}
......@@ -37,7 +37,6 @@ import PrelBase
import PrelIOBase
import PrelArr
import PrelST
import PrelUnsafe ( unsafePerformIO )
import PrelAddr
import PrelPack ( unpackCString )
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment