Add some more C wrappers; patch from Krister Walfridsson
[ghc-base.git] / System / IO.hs
index a887d99..47e9213 100644 (file)
@@ -1,4 +1,4 @@
-{-# OPTIONS_GHC -fno-implicit-prelude #-}
+{-# OPTIONS_GHC -XNoImplicitPrelude #-}
 -----------------------------------------------------------------------------
 -- |
 -- 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.
 
     -- ** Standard handles
 
@@ -37,20 +37,20 @@ module System.IO (
     -- ** Opening files
 
     withFile,
-    openFile,                 -- :: FilePath -> IOMode -> IO Handle
+    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
 
@@ -60,33 +60,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
@@ -98,95 +98,148 @@ module System.IO (
     -- ** 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 (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
 
     withBinaryFile,
-    openBinaryFile,           -- :: FilePath -> IOMode -> IO Handle
-    hSetBinaryMode,           -- :: Handle -> Bool -> IO ()
-    hPutBuf,                  -- :: Handle -> Ptr a -> Int -> IO ()
-    hGetBuf,                  -- :: Handle -> Ptr a -> Int -> IO Int
+    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
+    hPutBufNonBlocking,        -- :: Handle -> Ptr a -> Int -> IO Int
+    hGetBufNonBlocking,        -- :: Handle -> Ptr a -> Int -> IO Int
 #endif
 
-    -- * Temporary files (not portable: GHC\/Hugs only)
+    -- * Temporary files
 
-#if !defined(__NHC__)
     openTempFile,
     openBinaryTempFile,
+
+#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, currently 'localeEncoding' is always
+    -- 'latin1'; there is no support for encoding and decoding using
+    -- the ANSI code page).
+    --
+    -- 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,
+    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.String
+import Foreign.C.Types
 import System.Posix.Internals
 #endif
 
 #ifdef __GLASGOW_HASKELL__
-import GHC.Exception    as ExceptionBase hiding (catch)
-#endif
-#ifdef __HUGS__
-import Hugs.Exception   as ExceptionBase
-#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 ( onException )
+import GHC.IO.IOMode
+import GHC.IO.Handle.FD
+import GHC.IO.Handle
+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
 
@@ -194,9 +247,7 @@ import GHC.Show
 import Hugs.IO
 import Hugs.IOExts
 import Hugs.IORef
-import Hugs.Prelude    ( throw, Exception(NonTermination) )
-import Control.Exception ( bracket )
-import System.IO.Unsafe        ( unsafeInterleaveIO )
+import System.IO.Unsafe ( unsafeInterleaveIO )
 #endif
 
 #ifdef __NHC__
@@ -309,7 +360,7 @@ 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@.
@@ -340,11 +391,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__
@@ -355,12 +406,12 @@ 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
+hReady          :: Handle -> IO Bool
+hReady h        =  hWaitForInput h 0
 
 -- | The same as 'hPutStr', but adds a newline character.
 
-hPutStrLn      :: Handle -> String -> IO ()
+hPutStrLn       :: Handle -> String -> IO ()
 hPutStrLn hndl str = do
  hPutStr  hndl str
  hPutChar hndl '\n'
@@ -375,8 +426,8 @@ 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
@@ -416,12 +467,11 @@ openBinaryFile = openFile
 hSetBinaryMode _ _ = return ()
 #endif
 
-#ifndef __NHC__
 -- | 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.
+-- 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
@@ -451,7 +501,7 @@ openTempFile' loc tmp_dir template binary = do
     -- 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) = 
+    (prefix,suffix) =
        case break (== '.') $ reverse template of
          -- First case: template contains no '.'s. Just re-reverse it.
          (rev_suffix, "")       -> (reverse rev_suffix, "")
@@ -465,6 +515,7 @@ openTempFile' loc tmp_dir template binary = do
          -- beginning with '.' as the second component.
          _                      -> error "bug in System.IO.openTempFile"
 
+#ifndef __NHC__
     oflags1 = rw_flags .|. o_EXCL
 
     binary_flags
@@ -472,11 +523,16 @@ openTempFile' loc tmp_dir template binary = do
       | otherwise = 0
 
     oflags = oflags1 .|. binary_flags
+#endif
 
+#ifdef __NHC__
+    findTempName x = do h <- openFile filepath ReadWriteMode
+                        return (filepath, h)
+#else
     findTempName x = do
-      fd <- withCString filepath $ \ f ->
+      fd <- withFilePath filepath $ \ f ->
               c_open f oflags 0o600
-      if fd < 0 
+      if fd < 0
        then do
          errno <- getErrno
          if errno == eEXIST
@@ -486,9 +542,9 @@ openTempFile' loc tmp_dir template binary = do
          -- XXX We want to tell fdToHandle what the filepath is,
          -- as any exceptions etc will only be able to report the
          -- fd currently
-         h <- fdToHandle fd
-               `ExceptionBase.catchException` \e -> do c_close fd; throw e
-        return (filepath, h)
+         h <- fdToHandle fd `onException` c_close fd
+         return (filepath, h)
+#endif
       where
         filename        = prefix ++ show x ++ suffix
         filepath        = tmp_dir `combine` filename
@@ -512,13 +568,16 @@ pathSeparator = '\\'
 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
-read_flags   = std_flags    .|. o_RDONLY
-write_flags  = output_flags .|. o_WRONLY
 rw_flags     = output_flags .|. o_RDWR
-append_flags = write_flags  .|. o_APPEND
+#endif
+
+#ifdef __NHC__
+foreign import ccall "getpid" c_getpid :: IO Int
 #endif
 
 -- $locking
@@ -539,24 +598,3 @@ append_flags = write_flags  .|. o_APPEND
 -- 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
-
-#ifdef __GLASGOW_HASKELL__
--- 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
- )
-#endif