System.IO.latin1 docs
Bas van Dijk
v.dijk.bas at gmail.com
Tue Jan 4 19:57:46 CET 2011
On Tue, Jan 4, 2011 at 4:27 PM, Ross Paterson <ross at soi.city.ac.uk> wrote:
> On Tue, Jan 04, 2011 at 04:03:34PM +0100, Henning Thielemann wrote:
>> Simon Marlow schrieb:
>> > Good plan. I'll make a proposal to add System.IO.binary. A different
>> > type for binary handles is the right thing, but it's a larger
>> > undertaking so I don't plan to attack it right now (someone else is
>> > welcome to do so).
>>
>> Isn't this also the purpose of the safer-file-handles package?
>>
>> http://hackage.haskell.org/package/safer-file-handles
>
> No, that puts the IOMode and region in the type, not the binary mode.
Indeed. However, I would be glad to add such a safety feature if we
can distill a nice API.
What would such an API look like?
One approach might be something like this: (not type-checked, not even
parsed...)
-- Types
newtype TextHandle = ...
newtype ByteHandle = ...
-- Opening
openFile :: FilePath -> IOMode -> IO TextHandle
openBinaryFile :: FilePath -> IOMode -> IO ByteHandle
-- Text input/output
hGetLine :: TextHandle -> IO String
hPutStrLn :: TextHandle -> String -> IO ()
...
-- Binary input/output
hGetBuf :: ByteHandle -> Ptr a -> Int -> IO Int
hPutBuf :: ByteHandle -> Ptr a -> Int -> IO ()
...
-- General operations on handles (text/binary)
class Handle h where
hClose :: h -> IO ()
hIsEOF :: h -> IO Bool
hSetBuffering :: h -> BufferMode -> IO ()
...
instance Handle TextHandle where ...
instance Handle ByteHandle where ...
The disadvantage of this approach is that all general operations on
handles (that should both work for Text- and ByteHandles) need to be
put in a class. A way to solve this is to have a single Handle type
which is parameterized by a phantom type that represents the Text/Byte
mode: (I also use this style to encode the IOMode of Handles in
safer-file-handles).
{-# LANGUAGE EmptyDataDecls #-}
newtype Handle mode = ...
data Text
data Byte
type TextHandle = Handle Text
type ByteHandle = Handle Byte
The types of the open functions and the types of the text I/O and byte
I/O functions remain the same. The types of the general operations
will change to:
hClose :: Handle mode -> IO ()
hIsEOF :: Handle mode -> IO Bool
hSetBuffering :: Handle mode -> BufferMode -> IO ()
...
Note that these are now polymorphic in the text/byte mode.
In both these approaches the following questions remain:
* What about the standard handles? What are their types?
Maybe we need stdinText :: TextHandle, stdinBytes :: BytesHandle, etc..
But this will make it more difficult to use them at the same time.
* What about hSetBinaryMode :: Handle -> Bool -> IO () ?
Should we remove it from such an API.
What are your thoughts on this?
Regards,
Bas
More information about the Libraries
mailing list