Skip to content
Snippets Groups Projects
Commit 74cd7228 authored by sof's avatar sof
Browse files

[project @ 1998-03-12 08:56:24 by sof]

Added IOExts.openFileEx + IOExts.IOModeEx
parent aa4f16de
No related merge requests found
......@@ -183,6 +183,10 @@ described in <cite id="ImperativeFP">
References (aka mutable variables) and mutable arrays (but no form of
mutable byte arrays)
<item>
<tt/openFileEx/ extends the standard <tr/openFile/ action with support
for opening binary files.
<item>
<tt/performGC/ triggers an immediate garbage collection
......@@ -248,6 +252,12 @@ writeIOArray :: Ix ix => IOArray ix elt -> ix -> elt -> IO ()
freezeIOArray :: Ix ix => IOArray ix elt -> IO (Array ix elt)
instance Eq (IOArray ix elt)
openFileEx :: FilePath -> IOModeEx -> IO Handle
data IOModeEx = BinaryMode IO.IOMode | TextMode IO.IOMode
instance Eq IOModeEx
instance Read IOModeEx
instance Show IOModeEx
performGC :: IO ()
trace :: String -> a -> a
unsafePtrEq :: a -> a -> Bool
......
......@@ -25,6 +25,9 @@ module IOExts
, readIOArray
, writeIOArray
, freezeIOArray
, openFileEx
, IOModeEx(..)
, trace
, performGC
......@@ -36,6 +39,7 @@ module IOExts
\begin{code}
import PrelBase
import PrelIOBase
import PrelHandle ( openFileEx, IOModeEx(..) )
import PrelST
import PrelUnsafe
import PrelArr
......@@ -84,3 +88,4 @@ writeIOArray (IOArray arr) ix elt = stToIO (writeArray arr ix elt)
freezeIOArray (IOArray arr) = stToIO (freezeArray arr)
\end{code}
......@@ -186,9 +186,17 @@ stderr = unsafePerformIO (do
data IOMode = ReadMode | WriteMode | AppendMode | ReadWriteMode
deriving (Eq, Ord, Ix, Enum, Read, Show)
data IOModeEx
= BinaryMode IOMode
| TextMode IOMode
deriving (Eq, Read, Show)
openFile :: FilePath -> IOMode -> IO Handle
openFile fp im = openFileEx fp (TextMode im)
openFileEx :: FilePath -> IOModeEx -> IO Handle
openFile f m = do
openFileEx f m = do
ptr <- _ccall_ openFile f m'
if ptr /= ``NULL'' then do
#ifndef __PARALLEL_HASKELL__
......@@ -208,13 +216,22 @@ openFile f m = do
_ -> ioError
fail improved_error
where
imo = case m of
BinaryMode imo -> imo
TextMode imo -> imo
m' = case m of
BinaryMode _ -> imo' ++ "b"
TextMode imo -> imo'
imo' =
case imo of
ReadMode -> "r"
WriteMode -> "w"
AppendMode -> "a"
ReadWriteMode -> "r+"
htype = case m of
htype = case imo of
ReadMode -> ReadHandle
WriteMode -> WriteHandle
AppendMode -> AppendHandle
......
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