{-# LANGUAGE OverloadedStrings #-} module Text.MMark.Extension.PunctuationPrettifierSpec (spec) where import Test.Hspec import Text.MMark.Extension.PunctuationPrettifier import Text.MMark.Extension.TestUtils spec :: Spec spec = describe "punctuationPrettifier" $ do let to = withExt punctuationPrettifier context "on plain inlines" $ do it "replaces ... with ellipsis" $ "He forgot where he came from..." `to` "

He forgot where he came from…

\n" it "replaces --- with em dash" $ "Here we go---at last." `to` "

Here we go—at last.

\n" it "replaces -- with en dash" $ "Here we go -- at last." `to` "

Here we go – at last.

\n" it "replaces double quotes intelligently" $ "\"Something\"" `to` "

“Something”

\n" it "replaces double quotes intelligently (empty)" $ "\"\"" `to` "

“”

\n" it "replaces single quotes intelligently" $ do "'Something'" `to` "

‘Something’

\n" "I'm doin' well, 'cause I care 'bout 'Big Jim'." `to` "

I’m doin’ well, ‘cause I care ‘bout ‘Big Jim’.

\n" it "replaces single quotes intelligently (empty)" $ "''" `to` "

‘’

\n" it "a tricky test 1" $ "Something-\"foo\"." `to` "

Something-”foo”.

\n" it "a tricky test 2" $ "Something.--" `to` "

Something.–

\n" context "on other inlines" $ it "has no effect" $ "`code -- span`" `to` "

code -- span

\n"