{-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE TypeApplications #-} module OgmarkupSpec where import Data.Maybe (fromMaybe) import Data.Text (Text) import Test.Hspec import Text.Shakespeare.Text import Text.Ogmarkup spec :: Spec spec = describe "ogmarkup" $ do it "should merge paragraphs with consecutive dialogues" $ ogmarkup @TestConf consecutiveDialogues `shouldBe` "[doc][story][par][dial-anonymous]“[reply]This is a test.[/reply]”[/dial-anonymous][br][dial-anonymous]“[reply]May it works.[/reply]”[/dial-anonymous][/par][/story][/doc]" it "should not merge other paragraphs" $ ogmarkup @TestConf notConsecutiveDialogues `shouldBe` "[doc][story][par][dial-anonymous]“[reply]This is a test.[/reply]”[/dial-anonymous][/par][par]May it works.[/par][/story][/doc]" consecutiveDialogues :: Text consecutiveDialogues = "[This is a test.]\n\n[May it works.]" notConsecutiveDialogues :: Text notConsecutiveDialogues = "[This is a test.]\n\nMay it works." data TestConf instance GenConf TestConf Text where typography = unicodeEnglishTypo documentTemplate doc = [st|[doc]#{doc}[/doc]|] errorTemplate err = [st|[error]#{err}[/error]|] storyTemplate story = [st|[story]#{story}[/story]|] asideTemplate (Just cls) aside = [st|[aside-#{cls}]#{aside}[/aside-#{cls}]|] asideTemplate _ aside = [st|[aside]#{aside}[/aside]|] paragraphTemplate par = [st|[par]#{par}[/par]|] tellerTemplate teller = [st|[tell]#{teller}[/tell]|] dialogueTemplate auth dial = [st|[dial-#{auth}]#{dial}[/dial-#{auth}]|] thoughtTemplate auth thou = [st|[thou-#{auth}]#{thou}[/thou-#{auth}]|] replyTemplate rep = [st|[reply]#{rep}[/reply]|] betweenDialogue = "[br]" emphTemplate txt = [st|[em]#{txt}[/em]|] strongEmphTemplate txt = [st|[strong]#{txt}[/strong]|] authorNormalize = fromMaybe "anonymous" printSpace None = "" printSpace Normal = " " printSpace Nbsp = "_"