Safe Haskell | None |
---|---|
Language | Haskell2010 |
Ginger parser.
Synopsis
- parseGinger :: forall m. Monad m => IncludeResolver m -> Maybe SourceName -> Source -> m (Either ParserError (Template SourcePos))
- parseGingerFile :: forall m. Monad m => IncludeResolver m -> SourceName -> m (Either ParserError (Template SourcePos))
- parseGinger' :: Monad m => ParserOptions m -> Source -> m (Either ParserError (Template SourcePos))
- parseGingerFile' :: Monad m => ParserOptions m -> SourceName -> m (Either ParserError (Template SourcePos))
- data ParserError = ParserError {}
- data ParserOptions m = ParserOptions {}
- mkParserOptions :: Monad m => IncludeResolver m -> ParserOptions m
- data Delimiters = Delimiters {}
- defDelimiters :: Delimiters
- formatParserError :: Maybe String -> ParserError -> String
- type IncludeResolver m = SourceName -> m (Maybe Source)
- type Source = String
- type SourceName = String
- data SourcePos
- sourceName :: SourcePos -> SourceName
- sourceLine :: SourcePos -> Line
- sourceColumn :: SourcePos -> Column
- setSourceName :: SourcePos -> SourceName -> SourcePos
Documentation
parseGinger :: forall m. Monad m => IncludeResolver m -> Maybe SourceName -> Source -> m (Either ParserError (Template SourcePos)) Source #
Parse Ginger source from memory. The initial template is taken directly
from the provided Source
, while all subsequent includes are loaded through
the provided IncludeResolver
.
parseGingerFile :: forall m. Monad m => IncludeResolver m -> SourceName -> m (Either ParserError (Template SourcePos)) Source #
Parse Ginger source from a file. Both the initial template and all
subsequent includes are loaded through the provided IncludeResolver
. A
consequence of this is that if you pass a "null resolver" (like `const
(return Nothing)`), this function will always fail.
parseGinger' :: Monad m => ParserOptions m -> Source -> m (Either ParserError (Template SourcePos)) Source #
Parse Ginger source from memory. Flavor of parseGinger
that takes
additional ParserOptions
.
parseGingerFile' :: Monad m => ParserOptions m -> SourceName -> m (Either ParserError (Template SourcePos)) Source #
Parse Ginger source from a file. Flavor of parseGingerFile
that takes
additional ParserOptions
.
data ParserError Source #
Error information for Ginger parser errors.
ParserError | |
|
Instances
Show ParserError Source # | |
Defined in Text.Ginger.Parse showsPrec :: Int -> ParserError -> ShowS # show :: ParserError -> String # showList :: [ParserError] -> ShowS # | |
Generic ParserError Source # | |
Defined in Text.Ginger.Parse type Rep ParserError :: * -> * # from :: ParserError -> Rep ParserError x # to :: Rep ParserError x -> ParserError # | |
Exception ParserError Source # | |
Defined in Text.Ginger.Parse | |
type Rep ParserError Source # | |
Defined in Text.Ginger.Parse type Rep ParserError = D1 (MetaData "ParserError" "Text.Ginger.Parse" "ginger-0.8.0.1-1eaVEsutUYRCDo9ki4vBJF" False) (C1 (MetaCons "ParserError" PrefixI True) (S1 (MetaSel (Just "peErrorMessage") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: S1 (MetaSel (Just "peSourcePosition") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe SourcePos)))) |
data ParserOptions m Source #
ParserOptions | |
|
mkParserOptions :: Monad m => IncludeResolver m -> ParserOptions m Source #
Default parser options for a given resolver
data Delimiters Source #
Delimiter configuration.
:: Maybe String | Template source code (not filename) |
-> ParserError | Error to format |
-> String |
Formats a parser errror into something human-friendly.
If template source code is not provided, only the line and column numbers
and the error message are printed. If template source code is provided,
the offending source line is also printed, with a caret (^
) marking the
exact location of the error.
type IncludeResolver m = SourceName -> m (Maybe Source) Source #
Used to resolve includes. Ginger will call this function whenever it
encounters an {% include %}, {% import %}, or {% extends %} directive.
If the required source code is not available, the resolver should return
Nothing
, else Just
the source.
type SourceName = String #
The abstract data type SourcePos
represents source positions. It
contains the name of the source (i.e. file name), a line number and
a column number. SourcePos
is an instance of the Show
, Eq
and
Ord
class.
Instances
Eq SourcePos | |
Data SourcePos | |
Defined in Text.Parsec.Pos gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SourcePos -> c SourcePos # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SourcePos # toConstr :: SourcePos -> Constr # dataTypeOf :: SourcePos -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SourcePos) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SourcePos) # gmapT :: (forall b. Data b => b -> b) -> SourcePos -> SourcePos # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SourcePos -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SourcePos -> r # gmapQ :: (forall d. Data d => d -> u) -> SourcePos -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SourcePos -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SourcePos -> m SourcePos # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SourcePos -> m SourcePos # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SourcePos -> m SourcePos # | |
Ord SourcePos | |
Defined in Text.Parsec.Pos | |
Show SourcePos | |
ToGVal m SourcePos Source # | |
sourceName :: SourcePos -> SourceName #
Extracts the name of the source from a source position.
sourceLine :: SourcePos -> Line #
Extracts the line number from a source position.
sourceColumn :: SourcePos -> Column #
Extracts the column number from a source position.
setSourceName :: SourcePos -> SourceName -> SourcePos #
Set the name of the source.