Skip to content

Commit

Permalink
Make ‘renderMustache’ throw exceptions on missing values
Browse files Browse the repository at this point in the history
  • Loading branch information
mrkkrp committed Dec 9, 2016
1 parent ae4a8f0 commit 540a4b7
Show file tree
Hide file tree
Showing 9 changed files with 96 additions and 42 deletions.
5 changes: 5 additions & 0 deletions CHANGELOG.md
@@ -1,5 +1,10 @@
## Stache 0.2.0

* Breaking change: the `renderMustache` function will throw an exception
when referenced key was not provided. This is a better behavior than
silent interpolation of an empty string, because missing values are almost
always a mistake and it's easy to provide empty strings explicitly anyway.

* Allowed `directory-1.3.0.0`.

## Stache 0.1.8
Expand Down
2 changes: 1 addition & 1 deletion Text/Mustache/Compile.hs
Expand Up @@ -102,5 +102,5 @@ pathToPName = PName . T.pack . F.takeBaseName
withException :: MonadThrow m
=> Either (ParseError Char Dec) Template -- ^ Value to process
-> m Template -- ^ The result
withException = either (throwM . MustacheException) return
withException = either (throwM . MustacheParserException) return
{-# INLINE withException #-}
16 changes: 12 additions & 4 deletions Text/Mustache/Render.hs
Expand Up @@ -18,13 +18,13 @@ module Text.Mustache.Render
( renderMustache )
where

import Control.Exception (throw)
import Control.Monad.Reader
import Control.Monad.Writer.Lazy
import Data.Aeson
import Data.Foldable (asum)
import Data.List (tails)
import Data.List.NonEmpty (NonEmpty (..))
import Data.Maybe (fromMaybe)
import Data.Text (Text)
import Text.Megaparsec.Pos (Pos, unPos)
import Text.Mustache.Type
Expand Down Expand Up @@ -67,6 +67,11 @@ data RenderContext = RenderContext

-- | Render a Mustache 'Template' using Aeson's 'Value' to get actual values
-- for interpolation.
--
-- As of version 0.2.0, if referenced values are missing (which almost
-- always indicates some sort of mistake), 'MustacheRenderException' will be
-- thrown. The included 'Key' will indicate full path to missing value and
-- 'PName' will contain the name of active partial.

renderMustache :: Template -> Value -> TL.Text
renderMustache t =
Expand Down Expand Up @@ -182,10 +187,13 @@ renderMany f (n:ns) = do
lookupKey :: Key -> Render Value
lookupKey (Key []) = NE.head <$> asks rcContext
lookupKey k = do
v <- asks rcContext
p <- asks rcPrefix
v <- asks rcContext
p <- asks rcPrefix
pname <- asks (templateActual . rcTemplate)
let f x = asum (simpleLookup False (x <> k) <$> v)
(return . fromMaybe Null . asum) (fmap (f . Key) . reverse . tails $ unKey p)
case asum (fmap (f . Key) . reverse . tails $ unKey p) of
Nothing -> throw (MustacheRenderException pname (p <> k))
Just r -> return r

-- | Lookup a 'Value' by traversing another 'Value' using given 'Key' as
-- “path”.
Expand Down
35 changes: 30 additions & 5 deletions Text/Mustache/Type.hs
Expand Up @@ -15,11 +15,13 @@
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE OverloadedStrings #-}

module Text.Mustache.Type
( Template (..)
, Node (..)
, Key (..)
, showKey
, PName (..)
, MustacheException (..) )
where
Expand All @@ -41,7 +43,7 @@ import qualified Data.Text as T
-- all available templates (partials).
--
-- 'Template' is a 'Semigroup'. This means that you can combine 'Template's
-- (and their caches) using the ('<>') operator, the resulting 'Template'
-- (and their caches) using the @('<>')@ operator, the resulting 'Template'
-- will have the same currently selected template as the left one. Union of
-- caches is also left-biased.

Expand Down Expand Up @@ -82,6 +84,15 @@ newtype Key = Key { unKey :: [Text] }

instance NFData Key

-- | Pretty-print a key, this is helpful, for example, if you want to
-- display an error message.
--
-- @since 0.2.0

showKey :: Key -> Text
showKey (Key []) = "<implicit>"
showKey (Key xs) = T.intercalate "." xs

-- | Identifier for partials. Note that with the @OverloadedStrings@
-- extension you can use just string literals to create values of this type.

Expand All @@ -93,14 +104,28 @@ instance IsString PName where

instance NFData PName

-- | Exception that is thrown when parsing of a template has failed.

data MustacheException = MustacheException (ParseError Char Dec)
-- | Exception that is thrown when parsing of a template has failed or
-- referenced values were not provided.

data MustacheException
= MustacheParserException (ParseError Char Dec)
-- ^ Template parser has failed. This contains the parse error.
--
-- /Before version 0.2.0 it was called 'MustacheException'./
| MustacheRenderException PName Key
-- ^ A referenced value was not provided. The exception provides info
-- about partial in which the issue happened 'PName' and name of the
-- missing key 'Key'.
--
-- @since 0.2.0
deriving (Eq, Show, Typeable, Generic)

#if MIN_VERSION_base(4,8,0)
instance Exception MustacheException where
displayException (MustacheException e) = parseErrorPretty e
displayException (MustacheParserException e) = parseErrorPretty e
displayException (MustacheRenderException pname key) =
"Referenced value was not provided in partial \"" ++ T.unpack (unPName pname) ++
"\", key: " ++ T.unpack (showKey key)
#else
instance Exception MustacheException
#endif
34 changes: 17 additions & 17 deletions specification/interpolation.yml
Expand Up @@ -103,23 +103,23 @@ tests:

# Context Misses

- name: Basic Context Miss Interpolation
desc: Failed context lookups should default to empty strings.
data: { }
template: "I ({{cannot}}) be seen!"
expected: "I () be seen!"

- name: Triple Mustache Context Miss Interpolation
desc: Failed context lookups should default to empty strings.
data: { }
template: "I ({{{cannot}}}) be seen!"
expected: "I () be seen!"

- name: Ampersand Context Miss Interpolation
desc: Failed context lookups should default to empty strings.
data: { }
template: "I ({{&cannot}}) be seen!"
expected: "I () be seen!"
# - name: Basic Context Miss Interpolation
# desc: Failed context lookups should default to empty strings.
# data: { }
# template: "I ({{cannot}}) be seen!"
# expected: "I () be seen!"

# - name: Triple Mustache Context Miss Interpolation
# desc: Failed context lookups should default to empty strings.
# data: { }
# template: "I ({{{cannot}}}) be seen!"
# expected: "I () be seen!"

# - name: Ampersand Context Miss Interpolation
# desc: Failed context lookups should default to empty strings.
# data: { }
# template: "I ({{&cannot}}) be seen!"
# expected: "I () be seen!"

# Dotted Names

Expand Down
10 changes: 5 additions & 5 deletions specification/inverted.yml
Expand Up @@ -92,11 +92,11 @@ tests:
template: "| A {{^bool}}B {{^bool}}C{{/bool}} D{{/bool}} E |"
expected: "| A E |"

- name: Context Misses
desc: Failed context lookups should be considered falsey.
data: { }
template: "[{{^missing}}Cannot find key 'missing'!{{/missing}}]"
expected: "[Cannot find key 'missing'!]"
# - name: Context Misses
# desc: Failed context lookups should be considered falsey.
# data: { }
# template: "[{{^missing}}Cannot find key 'missing'!{{/missing}}]"
# expected: "[Cannot find key 'missing'!]"

# Dotted Names

Expand Down
10 changes: 5 additions & 5 deletions specification/sections.yml
Expand Up @@ -132,11 +132,11 @@ tests:
template: "| A {{#bool}}B {{#bool}}C{{/bool}} D{{/bool}} E |"
expected: "| A E |"

- name: Context Misses
desc: Failed context lookups should be considered falsey.
data: { }
template: "[{{#missing}}Found key 'missing'!{{/missing}}]"
expected: "[]"
# - name: Context Misses
# desc: Failed context lookups should be considered falsey.
# data: { }
# template: "[{{#missing}}Found key 'missing'!{{/missing}}]"
# expected: "[]"

# Implicit Iterators

Expand Down
15 changes: 11 additions & 4 deletions tests/Text/Mustache/RenderSpec.hs
Expand Up @@ -6,6 +6,7 @@ module Text.Mustache.RenderSpec
, spec )
where

import Control.Exception (evaluate)
import Data.Aeson (object, KeyValue (..), Value (..))
import Data.Text (Text)
import Test.Hspec
Expand Down Expand Up @@ -40,8 +41,13 @@ spec = describe "renderMustache" $ do
context "when rendering a section" $ do
let nodes = [Section (key "foo") [UnescapedVar (key "bar"), TextBlock "*"]]
context "when the key is not present" $
it "renders nothing" $
r nodes (object []) `shouldBe` ""
it "throws the correct exception" $
evaluate (r nodes (object [])) `shouldThrow`
(== MustacheRenderException "test" (key "foo"))
context "when the key is not present inside a section" $
it "throws the correct exception" $
evaluate (r nodes (object ["foo" .= ([1] :: [Int])])) `shouldThrow`
(== MustacheRenderException "test" (Key ["foo","bar"]))
context "when the key is present" $ do
context "when the key is a “false” value" $ do
it "skips the Null value" $
Expand Down Expand Up @@ -97,8 +103,9 @@ spec = describe "renderMustache" $ do
context "when rendering an inverted section" $ do
let nodes = [InvertedSection (key "foo") [TextBlock "Here!"]]
context "when the key is not present" $
it "renders the inverse section" $
r nodes (object []) `shouldBe` "Here!"
it "throws the correct exception" $
evaluate (r nodes (object [])) `shouldThrow`
(== MustacheRenderException "test" (key "foo"))
context "when the key is present" $ do
context "when the key is a “false” value" $ do
it "renders with Null value" $
Expand Down
11 changes: 10 additions & 1 deletion tests/Text/Mustache/TypeSpec.hs
Expand Up @@ -14,7 +14,7 @@ main :: IO ()
main = hspec spec

spec :: Spec
spec =
spec = do
describe "Template instances" $
context "the Semigroup instance" $ do
it "the resulting template inherits focus of the left one" $
Expand All @@ -26,6 +26,15 @@ spec =
[ ("c", [TextBlock "foo"])
, ("d", [TextBlock "bar"])
, ("e", [TextBlock "baz"]) ]
describe "showKey" $ do
context "when the key has no elements in it" $
it "is rendered correctly" $
showKey (Key []) `shouldBe` "<implicit>"
context "when the key has some elements" $
it "is rendered correctly" $ do
showKey (Key ["boo"]) `shouldBe` "boo"
showKey (Key ["foo","bar"]) `shouldBe` "foo.bar"
showKey (Key ["baz","baz","quux"]) `shouldBe` "baz.baz.quux"

templateA :: Template
templateA = Template "a" $ M.fromList
Expand Down

0 comments on commit 540a4b7

Please sign in to comment.