hpp-0.6.0: A Haskell pre-processor

Safe HaskellNone
LanguageHaskell2010

Hpp

Contents

Description

Front-end interface to the pre-processor.

Synopsis

Running the Preprocessor

preprocess :: Monad m => [ByteString] -> HppT m () Source #

Preprocess lines of input.

runHpp :: MonadIO m => HppState -> HppT m a -> ExceptT Error m (HppOutput, HppState) Source #

Run a preprocessor action with some initial state. Returns the result of preprocessing as well as an updated preprocessor state representation.

streamHpp :: MonadIO m => HppState -> ([ByteString] -> m ()) -> HppT m a -> ExceptT Error m ([FilePath], HppState) Source #

streamHpp state sink action runs a preprocessor action with some initial state. Output is streamed to the caller-provided output sink as it is generated. The list of files read during preprocessing is returned along with an updated preprocessor state representation.

expand :: HppState -> HppT (State ([ByteString] -> [ByteString])) a -> Except Error (HppOutput, HppState) Source #

Like runHpp, but does not access the filesystem. Run a preprocessor action with some initial state. Returns the result of preprocessing as well as an updated preprocessor state representation. Since this operation performs no IO, #include directives are ignored in terms of the generated output lines, but the files named in those directive are available in the HppOutput value returned.

Preprocessor State

data HppState Source #

Dynamic state of the preprocessor engine.

Instances
Show HppState Source # 
Instance details

Defined in Hpp.Types

Monad m => HasEnv (StateT HppState m) Source # 
Instance details

Defined in Hpp.Types

Monad m => HasHppState (StateT HppState m) Source # 
Instance details

Defined in Hpp.Types

emptyHppState :: HppState Source #

An HppState containing no macro definitions, and default values for the starting configuration: the name of the current file is "NoFile", there are no paths to be searched for included files, etc. See Config for more information on available configuration.

initHppState :: Config -> Env -> HppState Source #

Create a HppState with the given Config and Env.

Adding Definitions

parseDefinition :: ByteString -> ByteString -> Maybe (ByteString, Macro) Source #

Lower level parsing of macro definitions. Will typically be used with insertPair for manual construction of a Env binding environment.

addDefinition :: ByteString -> ByteString -> HppState -> Maybe HppState Source #

addDefinition name expression adds a binding of name to expression in the preprocessor’s internal state.

Core Types

data HppT m a Source #

The type of preprocessor actions. Created with preprocess and executed with runHpp or streamHpp.

Instances
MonadTrans HppT Source # 
Instance details

Defined in Hpp

Methods

lift :: Monad m => m a -> HppT m a #

Monad m => Monad (HppT m) Source # 
Instance details

Defined in Hpp

Methods

(>>=) :: HppT m a -> (a -> HppT m b) -> HppT m b #

(>>) :: HppT m a -> HppT m b -> HppT m b #

return :: a -> HppT m a #

fail :: String -> HppT m a #

Functor m => Functor (HppT m) Source # 
Instance details

Defined in Hpp

Methods

fmap :: (a -> b) -> HppT m a -> HppT m b #

(<$) :: a -> HppT m b -> HppT m a #

Monad m => Applicative (HppT m) Source # 
Instance details

Defined in Hpp

Methods

pure :: a -> HppT m a #

(<*>) :: HppT m (a -> b) -> HppT m a -> HppT m b #

liftA2 :: (a -> b -> c) -> HppT m a -> HppT m b -> HppT m c #

(*>) :: HppT m a -> HppT m b -> HppT m b #

(<*) :: HppT m a -> HppT m b -> HppT m a #

data HppOutput Source #

The result of running hpp

Constructors

HppOutput