{-# LANGUAGE OverloadedStrings , UnicodeSyntax #-} module WikiParserTest ( testData ) where import Control.Applicative import Data.Maybe import Data.Text (Text) import Network.URI import Rakka.Wiki import Rakka.Wiki.Parser import Test.HUnit import Text.ParserCombinators.Parsec cmdTypeOf ∷ Alternative f ⇒ Text → f CommandType cmdTypeOf "br" = pure InlineCommandType cmdTypeOf "i" = pure InlineCommandType cmdTypeOf "b" = pure InlineCommandType cmdTypeOf "span" = pure InlineCommandType cmdTypeOf "div" = pure BlockCommandType cmdTypeOf _ = empty parseWiki ∷ String → Either String WikiPage parseWiki src = case parse (wikiPage cmdTypeOf) "" src of Left err → Left (show err) Right page → Right page testData :: [Test] testData = [ (parseWiki "" ~?= Right []) , (parseWiki "\n" ~?= Right []) , (parseWiki "=heading=" ~?= Right [ Heading 1 "heading" ]) , (parseWiki "== heading == \n" ~?= Right [ Heading 2 "heading" ]) , (parseWiki "===== hello world =====\n" ~?= Right [ Heading 5 "hello world" ]) , (parseWiki "a =not a heading=" ~?= Right [ Paragraph [ Text "a =not a heading=" ] ]) , (parseWiki "=h=\n\n=h=" ~?= Right [ Heading 1 "h" , Heading 1 "h" ]) , (parseWiki "foo\nbar" ~?= Right [ Paragraph [ Text "foo" , Text "\n" , Text "bar" ] ]) , (parseWiki "foo\nbar\n\nbaz\n" ~?= Right [ Paragraph [ Text "foo" , Text "\n" , Text "bar" ] , Paragraph [ Text "baz" ] ]) , (parseWiki "foo\n\n\nbar" ~?= Right [ Paragraph [ Text "foo" ] , Paragraph [ Text "bar" ] ]) , (parseWiki "foo\n=h=" ~?= Right [ Paragraph [ Text "foo" ] , Heading 1 "h" ]) , (parseWiki "" ~?= Right []) , (parseWiki "foo" ~?= Right [ Paragraph [ Text "foo" ] ]) , (parseWiki "bar" ~?= Right [ Paragraph [ Text "bar" ] ]) , (parseWiki "foobar" ~?= Right [ Paragraph [ Text "foo" , Text "bar" ] ]) , (parseWiki "=h=" ~?= Right [ Heading 1 "h" ]) , (parseWiki "=h= " ~?= Right [ Heading 1 "h" ]) , (parseWiki " comment -->" ~?= Right []) , (parseWiki "[[[Page]]]" ~?= Right [ Paragraph [ ObjectLink "Page" Nothing ] ]) , (parseWiki "[[[Page|foo]]]" ~?= Right [ Paragraph [ ObjectLink "Page" (Just "foo") ] ]) , (parseWiki "[[Page]]" ~?= Right [ Paragraph [ PageLink (Just "Page") Nothing Nothing ] ]) , (parseWiki "[[Page|Link to \"Page\"]]" ~?= Right [ Paragraph [ PageLink (Just "Page") Nothing (Just "Link to \"Page\"") ] ]) , (parseWiki "[[Page#foo]]" ~?= Right [ Paragraph [ PageLink (Just "Page") (Just "foo") Nothing ] ]) , (parseWiki "[[#foo]]" ~?= Right [ Paragraph [ PageLink Nothing (Just "foo") Nothing ] ]) , (parseWiki "[[Page#foo|Link to \"Page#foo\"]]" ~?= Right [ Paragraph [ PageLink (Just "Page") (Just "foo") (Just "Link to \"Page#foo\"") ] ]) , (parseWiki "foo [[Bar]] baz" ~?= Right [ Paragraph [ Text "foo " , PageLink (Just "Bar") Nothing Nothing , Text " baz" ] ]) , (parseWiki "[[Foo]]\n[[Bar]]" ~?= Right [ Paragraph [ PageLink (Just "Foo") Nothing Nothing , Text "\n" , PageLink (Just "Bar") Nothing Nothing ] ]) , (parseWiki " foo" ~?= Right [ Preformatted [ Text "foo" ] ]) , (parseWiki " foo\n bar\n" ~?= Right [ Preformatted [ Text "foo" , Text "\n" , Text " bar" ] ]) , (parseWiki "foo\n bar\nbaz" ~?= Right [ Paragraph [ Text "foo" ] , Preformatted [ Text "bar" ] , Paragraph [ Text "baz" ] ]) , (parseWiki "----" ~?= Right [ HorizontalLine ]) , (parseWiki "\nfoo\nbar\n----\n" ~?= Right [ Paragraph [ Text "foo" , Text "\n" , Text "bar" ] , HorizontalLine ]) , (parseWiki "a----b" ~?= Right [ Paragraph [ Text "a----b" ] ]) , (parseWiki "* a" ~?= Right [ List Bullet [[Inline (Text "a")]] ]) , (parseWiki "* a*" ~?= Right [ List Bullet [[Inline (Text "a*")]] ]) , (parseWiki "* a\n* b\n" ~?= Right [ List Bullet [ [Inline (Text "a")] , [Inline (Text "b")] ] ]) , (parseWiki "*a\n*#b\n*#c\n" ~?= Right [ List Bullet [ [ Inline (Text "a") , Block (List Numbered [ [Inline (Text "b")] , [Inline (Text "c")] ]) ] ] ]) , (parseWiki "*a\n#b" ~?= Right [ List Bullet [ [Inline (Text "a")] ] , List Numbered [ [Inline (Text "b")] ] ]) , (parseWiki "*a" ~?= Right [ List Bullet [ [Inline (Text "a")] ] ]) , (parseWiki "*a\n*b" ~?= Right [ List Bullet [ [Inline (Text "a")] , [Inline (Text "b")] ] ]) , (parseWiki "foo:bar" ~?= Right [ Paragraph [ Text "foo" , Text ":bar" ] ]) , (parseWiki "; foo: bar" ~?= Right [ DefinitionList [Definition [Text "foo"] [Text "bar"]] ]) , (parseWiki "; foo: bar\n" ~?= Right [ DefinitionList [Definition [Text "foo"] [Text "bar"]] ]) , (parseWiki "; foo\n: bar\n; bar\n: baz\n: baz" ~?= Right [ DefinitionList [ Definition [Text "foo"] [ Text "bar" ] , Definition [Text "bar"] [ Text "baz" , Text "\n" , Text "baz" ] ] ]) , (parseWiki "" ~?= Right [ Paragraph [ Text "foo [[bar]] baz" ] ]) , (parseWiki "" ~?= Right [ Preformatted [ Text "foo [[bar]] baz" ] ]) , (parseWiki "" ~?= Right [ Preformatted [ Text "foo [[bar]] baz" ] ]) , (parseWiki "foo' bar" ~?= Right [ Paragraph [ Text "foo" , Text "'" , Text " bar" ] ]) , (parseWiki "''foo''" ~?= Right [ Paragraph [ Italic [Text "foo"] ] ]) , (parseWiki "'''foo'''" ~?= Right [ Paragraph [ Bold [Text "foo"] ] ]) , (parseWiki "foo''''" ~?= Right [ Paragraph [ Text "foo" , Text "'" ] ]) , (parseWiki "'''''foo'''''" ~?= Right [ Paragraph [ Italic [Bold [Text "foo"]] ] ]) , (parseWiki "
" ~?= Right [ Paragraph [ InlineCmd (InlineCommand "br" [] []) ] ]) , (parseWiki "
" ~?= Right [ Paragraph [ InlineCmd (InlineCommand "br" [("style", "clear: both")] []) ] ]) , (parseWiki "foo" ~?= Right [ Paragraph [ InlineCmd (InlineCommand "i" [] [ InlineCmd (InlineCommand "b" [] [ Text "foo" ]) ]) ] ]) , (parseWiki "\nfoo\n\nbar" ~?= Right [ Paragraph [ InlineCmd (InlineCommand "i" [] [ Text "\n" , Text "foo" , Text "\n" , Text "\n" , Text "bar" ]) ] ]) , (parseWiki "
foo
" ~?= Right [ BlockCmd (BlockCommand "div" [] [ Paragraph [Text "foo"] ]) ]) , (parseWiki "
\nbar\n
" ~?= Right [ BlockCmd (BlockCommand "div" [] [ Paragraph [Text "bar"] ]) ]) , (parseWiki "
" ~?= Right [ BlockCmd (BlockCommand "div" [] []) ]) , (parseWiki "foo
" ~?= Right [ Paragraph [Text "foo"] , BlockCmd (BlockCommand "div" [("id", "bar")] []) ]) , (parseWiki "[http://example.org/]" ~?= Right [ Paragraph [ExternalLink (fromJust $ parseURI "http://example.org/") Nothing] ]) , (parseWiki "[http://example.org/ example.org]" ~?= Right [ Paragraph [ExternalLink (fromJust $ parseURI "http://example.org/") (Just "example.org") ] ]) ]