Big patch to improve Unicode support in GHC. Validated on OS X and Windows, this
[ghc-base.git] / Control / Exception / Base.hs
index a11ff68..a617917 100644 (file)
@@ -1,4 +1,7 @@
-{-# OPTIONS_GHC -XNoImplicitPrelude #-}
+{-# LANGUAGE CPP, NoImplicitPrelude, MagicHash #-}
+#ifdef __GLASGOW_HASKELL__
+{-# LANGUAGE DeriveDataTypeable, StandaloneDeriving #-}
+#endif
 
 #include "Typeable.h"
 
@@ -78,13 +81,14 @@ module Control.Exception.Base (
         -- * Asynchronous Exceptions
 
         -- ** Asynchronous exception control
-
         mask,
+#ifndef __NHC__
         mask_,
         uninterruptibleMask,
         uninterruptibleMask_,
         MaskingState(..),
         getMaskingState,
+#endif
 
         -- ** (deprecated) Asynchronous exception control
 
@@ -108,18 +112,19 @@ module Control.Exception.Base (
         -- * Calls for GHC runtime
         recSelError, recConError, irrefutPatError, runtimeError,
         nonExhaustiveGuardsError, patError, noMethodBindingError,
+        absentError,
         nonTermination, nestedAtomically,
 #endif
   ) where
 
 #ifdef __GLASGOW_HASKELL__
 import GHC.Base
-import GHC.IO hiding (finally,onException)
+import GHC.IO hiding (bracket,finally,onException)
 import GHC.IO.Exception
 import GHC.Exception
 import GHC.Show
 -- import GHC.Exception hiding ( Exception )
-import GHC.Conc
+import GHC.Conc.Sync
 #endif
 
 #ifdef __HUGS__
@@ -223,6 +228,10 @@ assert :: Bool -> a -> a
 assert True  x = x
 assert False _ = throw (toException (UserError "" "Assertion failed"))
 
+mask   :: ((IO a-> IO a) -> IO a) -> IO a
+mask action = action restore
+    where restore act = act
+
 #endif
 
 #ifdef __HUGS__
@@ -420,7 +429,7 @@ catchJust
         -> IO a
 catchJust p a handler = catch a handler'
   where handler' e = case p e of
-                        Nothing -> throw e
+                        Nothing -> throwIO e
                         Just b  -> handler b
 
 -- | A version of 'catch' with the arguments swapped around; useful in
@@ -446,7 +455,7 @@ handleJust p =  flip (catchJust p)
 
 mapException :: (Exception e1, Exception e2) => (e1 -> e2) -> a -> a
 mapException f v = unsafePerformIO (catch (evaluate v)
-                                          (\x -> throw (f x)))
+                                          (\x -> throwIO (f x)))
 
 -----------------------------------------------------------------------------
 -- 'try' and variations.
@@ -476,14 +485,14 @@ tryJust p a = do
   case r of
         Right v -> return (Right v)
         Left  e -> case p e of
-                        Nothing -> throw e
+                        Nothing -> throwIO e
                         Just b  -> return (Left b)
 
 -- | Like 'finally', but only performs the final action if there was an
 -- exception raised by the computation.
 onException :: IO a -> IO b -> IO a
 onException io what = io `catch` \e -> do _ <- what
-                                          throw (e :: SomeException)
+                                          throwIO (e :: SomeException)
 
 -----------------------------------------------------------------------------
 -- Some Useful Functions
@@ -700,12 +709,14 @@ instance Exception NestedAtomically
 
 #ifdef __GLASGOW_HASKELL__
 recSelError, recConError, irrefutPatError, runtimeError,
-             nonExhaustiveGuardsError, patError, noMethodBindingError
+  nonExhaustiveGuardsError, patError, noMethodBindingError,
+  absentError
         :: Addr# -> a   -- All take a UTF8-encoded C string
 
 recSelError              s = throw (RecSelError ("No match in record selector "
                                                 ++ unpackCStringUtf8# s))  -- No location info unfortunately
 runtimeError             s = error (unpackCStringUtf8# s)                   -- No location info unfortunately
+absentError              s = error ("Oops!  Entered absent arg " ++ unpackCStringUtf8# s)
 
 nonExhaustiveGuardsError s = throw (PatternMatchFail (untangle s "Non-exhaustive guards in"))
 irrefutPatError          s = throw (PatternMatchFail (untangle s "Irrefutable pattern failed for pattern"))