Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
System.IO.StringLike.Impl
Description
The classes in this library roughly encapulates things you can read or write through a "handle", typically writing something "string like" to a file, but the interface is very flexible.
Currently only String
, ByteString
and Text
in their strict/lazy varieties
and builders are implemented.
However, the interface has the flexibility to write non-character data.
For example an implementation for a [Int]
could just write all the Int
s in
binary to the file and read them back into a [Int]
.
Also the interface can be defined for "handles" other than standard files.
Currently the only such instance that does not use Handle
is for hGetContents
,
where one can call directly:
hGetContents fileName
In this case, "handle" is a FilePath
.
The initial motivation of to avoid having to change all your function calls if you change your string type, but it's actually more general than that now.
The point of this library is to be able to read and write raw data to the disk (and perhaps other places) quickly without thinking too much about it.
It's not intended to be a replacement for say Binary
. It's intended to be lower
level. Binary
internally creates lazy bytestrings for the user to write to the
disk, this library is instead just about directly writing raw data.
Note that we currently only have classes for
Most of the functions should be fairly self explanatory having the same meaning as in Prelude or System.IO but more general.
- type CanGetContents t = CanGetContentsClass IO Handle t
- class Monad m => CanGetContentsClass m handleT t where
- getContents :: CanGetContents t => IO t
- readFile :: CanGetContents t => FilePath -> IO t
- type CanGetLine t = CanGetLineClass IO Handle t
- class CanGetContentsClass m handleT t => CanGetLineClass m handleT t where
- getLine :: CanGetLine t => IO t
- type CanPutStr t = CanPutStrClass IO Handle t
- class Monad m => CanPutStrClass m handleT t where
- putStr :: CanPutStr t => t -> IO ()
- writeFile :: CanPutStr t => FilePath -> t -> IO ()
- appendFile :: CanPutStr t => FilePath -> t -> IO ()
- interact :: (CanGetContents t, CanPutStr t) => (t -> t) -> IO ()
- type CanPutStrLn t = CanPutStrLnClass IO Handle t
- class CanPutStrClass m handleT t => CanPutStrLnClass m handleT t where
- putStrLn :: CanPutStrLn t => t -> IO ()
- type family CanProxyT t
- class CanProxyTo t where
- class CanProxyFrom t where
Documentation
type CanGetContents t = CanGetContentsClass IO Handle t Source #
class Monad m => CanGetContentsClass m handleT t where Source #
Methods
hGetContents :: handleT -> m t Source #
Generalised hGetContents
hGetContents :: (CanProxyFrom t, CanGetContentsClass m handleT (CanProxyT t)) => handleT -> m t Source #
Generalised hGetContents
Instances
(Monad m, CanGetContentsClass m Handle Text) => CanGetContentsClass m Handle Builder Source # | |
(~) (* -> *) m IO => CanGetContentsClass m Handle Text Source # | |
(~) (* -> *) m IO => CanGetContentsClass m Handle Text Source # | |
(Monad m, CanGetContentsClass m Handle ByteString) => CanGetContentsClass m Handle Builder Source # | |
(~) (* -> *) m IO => CanGetContentsClass m Handle ByteString Source # | |
(~) (* -> *) m IO => CanGetContentsClass m Handle ByteString Source # | |
(~) (* -> *) m IO => CanGetContentsClass m Handle String Source # | |
((~) (* -> *) m IO, CanGetContentsClass m Handle t) => CanGetContentsClass m FilePath t Source # | |
getContents :: CanGetContents t => IO t Source #
type CanGetLine t = CanGetLineClass IO Handle t Source #
Type synonym for CanGetLineClass
. See CanGetContents
for more details.
class CanGetContentsClass m handleT t => CanGetLineClass m handleT t where Source #
Methods
hGetLine :: handleT -> m t Source #
Generalised hGetLine
hGetLine :: (CanProxyFrom t, CanGetLineClass m handleT (CanProxyT t)) => handleT -> m t Source #
Generalised hGetLine
Instances
CanGetLineClass m Handle Text => CanGetLineClass m Handle Builder Source # | |
(~) (* -> *) m IO => CanGetLineClass m Handle Text Source # | |
(~) (* -> *) m IO => CanGetLineClass m Handle Text Source # | |
CanGetLineClass m Handle ByteString => CanGetLineClass m Handle Builder Source # | |
(~) (* -> *) m IO => CanGetLineClass m Handle ByteString Source # | |
(~) (* -> *) m IO => CanGetLineClass m Handle ByteString Source # | |
(~) (* -> *) m IO => CanGetLineClass m Handle String Source # | |
getLine :: CanGetLine t => IO t Source #
type CanPutStr t = CanPutStrClass IO Handle t Source #
Type synonym for CanPutStrClass
. See CanGetContents
for more details.
class Monad m => CanPutStrClass m handleT t where Source #
Methods
hPutStr :: handleT -> t -> m () Source #
Generalised hPutStr
hPutStr :: (CanProxyTo t, CanPutStrClass m handleT (CanProxyT t)) => handleT -> t -> m () Source #
Generalised hPutStr
Instances
(Monad m, CanPutStrClass m Handle Text) => CanPutStrClass m Handle Builder Source # | |
(~) (* -> *) m IO => CanPutStrClass m Handle Text Source # | |
(~) (* -> *) m IO => CanPutStrClass m Handle Text Source # | |
(~) (* -> *) m IO => CanPutStrClass m Handle Builder Source # | |
(~) (* -> *) m IO => CanPutStrClass m Handle ByteString Source # | |
(~) (* -> *) m IO => CanPutStrClass m Handle ByteString Source # | |
(~) (* -> *) m IO => CanPutStrClass m Handle String Source # | |
((~) (* -> *) m IO, CanPutStrClass m Handle t) => CanPutStrClass m FilePath t Source # | |
type CanPutStrLn t = CanPutStrLnClass IO Handle t Source #
Effective type synonym for CanPutStrLnClass
. See CanGetContents
for more details.
class CanPutStrClass m handleT t => CanPutStrLnClass m handleT t where Source #
Methods
hPutStrLn :: handleT -> t -> m () Source #
Generalised hPutStrLn
hPutStrLn :: (CanProxyTo t, CanPutStrLnClass m handleT (CanProxyT t)) => handleT -> t -> m () Source #
Generalised hPutStrLn
Instances
CanPutStrLnClass m Handle Text => CanPutStrLnClass m Handle Builder Source # | |
(~) (* -> *) m IO => CanPutStrLnClass m Handle Text Source # | |
(~) (* -> *) m IO => CanPutStrLnClass m Handle Text Source # | |
CanPutStrClass m Handle Builder => CanPutStrLnClass m Handle Builder Source # | |
(~) (* -> *) m IO => CanPutStrLnClass m Handle ByteString Source # | |
(~) (* -> *) m IO => CanPutStrLnClass m Handle ByteString Source # | |
(~) (* -> *) m IO => CanPutStrLnClass m Handle String Source # | |
putStrLn :: CanPutStrLn t => t -> IO () Source #
type family CanProxyT t Source #
If you have a data structure where in many cases the simplest way to read or write to it is just convert it to another you should define an instance of this class.
For example, the simple way to write ByteString
Builder
s is just to
convert them to and from lazy ByteString
s.
Defining classese CanProxyTo
and CanProxyFrom
will define default methods
for many of the other classes in this library.
These can still be overriden if desired but it will save you a lot
of boilerplate if you just which to convert your structure through some other.
class CanProxyFrom t where Source #
Minimal complete definition
Methods
canProxyFrom :: CanProxyT t -> t Source #
How to convert from the type you will attempt to store
Instances