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

Highlight.Hrep.Monad

Synopsis

Documentation

data FilenameHandlingFromFiles Source #

This data type specifies how printing filenames will be handled, along with the computeFilenameHandlingFromFiles function.

Constructors

NoFilename

Do not print the filename on stdout.

PrintFilename

Print the filename on stdout.

data InputData m a Source #

This wraps up two pieces of information.

One is the value of FilenameHandlingFromFiles. This signals as to whether or not we need to print the filename when printing each line of output.

This other is a Producer of FileReader ByteStrings. This is a Producer for each line of each input file.

The main job of this module is to define createInputData, which produces InputData. InputData is what is processed to figure out what to output.

createInputData Source #

Arguments

:: forall m. MonadIO m 
=> Recursive

Whether or not to recursively read in files.

-> [InputFilename]

List of files passed in on the command line.

-> Producer ByteString m ()

A producer for standard input

-> m (InputData m ()) 

Create InputData based InputFilename list.

Setup for examples:

>>> :set -XOverloadedStrings
>>> import Highlight.Common.Options (InputFilename(InputFilename))
>>> import Highlight.Common.Options (Recursive(NotRecursive))

If the InputFilename list is empty, just create an InputData with NoFilename and the standard input Producer passed in.

>>> let stdinProd = yield ("hello" :: ByteString)
>>> let create = createInputData NotRecursive [] stdinProd
>>> InputData NoFilename prod <- create
>>> toListM prod
[FileReaderSuccess Stdin "hello"]

If the InputFilename list is not empty, create an InputData with lines from each file found on the command line.

>>> let inFiles = [InputFilename "test/golden/test-files/file1"]
>>> let create = createInputData NotRecursive inFiles stdinProd
>>> InputData NoFilename prod <- create
>>> Pipes.head prod
Just (FileReaderSuccess (FileSpecifiedByUser "test/golden/test-files/file1") "The...")

data Output Source #

Sum-type to represent where a given ByteString should be output, whether it is stdout or stderr.

Instances

Instances details
Eq Output Source # 
Instance details

Defined in Highlight.Common.Monad.Output

Methods

(==) :: Output -> Output -> Bool #

(/=) :: Output -> Output -> Bool #

Read Output Source # 
Instance details

Defined in Highlight.Common.Monad.Output

Show Output Source # 
Instance details

Defined in Highlight.Common.Monad.Output

handleInputData Source #

Arguments

:: forall m. MonadIO m 
=> (ByteString -> m [ByteString])

Function to use for conversion for a line from stdin.

-> (FilenameHandlingFromFiles -> ByteString -> Int -> ByteString -> m [ByteString])

Function to use for conversion for a line from a normal file.

-> (ByteString -> IOException -> Maybe IOException -> m [ByteString])

Function to use for conversion for an io error.

-> InputData m ()

All of the input lines.

-> Producer Output m () 

Convert InputData to Output.

runOutputProducer :: forall m. MonadIO m => Producer Output m () -> m () Source #

Run a Producer Output by connecting it to outputConsumer.

data CommonHighlightM r s e a Source #

This is the common monad for both highlight and hrep. It has been kept polymorphic here so it can be easily specialized by highlight and hrep.

r is the options or config type. s is the state. e is the error.

Instances

Instances details
MonadReader r (CommonHighlightM r s e) Source # 
Instance details

Defined in Highlight.Common.Monad

Methods

ask :: CommonHighlightM r s e r #

local :: (r -> r) -> CommonHighlightM r s e a -> CommonHighlightM r s e a #

reader :: (r -> a) -> CommonHighlightM r s e a #

MonadState s (CommonHighlightM r s e) Source # 
Instance details

Defined in Highlight.Common.Monad

Methods

get :: CommonHighlightM r s e s #

put :: s -> CommonHighlightM r s e () #

state :: (s -> (a, s)) -> CommonHighlightM r s e a #

MonadError e (CommonHighlightM r s e) Source # 
Instance details

Defined in Highlight.Common.Monad

Methods

throwError :: e -> CommonHighlightM r s e a #

catchError :: CommonHighlightM r s e a -> (e -> CommonHighlightM r s e a) -> CommonHighlightM r s e a #

Monad (CommonHighlightM r s e) Source # 
Instance details

Defined in Highlight.Common.Monad

Methods

(>>=) :: CommonHighlightM r s e a -> (a -> CommonHighlightM r s e b) -> CommonHighlightM r s e b #

(>>) :: CommonHighlightM r s e a -> CommonHighlightM r s e b -> CommonHighlightM r s e b #

return :: a -> CommonHighlightM r s e a #

Functor (CommonHighlightM r s e) Source # 
Instance details

Defined in Highlight.Common.Monad

Methods

fmap :: (a -> b) -> CommonHighlightM r s e a -> CommonHighlightM r s e b #

(<$) :: a -> CommonHighlightM r s e b -> CommonHighlightM r s e a #

Applicative (CommonHighlightM r s e) Source # 
Instance details

Defined in Highlight.Common.Monad

Methods

pure :: a -> CommonHighlightM r s e a #

(<*>) :: CommonHighlightM r s e (a -> b) -> CommonHighlightM r s e a -> CommonHighlightM r s e b #

liftA2 :: (a -> b -> c) -> CommonHighlightM r s e a -> CommonHighlightM r s e b -> CommonHighlightM r s e c #

(*>) :: CommonHighlightM r s e a -> CommonHighlightM r s e b -> CommonHighlightM r s e b #

(<*) :: CommonHighlightM r s e a -> CommonHighlightM r s e b -> CommonHighlightM r s e a #

MonadIO (CommonHighlightM r s e) Source # 
Instance details

Defined in Highlight.Common.Monad

Methods

liftIO :: IO a -> CommonHighlightM r s e a #

runCommonHighlightM :: r -> s -> CommonHighlightM r s e a -> IO (Either e a) Source #

Given an r and s, run CommonHighlightM.