{-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE TypeApplications #-} module GeneratorSpec where import Data.Maybe import Text.Shakespeare.Text import Data.Text (Text) import Test.Hspec import Text.Ogmarkup.Private.Config import Text.Ogmarkup.Private.Typography import qualified Text.Ogmarkup.Private.Ast as Ast import qualified Text.Ogmarkup.Private.Generator as Gen spec :: Spec spec = do describe "format" $ it "should deal with raw input" $ Gen.runGenerator (Gen.format @TestConf sentence) `shouldBe` "Bonjour toi." describe "component" $ it "should deal with thought" $ Gen.runGenerator (Gen.component @TestConf False False (Ast.Thought simpleReply Nothing)) `shouldBe` "[thou-anonymous][reply]Bonjour toi.[/reply][/thou-anonymous]" data TestConf instance GenConf TestConf Text where typography = frenchTypo 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 = "_" sentence :: Ast.Format Text sentence = Ast.Raw [ Ast.Word "Bonjour" , Ast.Word "toi" , Ast.Punctuation Ast.Point ] simpleReply :: Ast.Reply Text simpleReply = Ast.Simple [ sentence ]