Skip to content
Snippets Groups Projects
Commit 880cb6cd authored by Ian Lynagh's avatar Ian Lynagh
Browse files

open(Binary)TempFile is now portable

parent 9e674b44
No related branches found
No related tags found
No related merge requests found
...@@ -157,10 +157,8 @@ module System.IO ( ...@@ -157,10 +157,8 @@ module System.IO (
-- * Temporary files (not portable: GHC only) -- * Temporary files (not portable: GHC only)
#ifdef __GLASGOW_HASKELL__
openTempFile, openTempFile,
openBinaryTempFile, openBinaryTempFile,
#endif
) where ) where
import Data.Bits import Data.Bits
...@@ -170,6 +168,13 @@ import Foreign.C.Error ...@@ -170,6 +168,13 @@ import Foreign.C.Error
import Foreign.C.String import Foreign.C.String
import System.Posix.Internals import System.Posix.Internals
#ifdef __GLASGOW_HASKELL__
import GHC.Exception as ExceptionBase hiding (catch)
#endif
#ifdef __HUGS__
import Hugs.Exception as ExceptionBase
#endif
#ifdef __GLASGOW_HASKELL__ #ifdef __GLASGOW_HASKELL__
import GHC.Base import GHC.Base
import GHC.IOBase -- Together these four Prelude modules define import GHC.IOBase -- Together these four Prelude modules define
...@@ -450,8 +455,11 @@ openTempFile' loc tmp_dir template binary = do ...@@ -450,8 +455,11 @@ openTempFile' loc tmp_dir template binary = do
then findTempName (x+1) then findTempName (x+1)
else ioError (errnoToIOError loc errno Nothing (Just tmp_dir)) else ioError (errnoToIOError loc errno Nothing (Just tmp_dir))
else do else do
h <- fdToHandle' fd Nothing False filepath ReadWriteMode True -- XXX We want to tell fdToHandle what the filepath is,
`catchException` \e -> do c_close fd; throw e -- 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) return (filepath, h)
where where
filename = prefix ++ show x ++ suffix filename = prefix ++ show x ++ suffix
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment