Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- fromHandle :: MonadIO m => Handle -> Producer Text m ()
- stdin :: MonadIO m => Producer Text m ()
- readFile :: MonadSafe m => FilePath -> Producer Text m ()
- toHandle :: MonadIO m => Handle -> Consumer' Text m r
- stdout :: MonadIO m => Consumer' Text m ()
- writeFile :: MonadSafe m => FilePath -> Consumer' Text m ()
- class (MonadCatch m, MonadMask m, MonadIO m, MonadIO (Base m)) => MonadSafe (m :: Type -> Type) where
- runSafeT :: (MonadMask m, MonadIO m) => SafeT m r -> m r
- runSafeP :: forall (m :: Type -> Type) r. (MonadMask m, MonadIO m) => Effect (SafeT m) r -> Effect' m r
- withFile :: MonadSafe m => FilePath -> IOMode -> (Handle -> m r) -> m r
Simple streaming text IO
Where pipes IO
replaces lazy IO
, Producer Text IO r
replaces lazy Text
.
The official IO of this package and the pipes ecosystem generally would use the
IO functions in Pipes.ByteString
and the encoding and decoding material in
Pipes.Text.Encoding
.
The streaming functions exported here, namely, readFile
, writeFile
, fromHandle
, toHandle
,
stdin
and stdout
simplify this and use the system encoding on the model of Data.Text.IO
and Data.Text.Lazy.IO
Some caveats described below.
The main points are as in Pipes.ByteString:
A Handle
can be associated with a Producer
or Consumer
according
as it is read or written to.
import Pipes import qualified Pipes.Text as Text import qualified Pipes.Text.IO as Text import System.IO main = withFile "inFile.txt" ReadMode $ \hIn -> withFile "outFile.txt" WriteMode $ \hOut -> runEffect $ Text.fromHandle hIn >-> Text.toHandle hOut
To stream from files, the following is perhaps more Prelude-like (note that it uses Pipes.Safe):
import Pipes import qualified Pipes.Text as Text import qualified Pipes.Text.IO as Text import Pipes.Safe main = runSafeT $ runEffect $ Text.readFile "inFile.txt" >-> Text.writeFile "outFile.txt"
Finally, you can stream to and from stdin
and stdout
using the predefined stdin
and stdout
pipes, as with the following "echo" program:
main = runEffect $ Text.stdin >-> Text.stdout
These programs, unlike the corresponding programs written with the line-based functions, will pass along a 1 terabyte line without affecting memory use.
Caveats
The operations exported here are a convenience, like the similar operations in
Data.Text.IO
(or rather, Data.Text.Lazy.IO
, since, again, Producer Text m r
is
'effectful text' and something like the pipes equivalent of lazy Text.)
- Like the functions in
Data.Text.IO
, they attempt to work with the system encoding. - Like the functions in
Data.Text.IO
, they significantly slower than ByteString operations. Where you know what encoding you are working with, usePipes.ByteString
andPipes.Text.Encoding
instead, e.g.view utf8 Bytes.stdin
instead ofText.stdin
- Like the functions in
Data.Text.IO
, they use Text exceptions, not the standard Pipes protocols.
Producers
fromHandle :: MonadIO m => Handle -> Producer Text m () Source #
Convert a Handle
into a text stream using a text size
determined by the good sense of the text library. Note with the remarks
at the head of this module that this
is slower than view utf8 (Pipes.ByteString.fromHandle h)
but uses the system encoding and has other nice Data.Text.IO
features
readFile :: MonadSafe m => FilePath -> Producer Text m () Source #
Stream text from a file in the simple fashion of Data.Text.IO
>>>
runSafeT $ runEffect $ Text.readFile "hello.hs" >-> Text.map toUpper >-> hoist lift Text.stdout
MAIN = PUTSTRLN "HELLO WORLD"
Consumers
toHandle :: MonadIO m => Handle -> Consumer' Text m r Source #
Convert a text stream into a Handle
Note: again, for best performance, where possible use
(for source (liftIO . hPutStr handle))
instead of (source >-> toHandle handle)
.
writeFile :: MonadSafe m => FilePath -> Consumer' Text m () Source #
Stream text into a file. Uses pipes-safe
.
Re-exports
class (MonadCatch m, MonadMask m, MonadIO m, MonadIO (Base m)) => MonadSafe (m :: Type -> Type) where #
type Base (m :: Type -> Type) :: Type -> Type #
The monad used to run resource management actions, corresponding to the
monad directly beneath SafeT
Lift an action from the Base
monad
register :: Base m () -> m ReleaseKey #
register
a finalizer, ensuring that the finalizer gets called if the
finalizer is not release
d before the end of the surrounding SafeT
block.
release :: ReleaseKey -> m () #
release
a registered finalizer
You can safely call release
more than once on the same ReleaseKey
.
Every release
after the first one does nothing.
Instances
MonadSafe m => MonadSafe (CatchT m) | |
(MonadIO m, MonadCatch m, MonadMask m) => MonadSafe (SafeT m) | |
MonadSafe m => MonadSafe (IdentityT m) | |
(MonadSafe m, Monoid w) => MonadSafe (WriterT w m) | |
MonadSafe m => MonadSafe (StateT s m) | |
MonadSafe m => MonadSafe (ReaderT i m) | |
MonadSafe m => MonadSafe (StateT s m) | |
(MonadSafe m, Monoid w) => MonadSafe (WriterT w m) | |
(MonadSafe m, Monoid w) => MonadSafe (RWST i w s m) | |
(MonadSafe m, Monoid w) => MonadSafe (RWST i w s m) | |
MonadSafe m => MonadSafe (Proxy a' a b' b m) | |
runSafeT :: (MonadMask m, MonadIO m) => SafeT m r -> m r #
Run the SafeT
monad transformer, executing all unreleased finalizers at
the end of the computation