| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Highlight.Highlight.Monad
Synopsis
- type HighlightM = CommonHighlightM Options FromGrepFilenameState HighlightErr
- data FromGrepFilenameState = FromGrepFilenameState {}
- initFromGrepFilenameState :: FromGrepFilenameState
- updateFilenameM :: MonadState FromGrepFilenameState m => ByteString -> m Int
- updateFilename :: ByteString -> FromGrepFilenameState -> FromGrepFilenameState
- runHighlightM :: Options -> HighlightM a -> IO (Either HighlightErr a)
- getColorGrepFilenamesM :: (HasColorGrepFilenames r, MonadReader r m) => m ColorGrepFilenames
- data FilenameHandlingFromFiles
- data InputData m a
- createInputData :: forall m. MonadIO m => Recursive -> [InputFilename] -> Producer ByteString m () -> m (InputData m ())
- data Output
- handleInputData :: forall m. MonadIO m => (ByteString -> m [ByteString]) -> (FilenameHandlingFromFiles -> ByteString -> Int -> ByteString -> m [ByteString]) -> (ByteString -> IOException -> Maybe IOException -> m [ByteString]) -> InputData m () -> Producer Output m ()
- runOutputProducer :: forall m. MonadIO m => Producer Output m () -> m ()
- data CommonHighlightM r s e a
- runCommonHighlightM :: r -> s -> CommonHighlightM r s e a -> IO (Either e a)
- getRecursiveM :: (HasRecursive r, MonadReader r m) => m Recursive
- getInputFilenamesM :: (HasInputFilenames r, MonadReader r m) => m [InputFilename]
- compileHighlightRegexWithErr :: (HasIgnoreCase r, HasRawRegex r) => CommonHighlightM r s HighlightErr RE
Documentation
type HighlightM = CommonHighlightM Options FromGrepFilenameState HighlightErr Source #
HighlightM is just CommonHighlightM specialized for highlight.
data FromGrepFilenameState Source #
The internal state that is used to figure out how to color filenames from
grep.
Constructors
| FromGrepFilenameState | |
updateFilenameM :: MonadState FromGrepFilenameState m => ByteString -> m Int Source #
Call updateFilename and return the new file number after doing the
update.
updateFilename :: ByteString -> FromGrepFilenameState -> FromGrepFilenameState Source #
Update the file number in FromGrepFilenameState if the ByteString
filename passed in is different from that in FromGrepFilenameState.
runHighlightM :: Options -> HighlightM a -> IO (Either HighlightErr a) Source #
getColorGrepFilenamesM :: (HasColorGrepFilenames r, MonadReader r m) => m ColorGrepFilenames Source #
Get the value of the ColorGrepFilenames option.
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. |
Instances
| Eq FilenameHandlingFromFiles Source # | |
Defined in Highlight.Common.Monad.Input Methods (==) :: FilenameHandlingFromFiles -> FilenameHandlingFromFiles -> Bool # (/=) :: FilenameHandlingFromFiles -> FilenameHandlingFromFiles -> Bool # | |
| Read FilenameHandlingFromFiles Source # | |
Defined in Highlight.Common.Monad.Input | |
| Show FilenameHandlingFromFiles Source # | |
Defined in Highlight.Common.Monad.Input Methods showsPrec :: Int -> FilenameHandlingFromFiles -> ShowS # show :: FilenameHandlingFromFiles -> String # showList :: [FilenameHandlingFromFiles] -> ShowS # | |
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.
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 prodJust (FileReaderSuccess (FileSpecifiedByUser "test/golden/test-files/file1") "The...")
Sum-type to represent where a given ByteString should be output, whether
it is stdout or stderr.
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 () |
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
runCommonHighlightM :: r -> s -> CommonHighlightM r s e a -> IO (Either e a) Source #
Given an r and s, run CommonHighlightM.
getRecursiveM :: (HasRecursive r, MonadReader r m) => m Recursive Source #
Get the Recursive option.
getInputFilenamesM :: (HasInputFilenames r, MonadReader r m) => m [InputFilename] Source #
Get a list of the InputFilename.
compileHighlightRegexWithErr :: (HasIgnoreCase r, HasRawRegex r) => CommonHighlightM r s HighlightErr RE Source #
Call compileHighlightRegex. Throw a HighlightErr if the regex cannot
be compiled.