hpp-0.5.1: A Haskell pre-processor

Safe HaskellNone
LanguageHaskell2010

Hpp.RunHpp

Description

Mid-level interface to the pre-processor.

Synopsis

Documentation

parseDefinition :: [TOKEN] -> Maybe (String, Macro) Source #

Parse the definition of an object-like or function macro.

preprocess :: (Monad m, HppCaps m) => [String] -> HppT [String] (Parser m [TOKEN]) () Source #

Run a stream of lines through the preprocessor.

runHpp :: forall m a src. (MonadIO m, HasHppState m) => (FilePath -> m src) -> (src -> m ()) -> HppT src m a -> m (Either (FilePath, Error) (HppResult a)) Source #

Interpret the IO components of the preprocessor. This implementation relies on IO for the purpose of checking search paths for included files.

expandHpp :: forall m a src. (Monad m, HasHppState m, Monoid src) => (src -> m ()) -> HppT src m a -> m (Either (FilePath, Error) (HppResult a)) Source #

Like ’runHpp’, but any #include directives are skipped. These ignored inclusions are tracked in the returned list of files, but note that since extra source files are not opened, any files they might wish to include are not discovered.

hppIOSink :: Config -> Env -> ([String] -> IO ()) -> [String] -> IO [FilePath] Source #

General hpp runner against input source file lines. Output lines are fed to the caller-supplied sink function. Any errors encountered are thrown with error.

type HppCaps t = (HasError t, HasHppState t, HasEnv t) Source #

The dynamic capabilities offered by HPP

hppIO :: Config -> Env -> FilePath -> [String] -> IO (Either Error ([FilePath], [String])) Source #

hpp runner that returns output lines.

data HppResult a Source #

Constructors

HppResult 

Fields