[project @ 2005-01-31 21:07:15 by panne]
[ghc-base.git] / GHC / IOBase.lhs
index b669a11..233148b 100644 (file)
@@ -1,5 +1,5 @@
 \begin{code}
-{-# OPTIONS -fno-implicit-prelude #-}
+{-# OPTIONS_GHC -fno-implicit-prelude #-}
 -----------------------------------------------------------------------------
 -- |
 -- Module      :  GHC.IOBase
@@ -122,6 +122,12 @@ stToIO (ST m) = IO m
 ioToST       :: IO a -> ST RealWorld a
 ioToST (IO m) = (ST m)
 
+-- This relies on IO and ST having the same representation modulo the
+-- constraint on the type of the state
+--
+unsafeIOToST        :: IO a -> ST s a
+unsafeIOToST (IO io) = ST $ \ s -> (unsafeCoerce# io) s
+
 -- ---------------------------------------------------------------------------
 -- Unsafe IO operations
 
@@ -167,7 +173,7 @@ It is less well known that
 >     
 >     main = do
 >            writeIORef test [42]
->            bang \<- readIORef test
+>            bang <- readIORef test
 >            print (bang :: [Char])
 
 This program will core dump.  This problem with polymorphic references
@@ -181,13 +187,19 @@ help of 'unsafePerformIO'.  So be careful!
 unsafePerformIO        :: IO a -> a
 unsafePerformIO (IO m) = case m realWorld# of (# _, r #)   -> r
 
+-- Why do we NOINLINE unsafePerformIO?  See the comment with
+-- GHC.ST.runST.  Essentially the issue is that the IO computation
+-- inside unsafePerformIO must be atomic: it must either all run, or
+-- not at all.  If we let the compiler see the application of the IO
+-- to realWorld#, it might float out part of the IO.
+
 {-|
 'unsafeInterleaveIO' allows 'IO' computation to be deferred lazily.
 When passed a value of type @IO a@, the 'IO' will only be performed
 when the value of the @a@ is demanded.  This is used to implement lazy
 file reading, see 'System.IO.hGetContents'.
 -}
-{-# NOINLINE unsafeInterleaveIO #-}
+{-# INLINE unsafeInterleaveIO #-}
 unsafeInterleaveIO :: IO a -> IO a
 unsafeInterleaveIO (IO m)
   = IO ( \ s -> let
@@ -195,6 +207,10 @@ unsafeInterleaveIO (IO m)
                in
                (# s, r #))
 
+-- We believe that INLINE on unsafeInterleaveIO is safe, because the
+-- state from this IO thread is passed explicitly to the interleaved
+-- IO, so it cannot be floated out and shared.
+
 -- ---------------------------------------------------------------------------
 -- Handle type
 
@@ -250,6 +266,15 @@ instance Eq (MVar a) where
 -- enough information to identify the handle for debugging.  A handle is
 -- equal according to '==' only to itself; no attempt
 -- is made to compare the internal state of different handles for equality.
+--
+-- GHC note: a 'Handle' will be automatically closed when the garbage
+-- collector detects that it has become unreferenced by the program.
+-- However, relying on this behaviour is not generally recommended:
+-- the garbage collector is unpredictable.  If possible, use explicit
+-- an explicit 'hClose' to close 'Handle's when they are no longer
+-- required.  GHC does not currently attempt to free up file
+-- descriptors when they have run out, it is your responsibility to
+-- ensure that this doesn't happen.
 
 data Handle 
   = FileHandle                         -- A normal handle to a file
@@ -543,6 +568,10 @@ data Exception
        -- ^The current thread was executing a call to
        -- 'Control.Concurrent.MVar.takeMVar' that could never return,
        -- because there are no other references to this 'MVar'.
+  | BlockedIndefinitely
+       -- ^The current thread was waiting to retry an atomic memory transaction
+       -- that could never become possible to complete because there are no other
+       -- threads referring to any of teh TVars involved.
   | Deadlock
        -- ^There are no runnable threads, so the program is
        -- deadlocked.  The 'Deadlock' exception is
@@ -680,6 +709,7 @@ instance Show Exception where
   showsPrec _ (DynException _err)        = showString "unknown exception"
   showsPrec _ (AsyncException e)        = shows e
   showsPrec _ (BlockedOnDeadMVar)       = showString "thread blocked indefinitely"
+  showsPrec _ (BlockedIndefinitely)     = showString "thread blocked indefinitely"
   showsPrec _ (NonTermination)           = showString "<<loop>>"
   showsPrec _ (Deadlock)                 = showString "<<deadlock>>"