hpp-0.3.0.0: A Haskell pre-processor

Safe HaskellNone
LanguageHaskell2010

Hpp

Description

Front-end 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) => Source m String () -> Source m String () Source

Run a stream of lines through the preprocessor.

yield :: Monad m => o -> Streamer m i o () Source

Yield a value downstream, then finish.

before :: Monad m => Streamer m i o q -> Streamer m i o r -> Streamer m i o r Source

x before y runs x to completion, discards its Done value, then becomes y.

source :: (Monad m, Foldable f) => f a -> Streamer m i a () Source

Feed values downstream.

hppReadFile :: HasHppFileIO m => Int -> FilePath -> m (InputStream m) Source

Read a file as an Hpp action

hppIO :: MonadIO m => Config -> Env -> Streamer (HppStream m) Void b r -> Streamer (HppStream m) b Void () -> m (Maybe ()) Source

Monad morphism between Hpp and IO.

hppRegisterCleanup :: (HasHppState m, Monad m) => Cleanup -> m () Source

Register a Cleanup in a threaded HppState.

streamHpp :: (Monad m, HasHppFileIO m) => FilePath -> Source m String () Source

Preprocess the given file producing line by line output.

sinkToFile :: MonadIO m => (Cleanup -> m ()) -> FilePath -> Streamer m String o () Source

Incrementally writes Strings to a temporary file. When all input is exhausted, the temporary file is renamed to the supplied FilePath.

sinkToStdOut :: MonadIO m => Streamer m String o () Source

Sink a stream to stdout

(~>) :: Monad m => Streamer m a b r -> Streamer m b c r' -> Streamer m a c r' infixl 9 Source

upstream ~> downstream composes two streams such that values flow from upstream to downstream.

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

The dynamic capabilities offered by HPP