implement simple harmless "true check" to mustache

This commit is contained in:
Mirek Kratochvil 2023-05-27 20:21:15 +02:00
parent 73498534cf
commit 08742b6b31
4 changed files with 32 additions and 10 deletions

View file

@ -118,6 +118,7 @@ getPartials = join . fmap getPartials'
getPartials' :: Node Text -> [FilePath]
getPartials' (Partial _ p) = return p
getPartials' (Section _ n) = getPartials n
getPartials' (ExistingSection _ n) = getPartials n
getPartials' (InvertedSection _ n) = getPartials n
getPartials' _ = mempty

View file

@ -28,7 +28,6 @@ import qualified Data.Text.Lazy as LT
import qualified Data.Vector as V
import Data.Word (Word8, Word16, Word32, Word64)
import Language.Haskell.TH.Lift (deriveLift)
import Language.Haskell.TH.Syntax
import Numeric.Natural (Natural)
@ -101,6 +100,7 @@ type ASTree α = [Node α]
data Node α
= TextBlock α
| Section DataIdentifier (ASTree α)
| ExistingSection DataIdentifier (ASTree α)
| InvertedSection DataIdentifier (ASTree α)
| Variable Bool DataIdentifier
| Partial (Maybe α) FilePath

View file

@ -38,7 +38,6 @@ module Text.Mustache.Parser
import Control.Monad
import Data.Char (isAlphaNum, isSpace)
import Data.List (nub)
import Data.Monoid ((<>))
import Data.Text as T (Text, null, pack)
import Prelude as Prel
import Text.Mustache.Types
@ -60,8 +59,10 @@ data MustacheState = MustacheState
}
data SectionStart = Normal | Existing | Inverted
data ParseTagRes
= SectionBegin Bool DataIdentifier
= SectionBegin SectionStart DataIdentifier
| SectionEnd DataIdentifier
| Tag (Node Text)
| HandledTag
@ -79,6 +80,9 @@ partialBegin = '>'
-- | @^@
invertedSectionBegin :: Char
invertedSectionBegin = '^'
-- | @^@
existingSectionBegin :: Char
existingSectionBegin = '?'
-- | @{@ and @}@
unescape2 :: (Char, Char)
unescape2 = ('{', '}')
@ -223,16 +227,16 @@ parseLine = do
continueFromTag :: ParseTagRes -> Parser STree
continueFromTag (SectionBegin inverted name) = do
continueFromTag (SectionBegin start name) = do
textNodes <- flushText
state@(MustacheState
{ currentSectionName = previousSection }) <- getState
putState $ state { currentSectionName = return name }
innerSectionContent <- parseText
let sectionTag =
if inverted
then InvertedSection
else Section
let sectionTag = case start of
Normal -> Section
Inverted -> InvertedSection
Existing -> ExistingSection
modifyState $ \s -> s { currentSectionName = previousSection }
outerSectionContent <- parseText
return (textNodes <> [sectionTag name innerSectionContent] <> outerSectionContent)
@ -255,7 +259,7 @@ switchOnTag = do
(MustacheState { sDelimiters = ( _, end )}) <- getState
choice
[ SectionBegin False <$> (try (char sectionBegin) >> genParseTagEnd mempty)
[ SectionBegin Normal <$> (try (char sectionBegin) >> genParseTagEnd mempty)
, SectionEnd
<$> (try (char sectionEnd) >> genParseTagEnd mempty)
, Tag . Variable False
@ -266,7 +270,12 @@ switchOnTag = do
<$> (try (char partialBegin) >> spaces >> (noneOf (nub end) `manyTill` try (spaces >> string end)))
, return HandledTag
<< (try (char delimiterChange) >> parseDelimChange)
, SectionBegin True
, SectionBegin Existing
<$> (try (char existingSectionBegin) >> genParseTagEnd mempty >>= \case
n@(NamedData _) -> return n
_ -> parserFail "Existing Sections can not be implicit."
)
, SectionBegin Inverted
<$> (try (char invertedSectionBegin) >> genParseTagEnd mempty >>= \case
n@(NamedData _) -> return n
_ -> parserFail "Inverted Sections can not be implicit."

View file

@ -148,6 +148,18 @@ substituteNode (Section (NamedData secName) secSTree) =
shiftContext newContext $ substituteAST secSTree
Nothing -> tellError $ SectionTargetNotFound secName
-- substituting an existing section (exact invert of the inverted section)
substituteNode (ExistingSection Implicit _) = tellError InvertedImplicitSection
substituteNode (ExistingSection (NamedData secName) invSecSTree) =
search secName >>= \case
Just (Bool False) -> return ()
Just (Array a) | V.null a -> return ()
Just Null -> return ()
Nothing -> return ()
_ -> contents
where
contents = mapM_ substituteNode invSecSTree
-- substituting an inverted section
substituteNode (InvertedSection Implicit _) = tellError InvertedImplicitSection
substituteNode (InvertedSection (NamedData secName) invSecSTree) =