Use explicit language extensions & remove extension fields from base.cabal
[ghc-base.git] / Foreign / Marshal / Error.hs
index 5b43dfc..ccf514d 100644 (file)
@@ -1,33 +1,30 @@
-{-# OPTIONS -fno-implicit-prelude #-}
+{-# LANGUAGE CPP, NoImplicitPrelude #-}
+
 -----------------------------------------------------------------------------
 -- |
 -- Module      :  Foreign.Marshal.Error
 -- Copyright   :  (c) The FFI task force 2001
--- License     :  BSD-style (see the file libraries/core/LICENSE)
+-- License     :  BSD-style (see the file libraries/base/LICENSE)
 -- 
 -- Maintainer  :  ffi@haskell.org
 -- Stability   :  provisional
 -- Portability :  portable
 --
--- $Id: Error.hs,v 1.3 2002/04/24 16:31:44 simonmar Exp $
---
--- Marshalling support: Handling of common error conditions
+-- Routines for testing return values and raising a 'userError' exception
+-- in case of values indicating an error state.
 --
 -----------------------------------------------------------------------------
 
 module Foreign.Marshal.Error (
-
-  -- throw an exception on specific return values
-  --
   throwIf,       -- :: (a -> Bool) -> (a -> String) -> IO a       -> IO a
   throwIf_,      -- :: (a -> Bool) -> (a -> String) -> IO a       -> IO ()
   throwIfNeg,    -- :: (Ord a, Num a) 
-                -- =>                (a -> String) -> IO a       -> IO a
+                 -- =>                (a -> String) -> IO a       -> IO a
   throwIfNeg_,   -- :: (Ord a, Num a)
-                -- =>                (a -> String) -> IO a       -> IO ()
+                 -- =>                (a -> String) -> IO a       -> IO ()
   throwIfNull,   -- ::                String        -> IO (Ptr a) -> IO (Ptr a)
 
-  -- discard return value
+  -- Discard return value
   --
   void           -- IO a -> IO ()
 ) where
@@ -35,47 +32,54 @@ module Foreign.Marshal.Error (
 import Foreign.Ptr
 
 #ifdef __GLASGOW_HASKELL__
+#ifdef __HADDOCK__
+import Data.Bool
+import System.IO.Error
+#endif
 import GHC.Base
 import GHC.Num
-import GHC.IOBase
+-- import GHC.IO
+import GHC.IO.Exception
 #endif
 
 -- exported functions
 -- ------------------
 
--- guard an IO operation and throw an exception if the result meets the given
--- predicate 
---
--- * the second argument computes an error message from the result of the IO
---   operation
+-- |Execute an 'IO' action, throwing a 'userError' if the predicate yields
+-- 'True' when applied to the result returned by the 'IO' action.
+-- If no exception is raised, return the result of the computation.
 --
-throwIf                 :: (a -> Bool) -> (a -> String) -> IO a -> IO a
+throwIf :: (a -> Bool)  -- ^ error condition on the result of the 'IO' action
+        -> (a -> String) -- ^ computes an error message from erroneous results
+                        -- of the 'IO' action
+        -> IO a         -- ^ the 'IO' action to be executed
+        -> IO a
 throwIf pred msgfct act  = 
   do
     res <- act
     (if pred res then ioError . userError . msgfct else return) res
 
--- like `throwIf', but discarding the result
+-- |Like 'throwIf', but discarding the result
 --
 throwIf_                 :: (a -> Bool) -> (a -> String) -> IO a -> IO ()
 throwIf_ pred msgfct act  = void $ throwIf pred msgfct act
 
--- guards against negative result values
+-- |Guards against negative result values
 --
 throwIfNeg :: (Ord a, Num a) => (a -> String) -> IO a -> IO a
 throwIfNeg  = throwIf (< 0)
 
--- like `throwIfNeg', but discarding the result
+-- |Like 'throwIfNeg', but discarding the result
 --
 throwIfNeg_ :: (Ord a, Num a) => (a -> String) -> IO a -> IO ()
 throwIfNeg_  = throwIf_ (< 0)
 
--- guards against null pointers
+-- |Guards against null pointers
 --
 throwIfNull :: String -> IO (Ptr a) -> IO (Ptr a)
 throwIfNull  = throwIf (== nullPtr) . const
 
--- discard the return value of an IO action
+-- |Discard the return value of an 'IO' action
 --
 void     :: IO a -> IO ()
 void act  = act >> return ()