add GHC.HetMet.{hetmet_kappa,hetmet_kappa_app}
[ghc-base.git] / System / IO.hs
index 8982119..bf26835 100644 (file)
@@ -1,4 +1,5 @@
-{-# OPTIONS_GHC -fno-implicit-prelude #-}
+{-# LANGUAGE CPP, NoImplicitPrelude #-}
+
 -----------------------------------------------------------------------------
 -- |
 -- Module      :  System.IO
 module System.IO (
     -- * The IO monad
 
-    IO,                               -- instance MonadFix
-    fixIO,                    -- :: (a -> IO a) -> IO a
+    IO,                        -- instance MonadFix
+    fixIO,                     -- :: (a -> IO a) -> IO a
 
     -- * Files and handles
 
-    FilePath,                 -- :: String
+    FilePath,                  -- :: String
+
+    Handle,             -- abstract, instance of: Eq, Show.
 
-    Handle,            -- abstract, instance of: Eq, Show.
+    -- | 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
+    -- 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.
 
     -- ** Standard handles
 
@@ -36,20 +46,21 @@ module System.IO (
 
     -- ** Opening files
 
-    openFile,                 -- :: FilePath -> IOMode -> IO Handle
+    withFile,
+    openFile,                  -- :: FilePath -> IOMode -> IO Handle
     IOMode(ReadMode,WriteMode,AppendMode,ReadWriteMode),
 
     -- ** Closing files
 
-    hClose,                   -- :: Handle -> IO ()
+    hClose,                    -- :: Handle -> IO ()
 
     -- ** Special cases
 
     -- | These functions are also exported by the "Prelude".
 
-    readFile,                 -- :: FilePath -> IO String
-    writeFile,                -- :: FilePath -> String -> IO ()
-    appendFile,                       -- :: FilePath -> String -> IO ()
+    readFile,                  -- :: FilePath -> IO String
+    writeFile,                 -- :: FilePath -> String -> IO ()
+    appendFile,                -- :: FilePath -> String -> IO ()
 
     -- ** File locking
 
@@ -59,33 +70,33 @@ module System.IO (
 
     -- ** Determining and changing the size of a file
 
-    hFileSize,                -- :: Handle -> IO Integer
+    hFileSize,                 -- :: Handle -> IO Integer
 #ifdef __GLASGOW_HASKELL__
     hSetFileSize,              -- :: Handle -> Integer -> IO ()
 #endif
 
     -- ** Detecting the end of input
 
-    hIsEOF,                   -- :: Handle -> IO Bool
-    isEOF,                    -- :: IO Bool
+    hIsEOF,                    -- :: Handle -> IO Bool
+    isEOF,                     -- :: IO Bool
 
     -- ** Buffering operations
 
     BufferMode(NoBuffering,LineBuffering,BlockBuffering),
-    hSetBuffering,            -- :: Handle -> BufferMode -> IO ()
-    hGetBuffering,            -- :: Handle -> IO BufferMode
-    hFlush,                   -- :: Handle -> IO ()
+    hSetBuffering,             -- :: Handle -> BufferMode -> IO ()
+    hGetBuffering,             -- :: Handle -> IO BufferMode
+    hFlush,                    -- :: Handle -> IO ()
 
     -- ** Repositioning handles
 
-    hGetPosn,                 -- :: Handle -> IO HandlePosn
-    hSetPosn,                 -- :: HandlePosn -> IO ()
+    hGetPosn,                  -- :: Handle -> IO HandlePosn
+    hSetPosn,                  -- :: HandlePosn -> IO ()
     HandlePosn,                -- abstract, instance of: Eq, Show.
 
-    hSeek,                    -- :: Handle -> SeekMode -> Integer -> IO ()
+    hSeek,                     -- :: Handle -> SeekMode -> Integer -> IO ()
     SeekMode(AbsoluteSeek,RelativeSeek,SeekFromEnd),
 #if !defined(__NHC__)
-    hTell,                    -- :: Handle -> IO Integer
+    hTell,                     -- :: Handle -> IO Integer
 #endif
 
     -- ** Handle properties
@@ -94,83 +105,158 @@ module System.IO (
     hIsReadable, hIsWritable,  -- :: Handle -> IO Bool
     hIsSeekable,               -- :: Handle -> IO Bool
 
-    -- ** Terminal operations
+    -- ** Terminal operations (not portable: GHC\/Hugs only)
 
 #if !defined(__NHC__)
-    hIsTerminalDevice,         -- :: Handle -> IO Bool
+    hIsTerminalDevice,          -- :: Handle -> IO Bool
 
-    hSetEcho,                  -- :: Handle -> Bool -> IO ()
-    hGetEcho,                  -- :: Handle -> IO Bool
+    hSetEcho,                   -- :: Handle -> Bool -> IO ()
+    hGetEcho,                   -- :: Handle -> IO Bool
 #endif
 
-    -- ** Showing handle state
+    -- ** Showing handle state (not portable: GHC only)
 
 #ifdef __GLASGOW_HASKELL__
-    hShow,                     -- :: Handle -> IO String
+    hShow,                      -- :: Handle -> IO String
 #endif
 
     -- * Text input and output
 
     -- ** Text input
 
-    hWaitForInput,            -- :: Handle -> Int -> IO Bool
-    hReady,                   -- :: Handle -> IO Bool
-    hGetChar,                 -- :: Handle -> IO Char
-    hGetLine,                 -- :: Handle -> IO [Char]
-    hLookAhead,                       -- :: Handle -> IO Char
-    hGetContents,             -- :: Handle -> IO [Char]
+    hWaitForInput,             -- :: Handle -> Int -> IO Bool
+    hReady,                    -- :: Handle -> IO Bool
+    hGetChar,                  -- :: Handle -> IO Char
+    hGetLine,                  -- :: Handle -> IO [Char]
+    hLookAhead,                -- :: Handle -> IO Char
+    hGetContents,              -- :: Handle -> IO [Char]
 
     -- ** Text output
 
-    hPutChar,                 -- :: Handle -> Char -> IO ()
-    hPutStr,                  -- :: Handle -> [Char] -> IO ()
-    hPutStrLn,                -- :: Handle -> [Char] -> IO ()
-    hPrint,                   -- :: Show a => Handle -> a -> IO ()
+    hPutChar,                  -- :: Handle -> Char -> IO ()
+    hPutStr,                   -- :: Handle -> [Char] -> IO ()
+    hPutStrLn,                 -- :: Handle -> [Char] -> IO ()
+    hPrint,                    -- :: Show a => Handle -> a -> IO ()
 
     -- ** Special cases for standard input and output
 
     -- | These functions are also exported by the "Prelude".
 
-    interact,                 -- :: (String -> String) -> IO ()
-    putChar,                  -- :: Char   -> IO ()
-    putStr,                   -- :: String -> IO () 
-    putStrLn,                 -- :: String -> IO ()
-    print,                    -- :: Show a => a -> IO ()
-    getChar,                  -- :: IO Char
-    getLine,                  -- :: IO String
-    getContents,              -- :: IO String
-    readIO,                   -- :: Read a => String -> IO a
-    readLn,                   -- :: Read a => IO a
+    interact,                  -- :: (String -> String) -> IO ()
+    putChar,                   -- :: Char   -> IO ()
+    putStr,                    -- :: String -> IO () 
+    putStrLn,                  -- :: String -> IO ()
+    print,                     -- :: Show a => a -> IO ()
+    getChar,                   -- :: IO Char
+    getLine,                   -- :: IO String
+    getContents,               -- :: IO String
+    readIO,                    -- :: Read a => String -> IO a
+    readLn,                    -- :: Read a => IO a
 
     -- * Binary input and output
 
-    openBinaryFile,           -- :: FilePath -> IOMode -> IO Handle
-    hSetBinaryMode,           -- :: Handle -> Bool -> IO ()
-#if !defined(__NHC__)
-    hPutBuf,                  -- :: Handle -> Ptr a -> Int -> IO ()
-    hGetBuf,                  -- :: Handle -> Ptr a -> Int -> IO Int
-#endif
+    withBinaryFile,
+    openBinaryFile,            -- :: FilePath -> IOMode -> IO Handle
+    hSetBinaryMode,            -- :: Handle -> Bool -> IO ()
+    hPutBuf,                   -- :: Handle -> Ptr a -> Int -> IO ()
+    hGetBuf,                   -- :: Handle -> Ptr a -> Int -> IO Int
 #if !defined(__NHC__) && !defined(__HUGS__)
-    hPutBufNonBlocking,               -- :: Handle -> Ptr a -> Int -> IO Int
-    hGetBufNonBlocking,               -- :: Handle -> Ptr a -> Int -> IO Int
+    hGetBufSome,               -- :: Handle -> Ptr a -> Int -> IO Int
+    hPutBufNonBlocking,        -- :: Handle -> Ptr a -> Int -> IO Int
+    hGetBufNonBlocking,        -- :: Handle -> Ptr a -> Int -> IO Int
 #endif
 
     -- * Temporary files
 
-#ifdef __GLASGOW_HASKELL__
     openTempFile,
     openBinaryTempFile,
+    openTempFileWithDefaultPermissions,
+    openBinaryTempFileWithDefaultPermissions,
+
+#if !defined(__NHC__) && !defined(__HUGS__)
+    -- * Unicode encoding\/decoding
+
+    -- | A text-mode 'Handle' has an associated 'TextEncoding', which
+    -- is used to decode bytes into Unicode characters when reading,
+    -- and encode Unicode characters into bytes when writing.
+    --
+    -- The default 'TextEncoding' is the same as the default encoding
+    -- on your system, which is also available as 'localeEncoding'.
+    -- (GHC note: on Windows, we currently do not support double-byte
+    -- encodings; if the console\'s code page is unsupported, then
+    -- 'localeEncoding' will be 'latin1'.)
+    --
+    -- Encoding and decoding errors are always detected and reported,
+    -- except during lazy I/O ('hGetContents', 'getContents', and
+    -- 'readFile'), where a decoding error merely results in
+    -- termination of the character stream, as with other I/O errors.
+
+    hSetEncoding, 
+    hGetEncoding,
+
+    -- ** Unicode encodings
+    TextEncoding, 
+    latin1,
+    utf8, utf8_bom,
+    utf16, utf16le, utf16be,
+    utf32, utf32le, utf32be, 
+    localeEncoding,
+    char8,
+    mkTextEncoding,
+#endif
+
+#if !defined(__NHC__) && !defined(__HUGS__)
+    -- * Newline conversion
+    
+    -- | In Haskell, a newline is always represented by the character
+    -- '\n'.  However, in files and external character streams, a
+    -- newline may be represented by another character sequence, such
+    -- as '\r\n'.
+    --
+    -- A text-mode 'Handle' has an associated 'NewlineMode' that
+    -- specifies how to transate newline characters.  The
+    -- 'NewlineMode' specifies the input and output translation
+    -- separately, so that for instance you can translate '\r\n'
+    -- to '\n' on input, but leave newlines as '\n' on output.
+    --
+    -- The default 'NewlineMode' for a 'Handle' is
+    -- 'nativeNewlineMode', which does no translation on Unix systems,
+    -- but translates '\r\n' to '\n' and back on Windows.
+    --
+    -- Binary-mode 'Handle's do no newline translation at all.
+    --
+    hSetNewlineMode, 
+    Newline(..), nativeNewline, 
+    NewlineMode(..), 
+    noNewlineTranslation, universalNewlineMode, nativeNewlineMode,
 #endif
   ) where
 
+import Control.Exception.Base
+
+#ifndef __NHC__
+import Data.Bits
+import Data.List
+import Data.Maybe
+import Foreign.C.Error
+import Foreign.C.Types
+import System.Posix.Internals
+import System.Posix.Types
+#endif
+
 #ifdef __GLASGOW_HASKELL__
 import GHC.Base
-import GHC.IOBase      -- Together these four Prelude modules define
-import GHC.Handle      -- all the stuff exported by IO for the GHC version
-import GHC.IO
-import GHC.Exception
+import GHC.IO hiding ( bracket, onException )
+import GHC.IO.IOMode
+import GHC.IO.Handle.FD
+import qualified GHC.IO.FD as FD
+import GHC.IO.Handle
+import GHC.IO.Handle.Text ( hGetBufSome, hPutStrLn )
+import GHC.IORef
+import GHC.IO.Exception ( userError )
+import GHC.IO.Encoding
 import GHC.Num
-import GHC.Read
+import Text.Read
 import GHC.Show
 #endif
 
@@ -178,8 +264,7 @@ import GHC.Show
 import Hugs.IO
 import Hugs.IOExts
 import Hugs.IORef
-import Hugs.Prelude    ( throw, Exception(NonTermination) )
-import System.IO.Unsafe        ( unsafeInterleaveIO )
+import System.IO.Unsafe ( unsafeInterleaveIO )
 #endif
 
 #ifdef __NHC__
@@ -214,11 +299,13 @@ import IO
   , hIsOpen, hIsClosed        -- :: Handle -> IO Bool
   , hIsReadable, hIsWritable  -- :: Handle -> IO Bool
   , hIsSeekable               -- :: Handle -> IO Bool
+  , bracket
 
   , IO ()
   , FilePath                  -- :: String
   )
-import NHC.IOExtras (fixIO)
+import NHC.IOExtras (fixIO, hPutBuf, hGetBuf)
+import NHC.FFI (Ptr)
 #endif
 
 -- -----------------------------------------------------------------------------
@@ -240,8 +327,7 @@ putStr s        =  hPutStr stdout s
 -- | The same as 'putStr', but adds a newline character.
 
 putStrLn        :: String -> IO ()
-putStrLn s      =  do putStr s
-                      putChar '\n'
+putStrLn s      =  hPutStrLn stdout s
 
 -- | The 'print' function outputs a value of any printable type to the
 -- standard output device.
@@ -290,13 +376,12 @@ interact f      =   do s <- getContents
 -- The file is read lazily, on demand, as with 'getContents'.
 
 readFile        :: FilePath -> IO String
-readFile name  =  openFile name ReadMode >>= hGetContents
+readFile name   =  openFile name ReadMode >>= hGetContents
 
 -- | The computation 'writeFile' @file str@ function writes the string @str@,
 -- to the file @file@.
 writeFile :: FilePath -> String -> IO ()
-writeFile f txt = bracket (openFile f WriteMode) hClose
-                         (\hdl -> hPutStr hdl txt) 
+writeFile f txt = withFile f WriteMode (\ hdl -> hPutStr hdl txt)
 
 -- | The computation 'appendFile' @file str@ function appends the string @str@,
 -- to the file @file@.
@@ -308,8 +393,7 @@ writeFile f txt = bracket (openFile f WriteMode) hClose
 -- > main = appendFile "squares" (show [(x,x*x) | x <- [0,0.1..2]])
 
 appendFile      :: FilePath -> String -> IO ()
-appendFile f txt = bracket (openFile f AppendMode) hClose
-                          (\hdl -> hPutStr hdl txt)
+appendFile f txt = withFile f AppendMode (\ hdl -> hPutStr hdl txt)
 
 -- | The 'readLn' function combines 'getLine' and 'readIO'.
 
@@ -323,11 +407,11 @@ readLn          =  do l <- getLine
 
 readIO          :: Read a => String -> IO a
 readIO s        =  case (do { (x,t) <- reads s ;
-                             ("","") <- lex t ;
+                              ("","") <- lex t ;
                               return x }) of
-                       [x]    -> return x
-                       []     -> ioError (userError "Prelude.readIO: no parse")
-                       _      -> ioError (userError "Prelude.readIO: ambiguous parse")
+                        [x]    -> return x
+                        []     -> ioError (userError "Prelude.readIO: no parse")
+                        _      -> ioError (userError "Prelude.readIO: ambiguous parse")
 #endif  /* __GLASGOW_HASKELL__ */
 
 #ifndef __NHC__
@@ -338,15 +422,8 @@ readIO s        =  case (do { (x,t) <- reads s ;
 --
 --  * 'System.IO.Error.isEOFError' if the end of file has been reached.
 
-hReady         :: Handle -> IO Bool
-hReady h       =  hWaitForInput h 0
-
--- | The same as 'hPutStr', but adds a newline character.
-
-hPutStrLn      :: Handle -> String -> IO ()
-hPutStrLn hndl str = do
- hPutStr  hndl str
- hPutChar hndl '\n'
+hReady          :: Handle -> IO Bool
+hReady h        =  hWaitForInput h 0
 
 -- | Computation 'hPrint' @hdl t@ writes the string representation of @t@
 -- given by the 'shows' function to the file or channel managed by @hdl@
@@ -358,10 +435,26 @@ hPutStrLn hndl str = do
 --
 --  * 'System.IO.Error.isPermissionError' if another system resource limit would be exceeded.
 
-hPrint         :: Show a => Handle -> a -> IO ()
-hPrint hdl     =  hPutStrLn hdl . show
+hPrint          :: Show a => Handle -> a -> IO ()
+hPrint hdl      =  hPutStrLn hdl . show
 #endif /* !__NHC__ */
 
+-- | @'withFile' name mode act@ opens a file using 'openFile' and passes
+-- the resulting handle to the computation @act@.  The handle will be
+-- closed on exit from 'withFile', whether by normal termination or by
+-- raising an exception.  If closing the handle raises an exception, then
+-- this exception will be raised by 'withFile' rather than any exception
+-- raised by 'act'.
+withFile :: FilePath -> IOMode -> (Handle -> IO r) -> IO r
+withFile name mode = bracket (openFile name mode) hClose
+
+-- | @'withBinaryFile' name mode act@ opens a file using 'openBinaryFile'
+-- and passes the resulting handle to the computation @act@.  The handle
+-- will be closed on exit from 'withBinaryFile', whether by normal
+-- termination or by raising an exception.
+withBinaryFile :: FilePath -> IOMode -> (Handle -> IO r) -> IO r
+withBinaryFile name mode = bracket (openBinaryFile name mode) hClose
+
 -- ---------------------------------------------------------------------------
 -- fixIO
 
@@ -383,13 +476,150 @@ fixIO k = do
 -- Assume a unix platform, where text and binary I/O are identical.
 openBinaryFile = openFile
 hSetBinaryMode _ _ = return ()
+
+type CMode = Int
+#endif
+
+-- | The function creates a temporary file in ReadWrite mode.
+-- The created file isn\'t deleted automatically, so you need to delete it manually.
+--
+-- The file is creates with permissions such that only the current
+-- user can read\/write it.
+--
+-- With some exceptions (see below), the file will be created securely
+-- in the sense that an attacker should not be able to cause
+-- openTempFile to overwrite another file on the filesystem using your
+-- credentials, by putting symbolic links (on Unix) in the place where
+-- the temporary file is to be created.  On Unix the @O_CREAT@ and
+-- @O_EXCL@ flags are used to prevent this attack, but note that
+-- @O_EXCL@ is sometimes not supported on NFS filesystems, so if you
+-- rely on this behaviour it is best to use local filesystems only.
+--
+openTempFile :: FilePath   -- ^ Directory in which to create the file
+             -> String     -- ^ File name template. If the template is \"foo.ext\" then
+                           -- the created file will be \"fooXXX.ext\" where XXX is some
+                           -- random number.
+             -> IO (FilePath, Handle)
+openTempFile tmp_dir template
+    = openTempFile' "openTempFile" tmp_dir template False 0o600
+
+-- | Like 'openTempFile', but opens the file in binary mode. See 'openBinaryFile' for more comments.
+openBinaryTempFile :: FilePath -> String -> IO (FilePath, Handle)
+openBinaryTempFile tmp_dir template
+    = openTempFile' "openBinaryTempFile" tmp_dir template True 0o600
+
+-- | Like 'openTempFile', but uses the default file permissions
+openTempFileWithDefaultPermissions :: FilePath -> String
+                                   -> IO (FilePath, Handle)
+openTempFileWithDefaultPermissions tmp_dir template
+    = openTempFile' "openBinaryTempFile" tmp_dir template False 0o666
+
+-- | Like 'openBinaryTempFile', but uses the default file permissions
+openBinaryTempFileWithDefaultPermissions :: FilePath -> String
+                                         -> IO (FilePath, Handle)
+openBinaryTempFileWithDefaultPermissions tmp_dir template
+    = openTempFile' "openBinaryTempFile" tmp_dir template True 0o666
+
+openTempFile' :: String -> FilePath -> String -> Bool -> CMode
+              -> IO (FilePath, Handle)
+openTempFile' loc tmp_dir template binary mode = do
+  pid <- c_getpid
+  findTempName pid
+  where
+    -- We split off the last extension, so we can use .foo.ext files
+    -- for temporary files (hidden on Unix OSes). Unfortunately we're
+    -- below filepath in the hierarchy here.
+    (prefix,suffix) =
+       case break (== '.') $ reverse template of
+         -- First case: template contains no '.'s. Just re-reverse it.
+         (rev_suffix, "")       -> (reverse rev_suffix, "")
+         -- Second case: template contains at least one '.'. Strip the
+         -- dot from the prefix and prepend it to the suffix (if we don't
+         -- do this, the unique number will get added after the '.' and
+         -- thus be part of the extension, which is wrong.)
+         (rev_suffix, '.':rest) -> (reverse rest, '.':reverse rev_suffix)
+         -- Otherwise, something is wrong, because (break (== '.')) should
+         -- always return a pair with either the empty string or a string
+         -- beginning with '.' as the second component.
+         _                      -> error "bug in System.IO.openTempFile"
+
+#ifndef __NHC__
+    oflags1 = rw_flags .|. o_EXCL
+
+    binary_flags
+      | binary    = o_BINARY
+      | otherwise = 0
+
+    oflags = oflags1 .|. binary_flags
+#endif
+
+#if defined(__NHC__)
+    findTempName x = do h <- openFile filepath ReadWriteMode
+                        return (filepath, h)
+#elif defined(__GLASGOW_HASKELL__)
+    findTempName x = do
+      fd <- withFilePath filepath $ \ f ->
+              c_open f oflags mode
+      if fd < 0
+       then do
+         errno <- getErrno
+         if errno == eEXIST
+           then findTempName (x+1)
+           else ioError (errnoToIOError loc errno Nothing (Just tmp_dir))
+       else do
+
+         (fD,fd_type) <- FD.mkFD fd ReadWriteMode Nothing{-no stat-}
+                              False{-is_socket-} 
+                              True{-is_nonblock-}
+
+         h <- mkHandleFromFD fD fd_type filepath ReadWriteMode False{-set non-block-}
+                           (Just localeEncoding)
+
+         return (filepath, h)
+#else
+         h <- fdToHandle fd `onException` c_close fd
+         return (filepath, h)
+#endif
+
+      where
+        filename        = prefix ++ show x ++ suffix
+        filepath        = tmp_dir `combine` filename
+
+        -- XXX bits copied from System.FilePath, since that's not available here
+        combine a b
+                  | null b = a
+                  | null a = b
+                  | last a == pathSeparator = a ++ b
+                  | otherwise = a ++ [pathSeparator] ++ b
+
+#if __HUGS__
+        fdToHandle fd   = openFd (fromIntegral fd) False ReadWriteMode binary
+#endif
+
+-- XXX Should use filepath library
+pathSeparator :: Char
+#ifdef mingw32_HOST_OS
+pathSeparator = '\\'
+#else
+pathSeparator = '/'
+#endif
+
+#ifndef __NHC__
+-- XXX Copied from GHC.Handle
+std_flags, output_flags, rw_flags :: CInt
+std_flags    = o_NONBLOCK   .|. o_NOCTTY
+output_flags = std_flags    .|. o_CREAT
+rw_flags     = output_flags .|. o_RDWR
+#endif
+
+#ifdef __NHC__
+foreign import ccall "getpid" c_getpid :: IO Int
 #endif
 
 -- $locking
 -- Implementations should enforce as far as possible, at least locally to the
 -- Haskell process, multiple-reader single-writer locking on files.
--- That is, /there may either be many handles on the same file which manage
--- input, or just one handle on the file which manages output/.  If any
+-- That is, /there may either be many handles on the same file which manage input, or just one handle on the file which manages output/.  If any
 -- open or semi-closed handle is managing a file for output, no new
 -- handle can be allocated for that file.  If any open or semi-closed
 -- handle is managing a file for input, new handles can only be allocated
@@ -403,22 +633,3 @@ hSetBinaryMode _ _ = return ()
 -- It follows that an attempt to write to a file (using 'writeFile', for
 -- example) that was earlier opened by 'readFile' will usually result in
 -- failure with 'System.IO.Error.isAlreadyInUseError'.
-
--- -----------------------------------------------------------------------------
--- Utils
-
--- Copied here to avoid recursive dependency with Control.Exception
-bracket 
-       :: IO a         -- ^ computation to run first (\"acquire resource\")
-       -> (a -> IO b)  -- ^ computation to run last (\"release resource\")
-       -> (a -> IO c)  -- ^ computation to run in-between
-       -> IO c         -- returns the value from the in-between computation
-bracket before after thing =
-  block (do
-    a <- before 
-    r <- catchException
-          (unblock (thing a))
-          (\e -> do { after a; throw e })
-    after a
-    return r
- )