import Control.Arrow.ArrowZero to help nhc98's type checker
[haskell-directory.git] / Control / Concurrent / MVar.hs
index c56750f..7213cf1 100644 (file)
@@ -28,15 +28,15 @@ module Control.Concurrent.MVar
        , withMVar      -- :: MVar a -> (a -> IO b) -> IO b
        , modifyMVar_   -- :: MVar a -> (a -> IO a) -> IO ()
        , modifyMVar    -- :: MVar a -> (a -> IO (a,b)) -> IO b
+#ifndef __HUGS__
        , addMVarFinalizer -- :: MVar a -> IO () -> IO ()
+#endif
     ) where
 
 #ifdef __HUGS__
-import ConcBase        ( MVar, newEmptyMVar, newMVar, takeMVar, putMVar,
+import Hugs.ConcBase ( MVar, newEmptyMVar, newMVar, takeMVar, putMVar,
                  tryTakeMVar, tryPutMVar, isEmptyMVar,
-                  readMVar, swapMVar,
                )
-import Prelude hiding( catch )
 #endif
 
 #ifdef __GLASGOW_HASKELL__
@@ -45,15 +45,9 @@ import GHC.Conc      ( MVar, newEmptyMVar, newMVar, takeMVar, putMVar,
                )
 #endif
 
+import Prelude
 import Control.Exception as Exception
 
-#ifdef __HUGS__
--- This is as close as Hugs gets to providing throw
-throw :: Exception -> IO a
-throw = throwIO
-#endif
-
-#ifdef __GLASGOW_HASKELL__
 {-|
   This is a combination of 'takeMVar' and 'putMVar'; ie. it takes the value
   from the 'MVar', puts it back, and also returns it.
@@ -67,8 +61,11 @@ readMVar m =
 
 -- |Swap the contents of an 'MVar' for a new value.
 swapMVar :: MVar a -> a -> IO a
-swapMVar mvar new = modifyMVar mvar (\old -> return (new,old))
-#endif
+swapMVar mvar new =
+  block $ do
+    old <- takeMVar mvar
+    putMVar mvar new
+    return old
 
 {-|
   'withMVar' is a safe wrapper for operating on the contents of an
@@ -76,6 +73,9 @@ swapMVar mvar new = modifyMVar mvar (\old -> return (new,old))
   original contents of the 'MVar' if an exception is raised (see
   "Control.Exception").
 -}
+{-# INLINE withMVar #-}
+-- inlining has been reported to have dramatic effects; see
+-- http://www.haskell.org//pipermail/haskell/2006-May/017907.html
 withMVar :: MVar a -> (a -> IO b) -> IO b
 withMVar m io = 
   block $ do
@@ -90,6 +90,7 @@ withMVar m io =
   'modifyMVar' will replace the original contents of the 'MVar' if an
   exception is raised during the operation.
 -}
+{-# INLINE modifyMVar_ #-}
 modifyMVar_ :: MVar a -> (a -> IO a) -> IO ()
 modifyMVar_ m io = 
   block $ do
@@ -102,6 +103,7 @@ modifyMVar_ m io =
   A slight variation on 'modifyMVar_' that allows a value to be
   returned (@b@) in addition to the modified value of the 'MVar'.
 -}
+{-# INLINE modifyMVar #-}
 modifyMVar :: MVar a -> (a -> IO (a,b)) -> IO b
 modifyMVar m io = 
   block $ do