highlight-1.0.0.2: Command line tool for highlighting parts of files matching a regex.
Safe HaskellNone
LanguageHaskell2010

Highlight.Pipes

Synopsis

Documentation

fromHandleLines :: forall m. MonadIO m => Handle -> Producer' ByteString m () Source #

Read input from a Handle, split it into lines, and return each of those lines as a ByteString in a Producer.

This function will close the Handle if the end of the file is reached. However, if an error was thrown while reading input from the Handle, the Handle is not closed.

Setup for examples:

>>> import Pipes.Prelude (toListM)
>>> import System.IO (IOMode(ReadMode), openBinaryFile)
>>> let goodFilePath = "test/golden/test-files/file2"

Examples:

>>> handle <- openBinaryFile goodFilePath ReadMode
>>> fmap head . toListM $ fromHandleLines handle
"Proud Pour is a wine company that funds solutions to local environmental"

fromFileLines :: forall m n x' x. (MonadIO m, MonadIO n) => FilePath -> m (Either IOException (Proxy x' x () ByteString n ())) Source #

Try calling fromHandleLines on the Handle obtained from openFilePathForReading.

Setup for examples:

>>> import Pipes (Producer)
>>> import Pipes.Prelude (toListM)
>>> let t a = a :: IO (Either IOException (Producer ByteString IO ()))
>>> let goodFilePath = "test/golden/test-files/file2"
>>> let badFilePath = "thisfiledoesnotexist"
>>> let handleErr err = error $ "got following error: " `mappend` show err

Example:

>>> eitherProducer <- t $ fromFileLines goodFilePath
>>> let producer = either handleErr id eitherProducer
>>> fmap head $ toListM producer
"Proud Pour is a wine company that funds solutions to local environmental"

Returns IOException if there was an error when opening the file.

>>> eitherProducer <- t $ fromFileLines badFilePath
>>> either print (const $ return ()) eitherProducer
thisfiledoesnotexist: openBinaryFile: does not exist ...

stderrConsumer :: forall m. MonadIO m => Consumer' ByteString m () Source #

Output ByteStrings to stderr.

If an ePIPE error is thrown, then just return (). If any other error is thrown, rethrow the error.

Setup for examples:

>>> :set -XOverloadedStrings
>>> import Pipes ((>->), runEffect)

Example:

>>> runEffect $ yield "hello" >-> stderrConsumer
hello

childOf :: MonadIO m => FilePath -> Producer' FilePath m () Source #

Select all immediate children of the given directory, ignoring "." and "..".

Throws an IOException if the directory is not readable or (on Windows) if the directory is actually a reparse point.

Setup for examples:

>>> import Data.List (sort)
>>> import Pipes.Prelude (toListM)

Examples:

>>> fmap (head . sort) . toListM $ childOf "test/golden/test-files"
"test/golden/test-files/dir1"

TODO: This could be rewritten to be faster by using the Windows- and Linux-specific functions to only read one file from a directory at a time like the actual childOf function.