remove tests from mustache
This commit is contained in:
parent
b9b6c1ed5a
commit
5f0b66e363
|
@ -27,9 +27,6 @@ tested-with:
|
||||||
extra-source-files:
|
extra-source-files:
|
||||||
README.md
|
README.md
|
||||||
CHANGELOG.md
|
CHANGELOG.md
|
||||||
test/unit/examples/test-template-partials.txt.mustache
|
|
||||||
test/unit/examples/test-template.txt.mustache
|
|
||||||
test/unit/examples/partials/test-partial.txt.mustache
|
|
||||||
|
|
||||||
source-repository head
|
source-repository head
|
||||||
type: git
|
type: git
|
||||||
|
@ -93,49 +90,3 @@ executable haskell-mustache
|
||||||
, text
|
, text
|
||||||
, yaml
|
, yaml
|
||||||
default-language: Haskell2010
|
default-language: Haskell2010
|
||||||
|
|
||||||
test-suite language-specifications
|
|
||||||
type: exitcode-stdio-1.0
|
|
||||||
main-is: Language.hs
|
|
||||||
other-modules:
|
|
||||||
Paths_mustache
|
|
||||||
hs-source-dirs:
|
|
||||||
test/integration
|
|
||||||
build-depends:
|
|
||||||
aeson
|
|
||||||
, base >=4.7 && <5
|
|
||||||
, base-unicode-symbols
|
|
||||||
, bytestring
|
|
||||||
, filepath
|
|
||||||
, hspec
|
|
||||||
, lens
|
|
||||||
, mustache
|
|
||||||
, tar
|
|
||||||
, text
|
|
||||||
, unordered-containers
|
|
||||||
, wreq
|
|
||||||
, yaml
|
|
||||||
, zlib
|
|
||||||
default-language: Haskell2010
|
|
||||||
|
|
||||||
test-suite unit-tests
|
|
||||||
type: exitcode-stdio-1.0
|
|
||||||
main-is: Spec.hs
|
|
||||||
other-modules:
|
|
||||||
Paths_mustache
|
|
||||||
hs-source-dirs:
|
|
||||||
test/unit
|
|
||||||
build-depends:
|
|
||||||
aeson
|
|
||||||
, base >=4.7 && <5
|
|
||||||
, bytestring
|
|
||||||
, directory
|
|
||||||
, filepath
|
|
||||||
, hspec
|
|
||||||
, mustache
|
|
||||||
, process
|
|
||||||
, temporary
|
|
||||||
, text
|
|
||||||
, unordered-containers
|
|
||||||
, yaml
|
|
||||||
default-language: Haskell2010
|
|
||||||
|
|
|
@ -1,110 +0,0 @@
|
||||||
{-# LANGUAGE LambdaCase #-}
|
|
||||||
{-# LANGUAGE NamedFieldPuns #-}
|
|
||||||
{-# LANGUAGE OverloadedStrings #-}
|
|
||||||
{-# LANGUAGE RecordWildCards #-}
|
|
||||||
{-# LANGUAGE TupleSections #-}
|
|
||||||
{-# LANGUAGE UnicodeSyntax #-}
|
|
||||||
module Main where
|
|
||||||
|
|
||||||
import qualified Codec.Archive.Tar as Tar
|
|
||||||
import qualified Codec.Compression.GZip as GZip
|
|
||||||
import Control.Applicative ((<$>), (<*>))
|
|
||||||
import Control.Lens
|
|
||||||
import Control.Monad
|
|
||||||
import Data.ByteString.Lazy (toStrict)
|
|
||||||
import Data.Foldable (for_)
|
|
||||||
import qualified Data.HashMap.Strict as HM (HashMap, empty,
|
|
||||||
traverseWithKey)
|
|
||||||
import Data.List
|
|
||||||
import Data.Maybe (fromMaybe)
|
|
||||||
import qualified Data.Text as T
|
|
||||||
import Data.Yaml as Y (FromJSON, Value (..), decode,
|
|
||||||
parseJSON, (.!=), (.:), (.:?))
|
|
||||||
import Network.Wreq
|
|
||||||
import System.FilePath
|
|
||||||
import Test.Hspec
|
|
||||||
import Text.Mustache
|
|
||||||
|
|
||||||
|
|
||||||
langspecs :: [String]
|
|
||||||
langspecs =
|
|
||||||
[ "https://codeload.github.com/andrewthad/spec/legacy.tar.gz/add_list_context_check"
|
|
||||||
, "https://codeload.github.com/mustache/spec/tar.gz/v1.1.3"
|
|
||||||
]
|
|
||||||
|
|
||||||
|
|
||||||
data LangSpecFile = LangSpecFile
|
|
||||||
{ overview :: String
|
|
||||||
, tests :: [LangSpecTest]
|
|
||||||
}
|
|
||||||
|
|
||||||
|
|
||||||
data LangSpecTest = LangSpecTest
|
|
||||||
{ name :: String
|
|
||||||
, specDescription :: String
|
|
||||||
, specData :: Y.Value
|
|
||||||
, template :: T.Text
|
|
||||||
, expected :: T.Text
|
|
||||||
, testPartials :: HM.HashMap String T.Text
|
|
||||||
}
|
|
||||||
|
|
||||||
|
|
||||||
instance FromJSON LangSpecFile where
|
|
||||||
parseJSON (Y.Object o) = LangSpecFile
|
|
||||||
<$> o .: "overview"
|
|
||||||
<*> o .: "tests"
|
|
||||||
parseJSON _ = mzero
|
|
||||||
|
|
||||||
|
|
||||||
instance FromJSON LangSpecTest where
|
|
||||||
parseJSON (Y.Object o) = LangSpecTest
|
|
||||||
<$> o .: "name"
|
|
||||||
<*> o .: "desc"
|
|
||||||
<*> o .: "data"
|
|
||||||
<*> o .: "template"
|
|
||||||
<*> o .: "expected"
|
|
||||||
<*> o .:? "partials" .!= HM.empty
|
|
||||||
parseJSON _ = mzero
|
|
||||||
|
|
||||||
|
|
||||||
getOfficialSpecRelease :: String -> IO [(String, LangSpecFile)]
|
|
||||||
getOfficialSpecRelease releaseURL = do
|
|
||||||
res <- get releaseURL
|
|
||||||
let archive = Tar.read $ GZip.decompress (res ^. responseBody)
|
|
||||||
return $ Tar.foldEntries handleEntry [] (error . show) archive
|
|
||||||
where
|
|
||||||
handleEntry e acc =
|
|
||||||
case content of
|
|
||||||
Tar.NormalFile f _
|
|
||||||
| takeExtension filename `elem` [".yml", ".yaml"]
|
|
||||||
&& not ("~" `isPrefixOf` takeFileName filename) ->
|
|
||||||
(filename, fromMaybe (error $ "Error parsing spec file " ++ filename) $ decode $ toStrict f):acc
|
|
||||||
_ -> acc
|
|
||||||
where
|
|
||||||
filename = Tar.entryPath e
|
|
||||||
content = Tar.entryContent e
|
|
||||||
|
|
||||||
|
|
||||||
testOfficialLangSpec :: [(String, LangSpecFile)] -> Spec
|
|
||||||
testOfficialLangSpec testfiles =
|
|
||||||
for_ testfiles $ \(filename, LangSpecFile { tests }) ->
|
|
||||||
describe ("File: " ++ takeFileName filename) $
|
|
||||||
for_ tests $ \(LangSpecTest { .. }) ->
|
|
||||||
it ("Name: " ++ name ++ " Description: " ++ specDescription) $
|
|
||||||
let
|
|
||||||
compiled = do
|
|
||||||
partials' <- HM.traverseWithKey compileTemplate testPartials
|
|
||||||
template' <- compileTemplate name template
|
|
||||||
return $ template' { partials = partials' }
|
|
||||||
in
|
|
||||||
case compiled of
|
|
||||||
Left m -> expectationFailure $ show m
|
|
||||||
Right tmp ->
|
|
||||||
substituteValue tmp (toMustache specData) `shouldBe` expected
|
|
||||||
|
|
||||||
|
|
||||||
main :: IO ()
|
|
||||||
main =
|
|
||||||
void $ do
|
|
||||||
specs <- mapM getOfficialSpecRelease langspecs
|
|
||||||
hspec $ mapM_ testOfficialLangSpec specs
|
|
|
@ -1,260 +0,0 @@
|
||||||
{-# OPTIONS_GHC -fno-warn-orphans #-}
|
|
||||||
{-# LANGUAGE LambdaCase #-}
|
|
||||||
{-# LANGUAGE NamedFieldPuns #-}
|
|
||||||
{-# LANGUAGE OverloadedStrings #-}
|
|
||||||
{-# LANGUAGE QuasiQuotes #-}
|
|
||||||
{-# LANGUAGE TemplateHaskell #-}
|
|
||||||
module Main where
|
|
||||||
|
|
||||||
|
|
||||||
import Control.Applicative ((<$>), (<*>))
|
|
||||||
import Data.Either
|
|
||||||
import Data.Function (on)
|
|
||||||
import Data.Monoid
|
|
||||||
import qualified Data.Text as T
|
|
||||||
import System.IO.Unsafe (unsafePerformIO)
|
|
||||||
import Test.Hspec
|
|
||||||
import Text.Mustache
|
|
||||||
import Text.Mustache.Compile
|
|
||||||
import Text.Mustache.Parser
|
|
||||||
import Text.Mustache.Types
|
|
||||||
|
|
||||||
|
|
||||||
escaped :: Bool
|
|
||||||
escaped = True
|
|
||||||
unescaped :: Bool
|
|
||||||
unescaped = False
|
|
||||||
|
|
||||||
|
|
||||||
parserSpec :: Spec
|
|
||||||
parserSpec =
|
|
||||||
describe "mustacheParser" $ do
|
|
||||||
let lparse = parse "testsuite"
|
|
||||||
let returnedOne = return . return
|
|
||||||
|
|
||||||
let text = "test12356p0--=-34{}jnv,\n"
|
|
||||||
|
|
||||||
it "parses text" $
|
|
||||||
lparse text `shouldBe` returnedOne (TextBlock text)
|
|
||||||
|
|
||||||
it "parses a variable" $
|
|
||||||
lparse "{{name}}" `shouldBe` returnedOne (Variable escaped (NamedData ["name"]))
|
|
||||||
|
|
||||||
it "parses a variable with whitespace" $
|
|
||||||
lparse "{{ name }}" `shouldBe` returnedOne (Variable escaped (NamedData ["name"]))
|
|
||||||
|
|
||||||
it "allows '-' in variable names" $
|
|
||||||
lparse "{{ name-name }}" `shouldBe`
|
|
||||||
returnedOne (Variable True (NamedData ["name-name"]))
|
|
||||||
|
|
||||||
it "allows '_' in variable names" $
|
|
||||||
lparse "{{ name_name }}" `shouldBe`
|
|
||||||
returnedOne (Variable True (NamedData ["name_name"]))
|
|
||||||
|
|
||||||
it "parses a variable unescaped with {{{}}}" $
|
|
||||||
lparse "{{{name}}}" `shouldBe` returnedOne (Variable unescaped (NamedData ["name"]))
|
|
||||||
|
|
||||||
it "parses a variable unescaped with {{{}}} with whitespace" $
|
|
||||||
lparse "{{{ name }}}" `shouldBe`
|
|
||||||
returnedOne (Variable False (NamedData ["name"]))
|
|
||||||
|
|
||||||
it "parses a variable unescaped with &" $
|
|
||||||
lparse "{{&name}}" `shouldBe` returnedOne (Variable unescaped (NamedData ["name"]))
|
|
||||||
|
|
||||||
it "parses a variable unescaped with & with whitespace" $
|
|
||||||
lparse "{{& name }}" `shouldBe`
|
|
||||||
returnedOne (Variable False (NamedData ["name"]))
|
|
||||||
|
|
||||||
it "parses a partial" $
|
|
||||||
lparse "{{>myPartial}}" `shouldBe`
|
|
||||||
returnedOne (Partial (Just "") "myPartial")
|
|
||||||
|
|
||||||
it "parses a partial with whitespace" $
|
|
||||||
lparse "{{> myPartial }}" `shouldBe`
|
|
||||||
returnedOne (Partial (Just "") "myPartial")
|
|
||||||
|
|
||||||
it "parses the an empty section" $
|
|
||||||
lparse "{{#section}}{{/section}}" `shouldBe`
|
|
||||||
returnedOne (Section (NamedData ["section"]) mempty)
|
|
||||||
|
|
||||||
it "parses the an empty section with whitespace" $
|
|
||||||
lparse "{{# section }}{{/ section }}" `shouldBe`
|
|
||||||
returnedOne (Section (NamedData ["section"]) mempty)
|
|
||||||
|
|
||||||
it "parses a delimiter change" $
|
|
||||||
lparse "{{=<< >>=}}<<var>>{{var}}" `shouldBe`
|
|
||||||
return [Variable True (NamedData ["var"]), TextBlock "{{var}}"]
|
|
||||||
|
|
||||||
it "parses a delimiter change with whitespace" $
|
|
||||||
lparse "{{=<< >>=}}<< var >>{{var}}" `shouldBe`
|
|
||||||
return [Variable True (NamedData ["var"]), TextBlock "{{var}}"]
|
|
||||||
|
|
||||||
it "parses two subsequent delimiter changes" $
|
|
||||||
lparse "{{=(( ))=}}(( var ))((=-- $-=))--#section$---/section$-" `shouldBe`
|
|
||||||
return [Variable True (NamedData ["var"]), Section (NamedData ["section"]) []]
|
|
||||||
|
|
||||||
it "propagates a delimiter change from a nested scope" $
|
|
||||||
lparse "{{#section}}{{=<< >>=}}<</section>><<var>>" `shouldBe`
|
|
||||||
return [Section (NamedData ["section"]) [], Variable escaped (NamedData ["var"])]
|
|
||||||
|
|
||||||
it "fails if the tag contains illegal characters" $
|
|
||||||
lparse "{{#&}}" `shouldSatisfy` isLeft
|
|
||||||
|
|
||||||
it "parses a nested variable" $
|
|
||||||
lparse "{{ name.val }}" `shouldBe` returnedOne (Variable escaped (NamedData ["name", "val"]))
|
|
||||||
|
|
||||||
it "parses a variable containing whitespace" $
|
|
||||||
lparse "{{ val space }}" `shouldBe` returnedOne (Variable escaped (NamedData ["val space"]))
|
|
||||||
|
|
||||||
|
|
||||||
substituteSpec :: Spec
|
|
||||||
substituteSpec =
|
|
||||||
describe "substitute" $ do
|
|
||||||
|
|
||||||
let toTemplate ast' = Template "testsuite" ast' mempty
|
|
||||||
|
|
||||||
it "substitutes a html escaped value for a variable" $
|
|
||||||
substitute
|
|
||||||
(toTemplate [Variable escaped (NamedData ["name"])])
|
|
||||||
(object ["name" ~> ("\" ' < > &" :: T.Text)])
|
|
||||||
`shouldBe` "" ' < > &"
|
|
||||||
|
|
||||||
it "substitutes raw value for an unescaped variable" $
|
|
||||||
substitute
|
|
||||||
(toTemplate [Variable unescaped (NamedData ["name"])])
|
|
||||||
(object ["name" ~> ("\" ' < > &" :: T.Text)])
|
|
||||||
`shouldBe` "\" ' < > &"
|
|
||||||
|
|
||||||
it "substitutes a section when the key is present (and an empty object)" $
|
|
||||||
substitute
|
|
||||||
(toTemplate [Section (NamedData ["section"]) [TextBlock "t"]])
|
|
||||||
(object ["section" ~> object []])
|
|
||||||
`shouldBe` "t"
|
|
||||||
|
|
||||||
it "substitutes a section when the key is present (and 'true')" $
|
|
||||||
substitute
|
|
||||||
(toTemplate [Section (NamedData ["section"]) [TextBlock "t"]])
|
|
||||||
(object ["section" ~> True])
|
|
||||||
`shouldBe` "t"
|
|
||||||
|
|
||||||
it "substitutes a section once when the key is present and a singleton list" $
|
|
||||||
substitute
|
|
||||||
(toTemplate [Section (NamedData ["section"]) [TextBlock "t"]])
|
|
||||||
(object ["section" ~> ["True" :: T.Text]])
|
|
||||||
`shouldBe` "t"
|
|
||||||
|
|
||||||
it "substitutes a section twice when the key is present and a list with two items" $
|
|
||||||
substitute
|
|
||||||
(toTemplate [Section (NamedData ["section"]) [TextBlock "t"]])
|
|
||||||
(object ["section" ~> (["True", "False"] :: [T.Text])])
|
|
||||||
`shouldBe` "tt"
|
|
||||||
|
|
||||||
it "substitutes a section twice when the key is present and a list with two\
|
|
||||||
\ objects, changing the scope to each object" $
|
|
||||||
substitute
|
|
||||||
(toTemplate [Section (NamedData ["section"]) [Variable escaped (NamedData ["t"])]])
|
|
||||||
(object
|
|
||||||
[ "section" ~>
|
|
||||||
[ object ["t" ~> ("var1" :: T.Text)]
|
|
||||||
, object ["t" ~> ("var2" :: T.Text)]
|
|
||||||
]
|
|
||||||
])
|
|
||||||
`shouldBe` "var1var2"
|
|
||||||
|
|
||||||
it "substitutes an inverse section when the key is present (and null)" $
|
|
||||||
substitute
|
|
||||||
(toTemplate [InvertedSection (NamedData ["section"]) [TextBlock "t"]])
|
|
||||||
(object ["section" ~> Null])
|
|
||||||
`shouldBe` "t"
|
|
||||||
|
|
||||||
it "does not substitute a section when the key is not present" $
|
|
||||||
substitute
|
|
||||||
(toTemplate [Section (NamedData ["section"]) [TextBlock "t"]])
|
|
||||||
(object [])
|
|
||||||
`shouldBe` ""
|
|
||||||
|
|
||||||
it "does not substitute a section when the key is present (and 'false')" $
|
|
||||||
substitute
|
|
||||||
(toTemplate [Section (NamedData ["section"]) [TextBlock "t"]])
|
|
||||||
(object ["section" ~> False])
|
|
||||||
`shouldBe` ""
|
|
||||||
|
|
||||||
it "does not substitute a section when the key is present (and null)" $
|
|
||||||
substitute
|
|
||||||
(toTemplate [Section (NamedData ["section"]) [TextBlock "t"]])
|
|
||||||
(object ["section" ~> Null])
|
|
||||||
`shouldBe` ""
|
|
||||||
|
|
||||||
it "does not substitute a section when the key is present (and empty list)" $
|
|
||||||
substitute
|
|
||||||
(toTemplate [Section (NamedData ["section"]) [TextBlock "t"]])
|
|
||||||
(object ["section" ~> ([] :: [T.Text])])
|
|
||||||
`shouldBe` ""
|
|
||||||
|
|
||||||
it "substitutes a lambda by applying lambda to contained text" $
|
|
||||||
substitute
|
|
||||||
(toTemplate [Section (NamedData ["lambda"]) [TextBlock "t"]])
|
|
||||||
(object ["lambda" ~> (overText T.toUpper)])
|
|
||||||
`shouldBe` "T"
|
|
||||||
|
|
||||||
it "substitutes a lambda by applying lambda to the nested substitution results" $
|
|
||||||
substitute
|
|
||||||
(toTemplate [Section (NamedData ["lambda"]) [TextBlock "t", Variable escaped (NamedData ["inner"])]])
|
|
||||||
(object [ "lambda" ~> (overText T.toUpper)
|
|
||||||
, "inner" ~> ("var" :: T.Text)
|
|
||||||
])
|
|
||||||
`shouldBe` "TVAR"
|
|
||||||
|
|
||||||
it "substitutes a lambda used directly as if applied to empty block" $
|
|
||||||
substitute
|
|
||||||
(toTemplate [Variable escaped (NamedData ["lambda"])])
|
|
||||||
(object ["lambda" ~> (Lambda $ \[] -> return [TextBlock "T"])])
|
|
||||||
`shouldBe` "T"
|
|
||||||
|
|
||||||
it "substitutes a nested section" $
|
|
||||||
substitute
|
|
||||||
(toTemplate [Variable escaped (NamedData ["outer", "inner"])])
|
|
||||||
(object
|
|
||||||
[ "outer" ~> object ["inner" ~> ("success" :: T.Text)]
|
|
||||||
, "inner" ~> ("error" :: T.Text)
|
|
||||||
]
|
|
||||||
)
|
|
||||||
`shouldBe` "success"
|
|
||||||
|
|
||||||
|
|
||||||
converterSpec :: Spec
|
|
||||||
converterSpec =
|
|
||||||
describe "toMustache" $
|
|
||||||
it "converts a String" $
|
|
||||||
toMustache ("My String" :: String) `shouldSatisfy` \case (String "My String") -> True; _ -> False
|
|
||||||
|
|
||||||
-- This is a one-off instance to define how we want the Spec to compare templates
|
|
||||||
instance Eq Template where
|
|
||||||
(==) = (==) `on` ast
|
|
||||||
|
|
||||||
compileTimeSpec :: Spec
|
|
||||||
compileTimeSpec =
|
|
||||||
describe "compileTimeCompiling" $ do
|
|
||||||
|
|
||||||
it "creates compiled templates from a QuasiQuoter" $
|
|
||||||
Right [mustache|This {{ template }} was injected at compile time with a quasiquoter|] `shouldBe`
|
|
||||||
compileTemplate "Template Name" "This {{ template }} was injected at compile time with a quasiquoter"
|
|
||||||
|
|
||||||
it "creates compiled templates from an embedded file" $
|
|
||||||
Right $(embedTemplate ["test/unit/examples"] "test-template.txt.mustache") `shouldBe`
|
|
||||||
compileTemplate "Template Name" "This {{ template }} was injected at compile time with an embedded file\n"
|
|
||||||
|
|
||||||
it "creates compiled templates from a single embedded file" $
|
|
||||||
Right $(embedSingleTemplate "test/unit/examples/test-template.txt.mustache") `shouldBe`
|
|
||||||
compileTemplate "Template Name" "This {{ template }} was injected at compile time with an embedded file\n"
|
|
||||||
|
|
||||||
it "creates compiled templates from an embedded file containing partials" $
|
|
||||||
Right $(embedTemplate ["test/unit/examples", "test/unit/examples/partials"] "test-template-partials.txt.mustache") `shouldBe`
|
|
||||||
unsafePerformIO (automaticCompile ["test/unit/examples", "test/unit/examples/partials"] "test-template-partials.txt.mustache")
|
|
||||||
|
|
||||||
main :: IO ()
|
|
||||||
main = hspec $ do
|
|
||||||
parserSpec
|
|
||||||
substituteSpec
|
|
||||||
converterSpec
|
|
||||||
compileTimeSpec
|
|
|
@ -1 +0,0 @@
|
||||||
and {{ partials }}
|
|
|
@ -1 +0,0 @@
|
||||||
This {{ template }} was injected at compile time with an embedded file {{> test-partial.txt.mustache }}
|
|
|
@ -1 +0,0 @@
|
||||||
This {{ template }} was injected at compile time with an embedded file
|
|
Loading…
Reference in a new issue