{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Hakyll.Web.Template.Internal.Element
( TemplateKey (..)
, TemplateExpr (..)
, TemplateElement (..)
, templateElems
, parseTemplateElemsFile
) where
import Control.Applicative ((<|>))
import Control.Monad (void)
import Control.Arrow (left)
import Data.Binary (Binary, get, getWord8, put, putWord8)
import Data.List (intercalate)
import Data.Maybe (isJust)
import Data.Typeable (Typeable)
import GHC.Exts (IsString (..))
import qualified Text.Parsec as P
import qualified Text.Parsec.String as P
import Hakyll.Core.Util.Parser
newtype TemplateKey = TemplateKey String
deriving (Get TemplateKey
[TemplateKey] -> Put
TemplateKey -> Put
forall t. (t -> Put) -> Get t -> ([t] -> Put) -> Binary t
putList :: [TemplateKey] -> Put
$cputList :: [TemplateKey] -> Put
get :: Get TemplateKey
$cget :: Get TemplateKey
put :: TemplateKey -> Put
$cput :: TemplateKey -> Put
Binary, Int -> TemplateKey -> ShowS
[TemplateKey] -> ShowS
TemplateKey -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TemplateKey] -> ShowS
$cshowList :: [TemplateKey] -> ShowS
show :: TemplateKey -> String
$cshow :: TemplateKey -> String
showsPrec :: Int -> TemplateKey -> ShowS
$cshowsPrec :: Int -> TemplateKey -> ShowS
Show, TemplateKey -> TemplateKey -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TemplateKey -> TemplateKey -> Bool
$c/= :: TemplateKey -> TemplateKey -> Bool
== :: TemplateKey -> TemplateKey -> Bool
$c== :: TemplateKey -> TemplateKey -> Bool
Eq, Typeable)
instance IsString TemplateKey where
fromString :: String -> TemplateKey
fromString = String -> TemplateKey
TemplateKey
data TemplateElement
= Chunk String
| Expr TemplateExpr
| Escaped
| If TemplateExpr [TemplateElement] (Maybe [TemplateElement])
| For TemplateExpr [TemplateElement] (Maybe [TemplateElement])
| Partial TemplateExpr
| TrimL
| TrimR
deriving (Int -> TemplateElement -> ShowS
[TemplateElement] -> ShowS
TemplateElement -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TemplateElement] -> ShowS
$cshowList :: [TemplateElement] -> ShowS
show :: TemplateElement -> String
$cshow :: TemplateElement -> String
showsPrec :: Int -> TemplateElement -> ShowS
$cshowsPrec :: Int -> TemplateElement -> ShowS
Show, TemplateElement -> TemplateElement -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TemplateElement -> TemplateElement -> Bool
$c/= :: TemplateElement -> TemplateElement -> Bool
== :: TemplateElement -> TemplateElement -> Bool
$c== :: TemplateElement -> TemplateElement -> Bool
Eq, Typeable)
instance Binary TemplateElement where
put :: TemplateElement -> Put
put (Chunk String
string) = Word8 -> Put
putWord8 Word8
0 forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall t. Binary t => t -> Put
put String
string
put (Expr TemplateExpr
e) = Word8 -> Put
putWord8 Word8
1 forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall t. Binary t => t -> Put
put TemplateExpr
e
put TemplateElement
Escaped = Word8 -> Put
putWord8 Word8
2
put (If TemplateExpr
e [TemplateElement]
t Maybe [TemplateElement]
f) = Word8 -> Put
putWord8 Word8
3 forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall t. Binary t => t -> Put
put TemplateExpr
e forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall t. Binary t => t -> Put
put [TemplateElement]
t forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall t. Binary t => t -> Put
put Maybe [TemplateElement]
f
put (For TemplateExpr
e [TemplateElement]
b Maybe [TemplateElement]
s) = Word8 -> Put
putWord8 Word8
4 forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall t. Binary t => t -> Put
put TemplateExpr
e forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall t. Binary t => t -> Put
put [TemplateElement]
b forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall t. Binary t => t -> Put
put Maybe [TemplateElement]
s
put (Partial TemplateExpr
e) = Word8 -> Put
putWord8 Word8
5 forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall t. Binary t => t -> Put
put TemplateExpr
e
put TemplateElement
TrimL = Word8 -> Put
putWord8 Word8
6
put TemplateElement
TrimR = Word8 -> Put
putWord8 Word8
7
get :: Get TemplateElement
get = Get Word8
getWord8 forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Word8
tag -> case Word8
tag of
Word8
0 -> String -> TemplateElement
Chunk forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall t. Binary t => Get t
get
Word8
1 -> TemplateExpr -> TemplateElement
Expr forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall t. Binary t => Get t
get
Word8
2 -> forall (f :: * -> *) a. Applicative f => a -> f a
pure TemplateElement
Escaped
Word8
3 -> TemplateExpr
-> [TemplateElement] -> Maybe [TemplateElement] -> TemplateElement
If forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall t. Binary t => Get t
get forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall t. Binary t => Get t
get forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall t. Binary t => Get t
get
Word8
4 -> TemplateExpr
-> [TemplateElement] -> Maybe [TemplateElement] -> TemplateElement
For forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall t. Binary t => Get t
get forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall t. Binary t => Get t
get forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall t. Binary t => Get t
get
Word8
5 -> TemplateExpr -> TemplateElement
Partial forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall t. Binary t => Get t
get
Word8
6 -> forall (f :: * -> *) a. Applicative f => a -> f a
pure TemplateElement
TrimL
Word8
7 -> forall (f :: * -> *) a. Applicative f => a -> f a
pure TemplateElement
TrimR
Word8
_ -> forall a. HasCallStack => String -> a
error String
"Hakyll.Web.Template.Internal: Error reading cached template"
data TemplateExpr
= Ident TemplateKey
| Call TemplateKey [TemplateExpr]
| StringLiteral String
deriving (TemplateExpr -> TemplateExpr -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TemplateExpr -> TemplateExpr -> Bool
$c/= :: TemplateExpr -> TemplateExpr -> Bool
== :: TemplateExpr -> TemplateExpr -> Bool
$c== :: TemplateExpr -> TemplateExpr -> Bool
Eq, Typeable)
instance Show TemplateExpr where
show :: TemplateExpr -> String
show (Ident (TemplateKey String
k)) = String
k
show (Call (TemplateKey String
k) [TemplateExpr]
as) =
String
k forall a. [a] -> [a] -> [a]
++ String
"(" forall a. [a] -> [a] -> [a]
++ forall a. [a] -> [[a]] -> [a]
intercalate String
", " (forall a b. (a -> b) -> [a] -> [b]
map forall a. Show a => a -> String
show [TemplateExpr]
as) forall a. [a] -> [a] -> [a]
++ String
")"
show (StringLiteral String
s) = forall a. Show a => a -> String
show String
s
instance Binary TemplateExpr where
put :: TemplateExpr -> Put
put (Ident TemplateKey
k) = Word8 -> Put
putWord8 Word8
0 forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall t. Binary t => t -> Put
put TemplateKey
k
put (Call TemplateKey
k [TemplateExpr]
as) = Word8 -> Put
putWord8 Word8
1 forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall t. Binary t => t -> Put
put TemplateKey
k forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall t. Binary t => t -> Put
put [TemplateExpr]
as
put (StringLiteral String
s) = Word8 -> Put
putWord8 Word8
2 forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall t. Binary t => t -> Put
put String
s
get :: Get TemplateExpr
get = Get Word8
getWord8 forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Word8
tag -> case Word8
tag of
Word8
0 -> TemplateKey -> TemplateExpr
Ident forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall t. Binary t => Get t
get
Word8
1 -> TemplateKey -> [TemplateExpr] -> TemplateExpr
Call forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall t. Binary t => Get t
get forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall t. Binary t => Get t
get
Word8
2 -> String -> TemplateExpr
StringLiteral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall t. Binary t => Get t
get
Word8
_ -> forall a. HasCallStack => String -> a
error String
"Hakyll.Web.Template.Internal: Error reading cached template"
parseTemplateElemsFile :: FilePath -> String -> Either String [TemplateElement]
parseTemplateElemsFile :: String -> String -> Either String [TemplateElement]
parseTemplateElemsFile String
file = forall (a :: * -> * -> *) b c d.
ArrowChoice a =>
a b c -> a (Either b d) (Either c d)
left (\ParseError
e -> String
"Cannot parse template " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show ParseError
e)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s t a.
Stream s Identity t =>
Parsec s () a -> String -> s -> Either ParseError a
P.parse (ParsecT String () Identity [TemplateElement]
templateElems forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* forall s (m :: * -> *) t u.
(Stream s m t, Show t) =>
ParsecT s u m ()
P.eof) String
file
templateElems :: P.Parser [TemplateElement]
templateElems :: ParsecT String () Identity [TemplateElement]
templateElems = forall a. Monoid a => [a] -> a
mconcat forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
P.many (forall s (m :: * -> *) t u a.
Stream s m t =>
[ParsecT s u m a] -> ParsecT s u m a
P.choice [ forall {a}.
ParsecT String () Identity a -> ParsecT String () Identity [a]
lift Parser TemplateElement
chunk
, forall {a}.
ParsecT String () Identity a -> ParsecT String () Identity [a]
lift Parser TemplateElement
escaped
, ParsecT String () Identity [TemplateElement]
conditional
, ParsecT String () Identity [TemplateElement]
for
, ParsecT String () Identity [TemplateElement]
partial
, ParsecT String () Identity [TemplateElement]
expr
])
where lift :: ParsecT String () Identity a -> ParsecT String () Identity [a]
lift = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall a. a -> [a] -> [a]
:[])
chunk :: P.Parser TemplateElement
chunk :: Parser TemplateElement
chunk = String -> TemplateElement
Chunk forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
P.many1 (forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m Char
P.noneOf String
"$")
expr :: P.Parser [TemplateElement]
expr :: ParsecT String () Identity [TemplateElement]
expr = forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
P.try forall a b. (a -> b) -> a -> b
$ do
Bool
trimLExpr <- Parser Bool
trimOpen
TemplateExpr
e <- Parser TemplateExpr
expr'
Bool
trimRExpr <- Parser Bool
trimClose
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ [TemplateElement
TrimL | Bool
trimLExpr] forall a. [a] -> [a] -> [a]
++ [TemplateExpr -> TemplateElement
Expr TemplateExpr
e] forall a. [a] -> [a] -> [a]
++ [TemplateElement
TrimR | Bool
trimRExpr]
expr' :: P.Parser TemplateExpr
expr' :: Parser TemplateExpr
expr' = Parser TemplateExpr
stringLiteral forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Parser TemplateExpr
call forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Parser TemplateExpr
ident
escaped :: P.Parser TemplateElement
escaped :: Parser TemplateElement
escaped = TemplateElement
Escaped forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
P.try (forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m String
P.string String
"$$")
trimOpen :: P.Parser Bool
trimOpen :: Parser Bool
trimOpen = do
forall (f :: * -> *) a. Functor f => f a -> f ()
void forall a b. (a -> b) -> a -> b
$ forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
P.char Char
'$'
Maybe Char
trimLIf <- forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m (Maybe a)
P.optionMaybe forall a b. (a -> b) -> a -> b
$ forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
P.try (forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
P.char Char
'-')
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a. Maybe a -> Bool
isJust Maybe Char
trimLIf
trimClose :: P.Parser Bool
trimClose :: Parser Bool
trimClose = do
Maybe Char
trimIfR <- forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m (Maybe a)
P.optionMaybe forall a b. (a -> b) -> a -> b
$ (forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
P.char Char
'-')
forall (f :: * -> *) a. Functor f => f a -> f ()
void forall a b. (a -> b) -> a -> b
$ forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
P.char Char
'$'
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a. Maybe a -> Bool
isJust Maybe Char
trimIfR
conditional :: P.Parser [TemplateElement]
conditional :: ParsecT String () Identity [TemplateElement]
conditional = forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
P.try forall a b. (a -> b) -> a -> b
$ do
Bool
trimLIf <- Parser Bool
trimOpen
forall (f :: * -> *) a. Functor f => f a -> f ()
void forall a b. (a -> b) -> a -> b
$ forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m String
P.string String
"if("
TemplateExpr
e <- Parser TemplateExpr
expr'
forall (f :: * -> *) a. Functor f => f a -> f ()
void forall a b. (a -> b) -> a -> b
$ forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
P.char Char
')'
Bool
trimRIf <- Parser Bool
trimClose
[TemplateElement]
thenBranch <- ParsecT String () Identity [TemplateElement]
templateElems
Maybe (Bool, [TemplateElement], Bool)
elseParse <- String -> Parser (Maybe (Bool, [TemplateElement], Bool))
opt String
"else"
Bool
trimLEnd <- Parser Bool
trimOpen
forall (f :: * -> *) a. Functor f => f a -> f ()
void forall a b. (a -> b) -> a -> b
$ forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m String
P.string String
"endif"
Bool
trimREnd <- Parser Bool
trimClose
let ([TemplateElement]
thenBody, Maybe [TemplateElement]
elseBody) = forall b a. b -> (a -> b) -> Maybe a -> b
maybe ([TemplateElement]
thenNoElse, forall a. Maybe a
Nothing) (Bool, [TemplateElement], Bool)
-> ([TemplateElement], Maybe [TemplateElement])
thenElse Maybe (Bool, [TemplateElement], Bool)
elseParse
where thenNoElse :: [TemplateElement]
thenNoElse =
[TemplateElement
TrimR | Bool
trimRIf] forall a. [a] -> [a] -> [a]
++ [TemplateElement]
thenBranch forall a. [a] -> [a] -> [a]
++ [TemplateElement
TrimL | Bool
trimLEnd]
thenElse :: (Bool, [TemplateElement], Bool)
-> ([TemplateElement], Maybe [TemplateElement])
thenElse (Bool
trimLElse, [TemplateElement]
elseBranch, Bool
trimRElse) = ([TemplateElement]
thenB, Maybe [TemplateElement]
elseB)
where thenB :: [TemplateElement]
thenB = [TemplateElement
TrimR | Bool
trimRIf]
forall a. [a] -> [a] -> [a]
++ [TemplateElement]
thenBranch
forall a. [a] -> [a] -> [a]
++ [TemplateElement
TrimL | Bool
trimLElse]
elseB :: Maybe [TemplateElement]
elseB = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ [TemplateElement
TrimR | Bool
trimRElse]
forall a. [a] -> [a] -> [a]
++ [TemplateElement]
elseBranch
forall a. [a] -> [a] -> [a]
++ [TemplateElement
TrimL | Bool
trimLEnd]
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ [TemplateElement
TrimL | Bool
trimLIf] forall a. [a] -> [a] -> [a]
++ [TemplateExpr
-> [TemplateElement] -> Maybe [TemplateElement] -> TemplateElement
If TemplateExpr
e [TemplateElement]
thenBody Maybe [TemplateElement]
elseBody] forall a. [a] -> [a] -> [a]
++ [TemplateElement
TrimR | Bool
trimREnd]
for :: P.Parser [TemplateElement]
for :: ParsecT String () Identity [TemplateElement]
for = forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
P.try forall a b. (a -> b) -> a -> b
$ do
Bool
trimLFor <- Parser Bool
trimOpen
forall (f :: * -> *) a. Functor f => f a -> f ()
void forall a b. (a -> b) -> a -> b
$ forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m String
P.string String
"for("
TemplateExpr
e <- Parser TemplateExpr
expr'
forall (f :: * -> *) a. Functor f => f a -> f ()
void forall a b. (a -> b) -> a -> b
$ forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
P.char Char
')'
Bool
trimRFor <- Parser Bool
trimClose
[TemplateElement]
bodyBranch <- ParsecT String () Identity [TemplateElement]
templateElems
Maybe (Bool, [TemplateElement], Bool)
sepParse <- String -> Parser (Maybe (Bool, [TemplateElement], Bool))
opt String
"sep"
Bool
trimLEnd <- Parser Bool
trimOpen
forall (f :: * -> *) a. Functor f => f a -> f ()
void forall a b. (a -> b) -> a -> b
$ forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m String
P.string String
"endfor"
Bool
trimREnd <- Parser Bool
trimClose
let ([TemplateElement]
forBody, Maybe [TemplateElement]
sepBody) = forall b a. b -> (a -> b) -> Maybe a -> b
maybe ([TemplateElement]
forNoSep, forall a. Maybe a
Nothing) (Bool, [TemplateElement], Bool)
-> ([TemplateElement], Maybe [TemplateElement])
forSep Maybe (Bool, [TemplateElement], Bool)
sepParse
where forNoSep :: [TemplateElement]
forNoSep =
[TemplateElement
TrimR | Bool
trimRFor] forall a. [a] -> [a] -> [a]
++ [TemplateElement]
bodyBranch forall a. [a] -> [a] -> [a]
++ [TemplateElement
TrimL | Bool
trimLEnd]
forSep :: (Bool, [TemplateElement], Bool)
-> ([TemplateElement], Maybe [TemplateElement])
forSep (Bool
trimLSep, [TemplateElement]
sepBranch, Bool
trimRSep) = ([TemplateElement]
forB, Maybe [TemplateElement]
sepB)
where forB :: [TemplateElement]
forB = [TemplateElement
TrimR | Bool
trimRFor]
forall a. [a] -> [a] -> [a]
++ [TemplateElement]
bodyBranch
forall a. [a] -> [a] -> [a]
++ [TemplateElement
TrimL | Bool
trimLSep]
sepB :: Maybe [TemplateElement]
sepB = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ [TemplateElement
TrimR | Bool
trimRSep]
forall a. [a] -> [a] -> [a]
++ [TemplateElement]
sepBranch
forall a. [a] -> [a] -> [a]
++ [TemplateElement
TrimL | Bool
trimLEnd]
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ [TemplateElement
TrimL | Bool
trimLFor] forall a. [a] -> [a] -> [a]
++ [TemplateExpr
-> [TemplateElement] -> Maybe [TemplateElement] -> TemplateElement
For TemplateExpr
e [TemplateElement]
forBody Maybe [TemplateElement]
sepBody] forall a. [a] -> [a] -> [a]
++ [TemplateElement
TrimR | Bool
trimREnd]
partial :: P.Parser [TemplateElement]
partial :: ParsecT String () Identity [TemplateElement]
partial = forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
P.try forall a b. (a -> b) -> a -> b
$ do
Bool
trimLPart <- Parser Bool
trimOpen
forall (f :: * -> *) a. Functor f => f a -> f ()
void forall a b. (a -> b) -> a -> b
$ forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m String
P.string String
"partial("
TemplateExpr
e <- Parser TemplateExpr
expr'
forall (f :: * -> *) a. Functor f => f a -> f ()
void forall a b. (a -> b) -> a -> b
$ forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
P.char Char
')'
Bool
trimRPart <- Parser Bool
trimClose
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ [TemplateElement
TrimL | Bool
trimLPart] forall a. [a] -> [a] -> [a]
++ [TemplateExpr -> TemplateElement
Partial TemplateExpr
e] forall a. [a] -> [a] -> [a]
++ [TemplateElement
TrimR | Bool
trimRPart]
ident :: P.Parser TemplateExpr
ident :: Parser TemplateExpr
ident = forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
P.try forall a b. (a -> b) -> a -> b
$ TemplateKey -> TemplateExpr
Ident forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser TemplateKey
key
call :: P.Parser TemplateExpr
call :: Parser TemplateExpr
call = forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
P.try forall a b. (a -> b) -> a -> b
$ do
TemplateKey
f <- Parser TemplateKey
key
forall (f :: * -> *) a. Functor f => f a -> f ()
void forall a b. (a -> b) -> a -> b
$ forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
P.char Char
'('
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
P.spaces
[TemplateExpr]
as <- forall s (m :: * -> *) t u a sep.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a]
P.sepBy Parser TemplateExpr
expr' (forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
P.spaces forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
P.char Char
',' forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
P.spaces)
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
P.spaces
forall (f :: * -> *) a. Functor f => f a -> f ()
void forall a b. (a -> b) -> a -> b
$ forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
P.char Char
')'
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ TemplateKey -> [TemplateExpr] -> TemplateExpr
Call TemplateKey
f [TemplateExpr]
as
stringLiteral :: P.Parser TemplateExpr
stringLiteral :: Parser TemplateExpr
stringLiteral = do
forall (f :: * -> *) a. Functor f => f a -> f ()
void forall a b. (a -> b) -> a -> b
$ forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
P.char Char
'\"'
String
str <- forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
P.many forall a b. (a -> b) -> a -> b
$ do
Char
x <- forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m Char
P.noneOf String
"\""
if Char
x forall a. Eq a => a -> a -> Bool
== Char
'\\' then forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
P.anyChar else forall (m :: * -> *) a. Monad m => a -> m a
return Char
x
forall (f :: * -> *) a. Functor f => f a -> f ()
void forall a b. (a -> b) -> a -> b
$ forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
P.char Char
'\"'
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ String -> TemplateExpr
StringLiteral String
str
key :: P.Parser TemplateKey
key :: Parser TemplateKey
key = String -> TemplateKey
TemplateKey forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT String () Identity String
metadataKey
opt :: String -> P.Parser (Maybe (Bool, [TemplateElement], Bool))
opt :: String -> Parser (Maybe (Bool, [TemplateElement], Bool))
opt String
clause = forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m (Maybe a)
P.optionMaybe forall a b. (a -> b) -> a -> b
$ forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
P.try forall a b. (a -> b) -> a -> b
$ do
Bool
trimL <- Parser Bool
trimOpen
forall (f :: * -> *) a. Functor f => f a -> f ()
void forall a b. (a -> b) -> a -> b
$ forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m String
P.string String
clause
Bool
trimR <- Parser Bool
trimClose
[TemplateElement]
branch <- ParsecT String () Identity [TemplateElement]
templateElems
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Bool
trimL, [TemplateElement]
branch, Bool
trimR)