aboutsummaryrefslogtreecommitdiff
path: root/bbcode/test/Text/BBCodeSpec.hs
blob: a6e66b670d2169bea541d4e7077d10734919a680 (plain)
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
{-# LANGUAGE OverloadedStrings, OverloadedLists #-}

module Text.BBCodeSpec (spec) where

import Test.Hspec
import Test.Hspec.QuickCheck (prop)
import Test.QuickCheck.Instances

import Text.BBCode

import Data.Text (Text)

import Control.Monad (zipWithM_)
import Data.Monoid ((<>))

spec :: Spec
spec = do
  zipWithM_ example [1..] examples
    where
      example n (s, ts) = let str = "Example " <> show n
                          in specify str (bbcode s == Right ts)

examples :: [(Text, DomForest)]
examples = [ ("[t]test[/t]"
             , pure [Element "t" [] [Content "test"]])
           , ("[t]te\\st[/t]"
             , pure [Element "t" [] [Content "te\\st"]])
           , ("[t]te\\[st[/t]"
             , pure [Element "t" [] [Content "te[st"]])
           , ("[t]test\\\\[/t]"
             , pure [Element "t" [] [Content "test\\"]])
           , ("[\\t]test[/\\t]"
             , pure [Element "\\t" [] [Content "test"]])
           , ("[t attr]test[/t]"
             , pure [Element "t" [("attr", "")] [Content "test"]])
           , ("[t=attr]test[/t]"
             , pure [Element "t" [("", "attr")] [Content "test"]])
           , ("[t attr=val]test[/t]"
             , pure [Element "t" [("attr", "val")] [Content "test"]])
           , ("[t attr=\"val\"]test[/t]"
             , pure [Element "t" [("attr", "val")] [Content "test"]])
           , ("[t attr=\"va]l\"]test[/t]"
             , pure [Element "t" [("attr", "va]l")] [Content "test"]])
           , ("[t attr=\"va\\\"l\"]test[/t]"
             , pure [Element "t" [("attr", "va\"l")] [Content "test"]])
           , ("[t attr=\"val\"   attr2=\"val2\"  ]test[/t]"
             , pure [Element "t" [("attr", "val"), ("attr2", "val2")] [Content "test"]])
           , ("[br/]"
             , pure [Element "br" [] []])
           , ("[br attr/]"
             , pure [Element "br" [("attr", "")] []])
           , ("[br=val/]"
             , pure [Element "br" [("", "val")] []])
           , ("[br attr=val/]"
             , pure [Element "br" [("attr", "val")] []])
           , ("[br attr=val val2/]"
             , pure [Element "br" [("attr", "val"), ("val2", "")] []])
           , ("foo\n\nbar"
             , [[Content "foo"], [Content "bar"]])
           , ("[b]foo[/b]\n\n[b]bar[/b]"
             , [[Element "b" [] [Content "foo"]], [Element "b" [] [Content "bar"]]])
           , ("[b]foo[/b][b]bar[/b]"
             , [[Element "b" [] [Content "foo"], Element "b" [] [Content "bar"]]])
           ]