hpp-0.3.0.0: A Haskell pre-processor

Safe HaskellSafe
LanguageHaskell2010

Hpp.Types

Contents

Description

The core types involved used by the pre-processor.

Synopsis

Documentation

type LineNum = Int Source

Line numbers are represented as Ints

type Env = [(String, Macro)] Source

A macro binding environment.

Errors

class HasError m where Source

Hpp can raise various parsing errors.

Methods

throwError :: Error -> m a Source

Instances

Resource cleanup

newtype Cleanup Source

A cleanup action that is run at most once. To be used as an abstract type with only runCleanup and mkCleanup as interface.

Constructors

Cleanup (IORef (IO ())) 

runCleanup :: Cleanup -> IO () Source

Runs an action and replaces it with a nop

mkCleanup :: IO () -> IO (Cleanup, IO ()) Source

mkCleanup cleanup returns two things: a Cleanup value, and an action to neutralize that Cleanup. In this way, the Cleanup value can be registered with a resource manager so that, in the event of an error, the cleanup action is run, while the neutralizer may be used to ensure that the registered Cleanup action has no effect if it is run. Typically one would neutralize a registered cleanup action before performing a manual cleanup that subsumes the registered cleanup.

Free Monad Transformers

data FreeF f a r Source

Base functor for a free monad transformer

Constructors

PureF a 
FreeF (f r) 

Instances

Pre-processor Actions

data HppState Source

Dynamic state of the preprocessor engine.

Constructors

HppState 

data HppF t r Source

A free monad construction to strictly delimit what capabilities we need to perform pre-processing.

Instances

Hpp Monad Transformer

newtype HppT t m a Source

A free monad transformer specialized to HppF as the base functor.

Constructors

HppT 

Fields

runHppT :: m (FreeF (HppF t) a (HppT t m a))
 

Instances

class HasHppState m where Source

An interpreter capability to modify dynamic state.

class HasEnv m where Source

An interpreter capability of threading a binding environment.

Methods

getEnv :: m Env Source

setEnv :: Env -> m () Source

Instances

(HasEnv m, Monad m) => HasEnv (ExceptT e m) Source 
Monad m => HasEnv (HppT t m) Source 
(Monad m, HasEnv m) => HasEnv (Streamer m i o) Source 

Expansion

data Scan Source

Macro expansion involves treating tokens differently if they appear in the original source for or as the result of a previous macro expansion. This distinction is used to prevent divergence by masking out definitions that could be used recursively.

Things are made somewhat more complicated than one might expect due to the fact that the scope of this masking is not structurally recursive. A object-like macro can expand into a fragment of a macro function application, one of whose arguments is a token matching the original object-like macro. That argument should not be expanded.

Macros

data Macro Source

There are object-like macros and function-like macros.

Constructors

Object [Token]

An object-like macro is replaced with its definition

Function Int ([([Scan], String)] -> [Scan])

A function-like macro of some arity taks macro-expanded and raw versions of its arguments, then substitutes them into a body producing a new set of tokens.

Instances