[project @ 2001-08-04 06:11:24 by ken]
[ghc-hetmet.git] / ghc / lib / std / PrelHandle.hsc
index 8f5e4bd..5862141 100644 (file)
@@ -4,7 +4,7 @@
 #undef DEBUG
 
 -- -----------------------------------------------------------------------------
--- $Id: PrelHandle.hsc,v 1.8 2001/06/01 13:06:01 sewardj Exp $
+-- $Id: PrelHandle.hsc,v 1.15 2001/07/13 15:01:28 simonmar Exp $
 --
 -- (c) The University of Glasgow, 1994-2001
 --
@@ -22,9 +22,11 @@ module PrelHandle (
 
   stdin, stdout, stderr,
   IOMode(..), IOModeEx(..), openFile, openFileEx, openFd,
-  hClose, hFileSize, hIsEOF, isEOF, hLookAhead, hSetBuffering, hSetBinaryMode,
+  hFileSize, hIsEOF, isEOF, hLookAhead, hSetBuffering, hSetBinaryMode,
   hFlush, 
 
+  hClose, hClose_help,
+
   HandlePosn(..), hGetPosn, hSetPosn,
   SeekMode(..), hSeek,
 
@@ -81,6 +83,15 @@ import PrelConc
 dEFAULT_OPEN_IN_BINARY_MODE :: Bool
 dEFAULT_OPEN_IN_BINARY_MODE = False
 
+-- Is seeking on text-mode handles allowed, or not?
+tEXT_MODE_SEEK_ALLOWED :: Bool
+#if defined(mingw32_TARGET_OS)
+tEXT_MODE_SEEK_ALLOWED = False
+#else
+tEXT_MODE_SEEK_ALLOWED = True
+#endif
+
+
 -- ---------------------------------------------------------------------------
 -- Creating a new handle
 
@@ -118,9 +129,7 @@ but we might want to revisit this in the future --SDM ].
 {-# INLINE withHandle #-}
 withHandle :: String -> Handle -> (Handle__ -> IO (Handle__,a)) -> IO a
 withHandle fun h@(FileHandle m)     act = withHandle' fun h m act
-withHandle fun h@(DuplexHandle r w) act = do 
-  withHandle' fun h r act
-  withHandle' fun h w act
+withHandle fun h@(DuplexHandle m _) act = withHandle' fun h m act
 
 withHandle' fun h m act = 
    block $ do
@@ -249,8 +258,8 @@ checkSeekableHandle act handle_ =
       ClosedHandle     -> ioe_closedHandle
       SemiClosedHandle -> ioe_closedHandle
       AppendHandle      -> ioe_notSeekable
-      _                 | haIsBin handle_ -> act handle_
-                        | otherwise       -> ioe_notSeekable_notBin
+      _  | haIsBin handle_ || tEXT_MODE_SEEK_ALLOWED -> act handle_
+         | otherwise                                 -> ioe_notSeekable_notBin
 
 -- -----------------------------------------------------------------------------
 -- Handy IOErrors
@@ -275,7 +284,8 @@ ioe_notSeekable = ioException
        "handle is not seekable" Nothing)
 ioe_notSeekable_notBin = ioException 
    (IOError Nothing IllegalOperation ""
-       "seek operations are only allowed on binary-mode handles" Nothing)
+       "seek operations on text-mode handles are not allowed on this platform" 
+        Nothing)
 
 ioe_bufsiz :: Int -> IO a
 ioe_bufsiz n = ioException 
@@ -616,6 +626,9 @@ openFile' filepath ex_mode =
                  ReadWriteMode -> rw_flags    
                  AppendMode    -> append_flags
 
+      truncate | WriteMode <- mode = True
+              | otherwise         = False
+
       binary_flags
 #ifdef HAVE_O_BINARY
          | binary    = o_BINARY
@@ -634,21 +647,24 @@ openFile' filepath ex_mode =
              throwErrnoIfMinus1Retry "openFile"
                (c_open f (fromIntegral oflags) 0o666)
 
-    openFd fd filepath mode binary
+    openFd fd filepath mode binary truncate
+       -- ASSERT: if we just created the file, then openFd won't fail
+       -- (so we don't need to worry about removing the newly created file
+       --  in the event of an error).
 
 
 std_flags    = o_NONBLOCK   .|. o_NOCTTY
 output_flags = std_flags    .|. o_CREAT
 read_flags   = std_flags    .|. o_RDONLY 
-write_flags  = output_flags .|. o_WRONLY .|. o_TRUNC
+write_flags  = output_flags .|. o_WRONLY
 rw_flags     = output_flags .|. o_RDWR
-append_flags = output_flags .|. o_WRONLY .|. o_APPEND
+append_flags = write_flags  .|. o_APPEND
 
 -- ---------------------------------------------------------------------------
 -- openFd
 
-openFd :: FD -> FilePath -> IOMode -> Bool -> IO Handle
-openFd fd filepath mode binary = do
+openFd :: FD -> FilePath -> IOMode -> Bool -> Bool -> IO Handle
+openFd fd filepath mode binary truncate = do
     -- turn on non-blocking mode
     setNonBlockingFD fd
 
@@ -677,6 +693,10 @@ openFd fd filepath mode binary = do
           when (r == -1)  $
                ioException (IOError Nothing ResourceBusy "openFile"
                                   "file is locked" Nothing)
+
+          -- truncate the file if necessary
+          when truncate (fileTruncate filepath)
+
           mkFileHandle fd filepath ha_type binary
 
 
@@ -754,8 +774,9 @@ hClose h@(DuplexHandle r w) = do
                  haType = ClosedHandle
                 }
 
-hClose' h m =
-  withHandle__' "hClose" h m $ \ handle_ -> do
+hClose' h m = withHandle__' "hClose" h m $ hClose_help
+
+hClose_help handle_ =
   case haType handle_ of 
       ClosedHandle -> return handle_
       _ -> do
@@ -1111,7 +1132,8 @@ hIsSeekable handle =
       SemiClosedHandle            -> ioe_closedHandle
       AppendHandle        -> return False
       _                    -> do t <- fdType (haFD handle_)
-                                return (t == RegularFile && haIsBin handle_)
+                                return (t == RegularFile
+                                         && (haIsBin handle_ || tEXT_MODE_SEEK_ALLOWED))
 
 -- -----------------------------------------------------------------------------
 -- Changing echo status
@@ -1152,19 +1174,19 @@ hIsTerminalDevice handle = do
 -- hSetBinaryMode
 
 #ifdef _WIN32
-hSetBinaryMode handle bin = 
-  withHandle "hSetBinaryMode" handle $ \ handle_ ->
+hSetBinaryMode handle bin =
+  withAllHandles__ "hSetBinaryMode" handle $ \ handle_ ->
     do let flg | bin       = (#const O_BINARY)
               | otherwise = (#const O_TEXT)
        throwErrnoIfMinus1_ "hSetBinaryMode"
           (setmode (fromIntegral (haFD handle_)) flg)
-       return (handle_{haIsBin=bin}, ())
+       return handle_{haIsBin=bin}
 
 foreign import "setmode" setmode :: CInt -> CInt -> IO CInt
 #else
 hSetBinaryMode handle bin =
-  withHandle "hSetBinaryMode" handle $ \ handle_ ->
-    return (handle_{haIsBin=bin}, ())
+  withAllHandles__ "hSetBinaryMode" handle $ \ handle_ ->
+    return handle_{haIsBin=bin}
 #endif
 
 -- -----------------------------------------------------------------------------