[project @ 2000-03-23 17:45:17 by simonpj]
[ghc-hetmet.git] / ghc / lib / std / PrelHandle.lhs
index 25b98ea..5372159 100644 (file)
@@ -16,7 +16,6 @@ module PrelHandle where
 
 import PrelBase
 import PrelAddr                ( Addr, nullAddr )
-import PrelArr         ( newVar, readVar, writeVar )
 import PrelByteArr     ( ByteArray(..), MutableByteArray(..) )
 import PrelRead                ( Read )
 import PrelList        ( span )
@@ -34,9 +33,7 @@ import PrelWeak               ( addForeignFinalizer )
 #endif
 import Ix
 
-#ifdef __CONCURRENT_HASKELL__
 import PrelConc
-#endif
 
 #ifndef __PARALLEL_HASKELL__
 import PrelForeign  ( makeForeignObj )
@@ -66,20 +63,11 @@ The @Handle@ and @Handle__@ types are defined in @IOBase@.
 
 \begin{code}
 {-# INLINE newHandle   #-}
-{-# INLINE withHandle #-}
 newHandle     :: Handle__ -> IO Handle
 
-#if defined(__CONCURRENT_HASKELL__)
-
 -- Use MVars for concurrent Haskell
 newHandle hc  = newMVar        hc      >>= \ h ->
                return (Handle h)
-#else 
-
--- Use ordinary MutableVars for non-concurrent Haskell
-newHandle hc  = stToIO (newVar hc      >>= \ h ->
-                       return (Handle h))
-#endif
 \end{code}
 
 %*********************************************************
@@ -109,8 +97,8 @@ orignal handle is always replaced [ this is the case at the moment,
 but we might want to revisit this in the future --SDM ].
 
 \begin{code}
-#ifdef __CONCURRENT_HASKELL__
 withHandle :: Handle -> (Handle__ -> IO (Handle__,a)) -> IO a
+{-# INLINE withHandle #-}
 withHandle (Handle h) act = do
    h_ <- takeMVar h
    (h',v)  <- catchException (act h_) (\ ex -> putMVar h h_ >> throw ex)
@@ -118,6 +106,7 @@ withHandle (Handle h) act = do
    return v
 
 withHandle_ :: Handle -> (Handle__ -> IO a) -> IO a
+{-# INLINE withHandle_ #-}
 withHandle_ (Handle h) act = do
    h_ <- takeMVar h
    v  <- catchException (act h_) (\ ex -> putMVar h h_ >> throw ex)
@@ -125,22 +114,12 @@ withHandle_ (Handle h) act = do
    return v
    
 withHandle__ :: Handle -> (Handle__ -> IO Handle__) -> IO ()
+{-# INLINE withHandle__ #-}
 withHandle__ (Handle h) act = do
    h_ <- takeMVar h
    h'  <- catchException (act h_) (\ ex -> putMVar h h_ >> throw ex)
    putMVar h h'
    return ()
-
-#else
-   -- of questionable value to install this exception
-   -- handler, but let's do it in the non-concurrent
-   -- case too, for now.
-withHandle (Handle h) act = do
-   h_ <- stToIO (readVar h)
-   v  <- catchException (act h_) (\ ex -> stToIO (writeVar h h_) >> throw ex)
-   return v
-
-#endif
 \end{code}
 
 nullFile__ is only used for closed handles, plugging it in as a null