File: Units.hs

package info (click to toggle)
haskell-hstringtemplate 0.8.8-4
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 164 kB
  • sloc: haskell: 999; makefile: 2
file content (42 lines) | stat: -rw-r--r-- 1,393 bytes parent folder | download | duplicates (2)
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
{-# OPTIONS -O2 -fglasgow-exts #-}

module Units where
import System.IO
import qualified Data.Map as M

import Text.StringTemplate
import Text.StringTemplate.Classes
import Text.StringTemplate.Base
import Test.HUnit
import Control.Monad
import System.Environment

no_prop = toString (setAttribute "foo" "f" $ newSTMP "a$foo.bar$a")
          ~=? "aa"

one_prop = toString (setAttribute "foo" (M.singleton "bar" "baz") $ newSTMP "a$foo.bar$a")
           ~=? "abaza"

anon_tmpl = toString (setAttribute "foo" "f" $ newSTMP "a$foo:{{$foo$\\}}$a")
            ~=? "a{f}a"

setA = setAttribute "foo" ["a","b","c"]
func_first = toString (setA $ newSTMP "$first(foo)$") ~=? "a"
func_last = toString (setA $ newSTMP "$last(foo)$") ~=? "c"
func_rest = toString (setA $ newSTMP "$rest(foo)$") ~=? "bc"
func_length = toString (setA $ newSTMP "$length(foo)$") ~=? "3"
func_reverse = toString (setA $ newSTMP "$reverse(foo)$") ~=? "cba"

tests = TestList ["no_prop" ~: no_prop,
                  "one_prop" ~: one_prop,
                  "func_first" ~: func_first,
                  "func_last" ~: func_last,
                  "func_rest" ~: func_rest,
                  "func_reverse" ~: func_reverse,
                  "func_length" ~: func_length,
                  "anon_tmpl" ~: anon_tmpl]

main = do
  c <- runTestTT tests
  when (errors c > 0 || failures c > 0) $
    fail "Not all tests passed."