Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
The core types involved used by the pre-processor.
Synopsis
- type LineNum = Int
- type Env = HashMap ByteString Macro
- type String = ByteString
- type TOKEN = Token ByteString
- data Error
- = UnterminatedBranch
- | BadMacroDefinition LineNum
- | BadIfPredicate
- | BadLineArgument LineNum String
- | IncludeDoesNotExist LineNum FilePath
- | FailedInclude LineNum FilePath
- | UserError LineNum String
- | UnknownCommand LineNum String
- | TooFewArgumentsToMacro LineNum String
- | BadMacroArguments LineNum String
- | NoInputFile
- | BadCommandLine String
- | RanOutOfInput
- class HasError m where
- throwError :: Error -> m a
- data FreeF f a r
- data HppState = HppState {}
- data HppF t r
- type Hpp t = FreeF (HppF t)
- newtype HppT t m a = HppT {}
- hppReadFile :: Monad m => Int -> FilePath -> HppT src m src
- hppReadNext :: Monad m => Int -> FilePath -> HppT src m src
- hppWriteOutput :: Monad m => t -> HppT t m ()
- class HasHppState m where
- class HasEnv m where
- data Scan
- data Macro
- lookupMacro :: (HasEnv m, Monad m) => String -> m (Maybe Macro)
- type Lens s a = forall f. Functor f => (a -> f a) -> s -> f s
- setL :: Lens s a -> a -> s -> s
- getL :: Lens s a -> s -> a
- over :: Lens s a -> (a -> a) -> s -> s
- emptyHppState :: Config -> HppState
- config :: Lens HppState Config
- dir :: Lens HppState FilePath
- lineNum :: Lens HppState LineNum
- env :: Lens HppState Env
- use :: (HasHppState m, Functor m) => Lens HppState a -> m a
- (.=) :: (HasHppState m, Monad m) => Lens HppState a -> a -> m ()
- (%=) :: (HasHppState m, Monad m) => Lens HppState a -> (a -> a) -> m ()
Documentation
Changing the underlying string type
type String = ByteString Source #
type TOKEN = Token ByteString Source #
Errors
Error conditions we may encounter.
class HasError m where Source #
Hpp can raise various parsing errors.
throwError :: Error -> m a Source #
Free Monad Transformers
Base functor for a free monad transformer
Pre-processor Actions
Dynamic state of the preprocessor engine.
A free monad construction to strictly delimit what capabilities we need to perform pre-processing.
Hpp Monad Transformer
A free monad transformer specialized to HppF as the base functor.
Instances
MonadTrans (HppT t) Source # | |
Monad m => Monad (HppT t m) Source # | |
Functor m => Functor (HppT t m) Source # | |
Monad m => Applicative (HppT t m) Source # | |
MonadIO m => MonadIO (HppT t m) Source # | |
(Monad m, HasHppState m) => HasEnv (HppT t m) Source # | |
(Monad m, HasHppState m) => HasHppState (HppT t m) Source # | |
(Monad m, HasError m) => HasError (HppT t m) Source # | |
hppReadFile :: Monad m => Int -> FilePath -> HppT src m src Source #
hppReadFile lineNumber fileName
introduces an #include
fileName
at the given line number.
hppReadNext :: Monad m => Int -> FilePath -> HppT src m src Source #
hppReadNext lineNumber fileName
introduces an #include_next
fileName
at the given line number.
hppWriteOutput :: Monad m => t -> HppT t m () Source #
class HasHppState m where Source #
An interpreter capability to modify dynamic state.
Instances
(Monad m, HasHppState m) => HasHppState (StateT s m) Source # | |
Monad m => HasHppState (StateT HppState m) Source # | |
(Monad m, HasHppState m) => HasHppState (ExceptT e m) Source # | |
(Monad m, HasHppState m) => HasHppState (HppT t m) Source # | |
An interpreter capability of threading a binding environment.
Expansion
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.
Macros
There are object-like macros and function-like macros.
Nano-lens
State Lenses
emptyHppState :: Config -> HppState Source #