File: test.hs

package info (click to toggle)
haskell-doctemplates 0.11.0.1-1
  • links: PTS
  • area: main
  • in suites: forky, sid, trixie
  • size: 288 kB
  • sloc: haskell: 1,223; makefile: 7
file content (116 lines) | stat: -rw-r--r-- 4,748 bytes parent folder | download | duplicates (3)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}

import Text.DocLayout (render)
import qualified Text.DocLayout as DL
import qualified Data.Map as M
import Text.DocTemplates
import Test.Tasty.Golden
import Test.Tasty
import Test.Tasty.HUnit
import qualified Data.Text as T
import qualified Data.Text.IO as T
import qualified Data.Text.Encoding as T
import System.FilePath
import System.IO.Temp
import Data.Aeson
import System.FilePath.Glob
import qualified Data.ByteString.Lazy as BL
import Data.Semigroup ((<>))
import Data.Maybe

main :: IO ()
main = withTempDirectory "test" "out." $ \tmpdir -> do
  testFiles <- glob "test/*.test"
  goldenTests <- mapM (getTest tmpdir) testFiles
  defaultMain $ testGroup "Tests"
    [ testGroup "Golden tests" goldenTests
    , testGroup "Unit tests" unitTests
    ]

unitTests :: [TestTree]
unitTests = [
    testCase "compile failure" $ do
      (res :: Either String (Template T.Text)) <-
        compileTemplate "" "$if(x$and$endif$"
      res @?= Left "(line 1, column 6):\nunexpected \"$\"\nexpecting \".\", \"/\" or \")\""
  , testCase "compile failure (keyword as variable)" $ do
    (res :: Either String (Template T.Text)) <-
        compileTemplate "foobar.txt" "$sep$"
    res @?= Left "\"foobar.txt\" (line 1, column 5):\nunexpected \"$\"\nexpecting letter or digit or \"()\""
  , testCase "compile failure (unknown pipe)" $ do
    (res :: Either String (Template T.Text)) <-
        compileTemplate "foobar.txt" "$foo/nope$"
    res @?= Left "\"foobar.txt\" (line 1, column 10):\nunexpected \"$\"\nexpecting letter, letter or digit or \"()\"\nUnknown pipe nope"
  , testCase "compile failure (missing parameter for pipe)" $ do
    (res :: Either String (Template T.Text)) <-
        compileTemplate "foobar.txt" "$foo/left$"
    res @?=  Left "\"foobar.txt\" (line 1, column 10):\nunexpected \"$\"\nexpecting letter, integer parameter for pipe, letter or digit or \"()\""
  , testCase "compile failure (unexpected parameter for pipe)" $ do
    (res :: Either String (Template T.Text)) <-
        compileTemplate "foobar.txt" "$foo/left a$"
    res @?= Left "\"foobar.txt\" (line 1, column 11):\nunexpected \"a\"\nexpecting integer parameter for pipe"
  , testCase "compile failure (error in partial)" $ do
      (res :: Either String (Template T.Text)) <-
         compileTemplate "test/foobar.txt" "$bad()$"
      res @?= Left "\"test/bad.txt\" (line 2, column 7):\nunexpected \"s\"\nexpecting \"$\""
  , testCase "comment with no newline" $ do
      (res :: Either String (Template T.Text)) <-
         compileTemplate "foo" "$-- hi"
      res @?= Right (mempty :: Template T.Text)
  , testCase "reflow" $ do
      (templ :: Either String (Template T.Text)) <-
        compileTemplate "foo" "not breakable and$~$ this is breakable\nok? $foo$$~$"
      let res :: T.Text
          res = case templ of
                  Right t -> render (Just 10)
                   (renderTemplate t (object ["foo" .= ("42" :: T.Text)]))
                  Left e  -> T.pack e
      res @?= "not breakable and\nthis is\nbreakable\nok? 42"
  , testCase "nowrap pipe" $ do
      (templ :: Either String (Template T.Text)) <-
        compileTemplate "foo" "$foo/nowrap$\n$foo$"
      let res :: T.Text
          res = case templ of
                  Right t -> render (Just 10)
                   (renderTemplate t (Context $ M.insert "foo"
                     (SimpleVal $
                       DL.hsep ["hello", "this", "is", "a",
                                "test", "of", "the", "wrapping"]
                       :: Val T.Text) mempty))
                  Left e  -> T.pack e
      res @?= "hello this is a test of the wrapping\nhello this\nis a test\nof the\nwrapping"
  ]

{- The test "golden" files are structured as follows:

{ "foo": ["bar", "baz"] }
.
A template with $foo$.
.
A template with bar, baz.

-}

diff :: FilePath -> FilePath -> [String]
diff ref new = ["diff", "-u", "--minimal", ref, new]

getTest :: FilePath -> FilePath -> IO TestTree
getTest tmpdir fp = do
  let actual = tmpdir </> takeFileName fp
  return $ goldenVsFileDiff fp diff fp actual $ do
    inp <- T.readFile fp
    let (j, template', _expected) =
            case T.splitOn "\n.\n" inp of
              [x,y,z] -> (x,y,z)
              _       -> error $ "Error parsing " ++ fp
    let j' = j <> "\n"
    let template = template' <> "\n"
    let templatePath = replaceExtension fp ".txt"
    let (context :: Value) = fromMaybe Null $
           decode' . BL.fromStrict . T.encodeUtf8 $ j'
    res <- applyTemplate templatePath template context
    case res of
      Left e -> error e
      Right x -> T.writeFile actual $ j' <> ".\n" <> template <> ".\n" <>
                    render Nothing x