hasciidoc/tests/Main.hs

42 lines
960 B
Haskell

{-# LANGUAGE OverloadedStrings #-}
module Main where
import Data.Attoparsec.Text
import qualified Data.Text as T
import Test.Tasty
import Test.Tasty.Hspec as HS
import Hasciidoc
main :: IO ()
main = defaultMain tests
tests :: TestTree
tests = testGroup "Tests" [specs]
-- Hspec Tests
specs :: TestTree
specs = testGroup "Specifications"
[ HS.testCase "Header Parsing" headerParseSpec
]
headerParseSpec :: Spec
headerParseSpec = do
describe "Document Header" $ do
describe "Document Title" $ do
describe "pTitle" $ do
it "parses a one-line level 0 title with no right-hand delimiter" $
parseOnly pTitle "= This is a level 0 title\n"
`shouldBe`
Right (0, "This is a level 0 title")
it "parses a one-line level 0 title with a right-hand delimeter" $
parseOnly pTitle "= This is another level 0 title =\n"
`shouldBe`
Right (0, "This is another level 0 title")