Skip to content

Commit

Permalink
feature: A bit of a parsing incident
Browse files Browse the repository at this point in the history
  • Loading branch information
supki committed Oct 8, 2024
1 parent fb1972d commit c10baab
Show file tree
Hide file tree
Showing 2 changed files with 11 additions and 3 deletions.
4 changes: 2 additions & 2 deletions src/T/Parse.hs
Original file line number Diff line number Diff line change
Expand Up @@ -69,7 +69,7 @@ parseBytes stdlib =

parseDelta :: Stdlib -> Delta -> ByteString -> Either ParseError Tmpl
parseDelta stdlib delta str =
case parseByteString (runReaderT parser stdlib) delta str of
case parseByteString (runReaderT (parser <* eof) stdlib) delta str of
Failure err ->
Left (ParseError err._errDoc)
Success tmpl ->
Expand Down Expand Up @@ -383,7 +383,7 @@ parseRaw =
-- Attempt to fish for a line block.
, do _ <- lookAhead (try (spacesExceptNewline *> string "{%" *> manyTill anyChar (try (string "%}")) *> spacesExceptNewline *> newline))
pure acc
-- Attempt to fish for a inline block.
-- Attempt to fish for an inline block.
, do _ <- lookAhead (string "{{" <|> string "{%")
pure acc
, do x <- anyChar
Expand Down
10 changes: 9 additions & 1 deletion test/T/ParseSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,7 @@
{-# LANGUAGE OverloadedRecordDot #-}
module T.ParseSpec (spec) where

import Data.Either (isLeft)
import Data.HashMap.Strict qualified as HashMap
import Data.Vector qualified as Vector
import Test.Hspec
Expand Down Expand Up @@ -192,6 +193,9 @@ spec =
]
(Tmpl.Cat []))

it "fake block" $
parse "{% fake %}" `shouldSatisfy` isLeft

var :: Name -> Exp
var name =
varE (noann name)
Expand Down Expand Up @@ -238,4 +242,8 @@ whenIf p thenTmpl =

shouldParseTo :: HasCallStack => Text -> Tmpl -> Expectation
tmpl `shouldParseTo` res =
first show (parseText Stdlib.def tmpl) `shouldBe` Right res
parse tmpl `shouldBe` Right res

parse :: Text -> Either String Tmpl
parse tmpl =
first show (parseText Stdlib.def tmpl)

0 comments on commit c10baab

Please sign in to comment.