diff options
Diffstat (limited to 'bbcode/test')
| -rw-r--r-- | bbcode/test/Spec.hs | 1 | ||||
| -rw-r--r-- | bbcode/test/Text/BBCode/LexerSpec.hs | 68 | 
2 files changed, 69 insertions, 0 deletions
| diff --git a/bbcode/test/Spec.hs b/bbcode/test/Spec.hs new file mode 100644 index 0000000..a824f8c --- /dev/null +++ b/bbcode/test/Spec.hs | |||
| @@ -0,0 +1 @@ | |||
| {-# OPTIONS_GHC -F -pgmF hspec-discover #-} | |||
| diff --git a/bbcode/test/Text/BBCode/LexerSpec.hs b/bbcode/test/Text/BBCode/LexerSpec.hs new file mode 100644 index 0000000..8b95874 --- /dev/null +++ b/bbcode/test/Text/BBCode/LexerSpec.hs | |||
| @@ -0,0 +1,68 @@ | |||
| 1 | {-# LANGUAGE OverloadedStrings #-} | ||
| 2 | {-# LANGUAGE FlexibleInstances #-} | ||
| 3 | |||
| 4 | module Text.BBCode.LexerSpec (spec) where | ||
| 5 | |||
| 6 | import Test.Hspec | ||
| 7 | import Test.Hspec.QuickCheck (prop) | ||
| 8 | import Test.QuickCheck (Property, Discard(..), property) | ||
| 9 | import Text.BBCode.Lexer | ||
| 10 | |||
| 11 | import Data.Text (Text) | ||
| 12 | import qualified Data.Text as T (singleton, replace, last, null) | ||
| 13 | |||
| 14 | import Data.Monoid ((<>), mconcat, Endo(..)) | ||
| 15 | |||
| 16 | import Data.Attoparsec.Text (parseOnly, endOfInput) | ||
| 17 | |||
| 18 | import Control.Applicative | ||
| 19 | import Control.Monad (zipWithM_) | ||
| 20 | |||
| 21 | coToken :: BBToken -> Text | ||
| 22 | -- ^ Inverse of `token` | ||
| 23 | coToken (BBOpen t) = "[" <> escape [']'] t <> "]" | ||
| 24 | coToken (BBClose t) = "[/" <> escape [']'] t <> "]" | ||
| 25 | coToken (BBStr t) = escape ['['] t | ||
| 26 | |||
| 27 | escape :: [Char] -> Text -> Text | ||
| 28 | -- ^ Inverse of `escapedText` | ||
| 29 | escape xs = endos [ T.replace c' ("\\" <> c') . T.replace ("\\" <> c') ("\\\\" <> c') | c <- xs, let c' = T.singleton c ] . escapeLast | ||
| 30 | where | ||
| 31 | endos = appEndo . mconcat . map Endo | ||
| 32 | escapeLast t | ||
| 33 | | T.null t = "" | ||
| 34 | | T.last t == '\\' = t <> "\\" | ||
| 35 | | otherwise = t | ||
| 36 | |||
| 37 | tokenize :: Text -> Either String [BBToken] | ||
| 38 | -- ^ Run 'many token' against input | ||
| 39 | tokenize = parseOnly (many token <* endOfInput) | ||
| 40 | |||
| 41 | spec :: Spec | ||
| 42 | spec = do | ||
| 43 | prop "prop_token" prop_token | ||
| 44 | zipWithM_ example [1..] examples | ||
| 45 | where | ||
| 46 | example n (s, ts) = let str = "Example " <> show n | ||
| 47 | in specify str $ (tokenize s == Right ts) | ||
| 48 | |||
| 49 | prop_token :: Text -> Property | ||
| 50 | -- ^ prop> (mconcat . map coToken) <$> tokenize x == Right x | ||
| 51 | -- | ||
| 52 | -- Where 'x' is restricted such that `tokenize` succeeds | ||
| 53 | prop_token x = discardLeft (((== x) . mconcat . map coToken) <$> tokenize x) | ||
| 54 | where | ||
| 55 | discardLeft = either (const $ property Discard) property | ||
| 56 | |||
| 57 | examples :: [(Text, [BBToken])] | ||
| 58 | examples = [ ("[t]test[/t]" | ||
| 59 | , [BBOpen "t", BBStr "test", BBClose "t"]) | ||
| 60 | , ("[t]te\\st[/t]" | ||
| 61 | , [BBOpen "t", BBStr "te\\st", BBClose "t"]) | ||
| 62 | , ("[t]te\\[st[/t]" | ||
| 63 | , [BBOpen "t", BBStr "te[st", BBClose "t"]) | ||
| 64 | , ("[\\t]test[/t]" | ||
| 65 | , [BBOpen "\\t", BBStr "test", BBClose "t"]) | ||
| 66 | , ("[t]test[/t\\]]" | ||
| 67 | , [BBOpen "t", BBStr "test", BBClose "t]"]) | ||
| 68 | ] | ||
