hpp-0.5.0.1: A Haskell pre-processor

Safe HaskellNone
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 = Trie Macro Source #

A macro binding environment.

Changing the underlying string type

Errors

class HasError m where Source #

Hpp can raise various parsing errors.

Minimal complete definition

throwError

Methods

throwError :: Error -> m a Source #

Instances

(Monad m, HasError m) => HasError (StateT s m) Source # 

Methods

throwError :: Error -> StateT s m a Source #

Monad m => HasError (ExceptT Error m) Source # 
(Monad m, HasError m) => HasError (HppT t m) Source # 

Methods

throwError :: Error -> HppT t m a Source #

Free Monad Transformers

data FreeF f a r Source #

Base functor for a free monad transformer

Constructors

PureF a 
FreeF (f r) 

Instances

Functor f => Functor (FreeF f a) Source # 

Methods

fmap :: (a -> b) -> FreeF f a a -> FreeF f a b #

(<$) :: a -> FreeF f a b -> FreeF f a a #

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.

Constructors

ReadFile Int FilePath (t -> r) 
ReadNext Int FilePath (t -> r) 
WriteOutput t r 

Instances

Functor (HppF t) Source # 

Methods

fmap :: (a -> b) -> HppF t a -> HppF t b #

(<$) :: a -> HppF t b -> HppF t a #

Hpp Monad Transformer

newtype HppT t m a Source #

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

Constructors

HppT 

Fields

Instances

MonadTrans (HppT t) Source # 

Methods

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

Monad m => Monad (HppT t m) Source # 

Methods

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

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

return :: a -> HppT t m a #

fail :: String -> HppT t m a #

Functor m => Functor (HppT t m) Source # 

Methods

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

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

Monad m => Applicative (HppT t m) Source # 

Methods

pure :: a -> HppT t m a #

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

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

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

MonadIO m => MonadIO (HppT t m) Source # 

Methods

liftIO :: IO a -> HppT t m a #

(Monad m, HasHppState m) => HasEnv (HppT t m) Source # 

Methods

getEnv :: HppT t m Env Source #

setEnv :: Env -> HppT t m () Source #

(Monad m, HasHppState m) => HasHppState (HppT t m) Source # 
(Monad m, HasError m) => HasError (HppT t m) Source # 

Methods

throwError :: Error -> HppT t m a Source #

writeOutput :: Monad m => t -> HppT t m () Source #

class HasHppState m where Source #

An interpreter capability to modify dynamic state.

Minimal complete definition

getState, setState

class HasEnv m where Source #

An interpreter capability of threading a binding environment.

Minimal complete definition

getEnv, setEnv

Methods

getEnv :: m Env Source #

setEnv :: Env -> m () Source #

Instances

Monad m => HasEnv (StateT HppState m) Source # 
Monad m => HasEnv (StateT Env m) Source # 
(HasEnv m, Monad m) => HasEnv (ExceptT e m) Source # 

Methods

getEnv :: ExceptT e m Env Source #

setEnv :: Env -> ExceptT e m () Source #

(Monad m, HasHppState m) => HasEnv (HppT t m) Source # 

Methods

getEnv :: HppT t m Env Source #

setEnv :: Env -> HppT t m () Source #

Expansion

data Scan Source #

Macro expansion involves treating tokens differently if they appear in the original source 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.

Instances

Eq Scan Source # 

Methods

(==) :: Scan -> Scan -> Bool #

(/=) :: Scan -> Scan -> Bool #

Show Scan Source # 

Methods

showsPrec :: Int -> Scan -> ShowS #

show :: Scan -> String #

showList :: [Scan] -> ShowS #

Macros

data Macro Source #

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

Constructors

Object [Token String]

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

lookupMacro :: (HasEnv m, Monad m) => String -> m (Maybe Macro) Source #

Looks up a Macro in the current environment. If the Macro is found, the environment is juggled so that subsequent lookups of the same Macro may evaluate more quickly.

Nano-lens

type Lens s a = forall f. Functor f => (a -> f a) -> s -> f s Source #

setL :: Lens s a -> a -> s -> s Source #

getL :: Lens s a -> s -> a Source #

over :: Lens s a -> (a -> a) -> s -> s Source #

State Lenses

use :: (HasHppState m, Functor m) => Lens HppState a -> m a Source #

(.=) :: (HasHppState m, Monad m) => Lens HppState a -> a -> m () infix 4 Source #

(%=) :: (HasHppState m, Monad m) => Lens HppState a -> (a -> a) -> m () infix 4 Source #