summaryrefslogtreecommitdiff
path: root/ghc/lib/exts/IOExts.lhs
diff options
context:
space:
mode:
authorsof <unknown>1998-08-14 13:01:45 +0000
committersof <unknown>1998-08-14 13:01:45 +0000
commit50a3ac89dc651b98ce13568521b48c7a61d082fc (patch)
tree1a092a5b5fe13056a7c10b4535f273e4cfed00bd /ghc/lib/exts/IOExts.lhs
parent5de97ffe57fc0bc90c8562a4685c30ddca783c72 (diff)
downloadhaskell-50a3ac89dc651b98ce13568521b48c7a61d082fc.tar.gz
[project @ 1998-08-14 13:01:44 by sof]
New functions: unsafeIOToST, hConnectTo
Diffstat (limited to 'ghc/lib/exts/IOExts.lhs')
-rw-r--r--ghc/lib/exts/IOExts.lhs52
1 files changed, 46 insertions, 6 deletions
diff --git a/ghc/lib/exts/IOExts.lhs b/ghc/lib/exts/IOExts.lhs
index d74c21a671..8b09456ca0 100644
--- a/ghc/lib/exts/IOExts.lhs
+++ b/ghc/lib/exts/IOExts.lhs
@@ -1,9 +1,15 @@
%
% (c) The AQUA Project, Glasgow University, 1994-1996
%
-
\section[IOExts]{Module @IOExts@}
+@IOExts@ provides useful functionality that fall outside the
+standard Haskell IO interface. Expect the contents of IOExts
+to be the same for Hugs and GHC (same goes for any other
+Hugs/GHC extension libraries, unless a function/type is
+explicitly flagged as being implementation specific
+extension.)
+
\begin{code}
{-# OPTIONS -fno-implicit-prelude #-}
@@ -12,14 +18,12 @@ module IOExts
, unsafePerformIO
, unsafeInterleaveIO
- , IORef
- -- instance Eq (IORef a)
+ , IORef -- instance of: Eq
, newIORef
, readIORef
, writeIORef
- , IOArray
- -- instance Eq (IOArray ix a)
+ , IOArray -- instance of: Eq
, newIOArray
, boundsIOArray
, readIOArray
@@ -31,25 +35,34 @@ module IOExts
, hSetEcho
, hGetEcho
+ , hIsTerminalDevice
+ , hConnectTo
, trace
, performGC
, reallyUnsafePtrEq
+ , unsafeIOToST
+
) where
+
\end{code}
\begin{code}
import PrelBase
import PrelIOBase
import PrelHandle ( openFileEx, IOModeEx(..),
- hSetEcho, hGetEcho
+ hSetEcho, hGetEcho, getHandleFd
)
import PrelST
import PrelArr
import PrelGHC
import Ix
+import IO
+import PrelHandle
+import PrelErr
+reallyUnsafePtrEq :: a -> a -> Bool
reallyUnsafePtrEq a b =
case reallyUnsafePtrEquality# a b of
0# -> False
@@ -93,3 +106,30 @@ writeIOArray (IOArray arr) ix elt = stToIO (writeArray arr ix elt)
freezeIOArray (IOArray arr) = stToIO (freezeArray arr)
\end{code}
+\begin{code}
+{-# NOINLINE trace #-}
+trace :: String -> a -> a
+trace string expr = unsafePerformIO $ do
+ fd <- getHandleFd stderr
+ hPutStrLn stderr string
+ _ccall_ PostTraceHook fd
+ return expr
+
+\end{code}
+
+\begin{code}
+unsafeIOToST :: IO a -> ST s a
+unsafeIOToST (IO io) = ST $ \ s ->
+ case ((unsafeCoerce# io) s) of
+ IOok new_s a -> unsafeCoerce# (STret new_s a)
+ IOfail new_s e -> error ("I/O Error (unsafeIOToST): " ++ showsPrec 0 e "\n")
+\end{code}
+
+Not something you want to call normally, but useful
+in the cases where you do want to flush stuff out of
+the heap or make sure you've got room enough
+
+\begin{code}
+performGC :: IO ()
+performGC = _ccall_GC_ StgPerformGarbageCollection
+\end{code}