{-# LANGUAGE OverloadedLists #-} {-# LANGUAGE OverloadedStrings #-} module Text.Seonbi.FacadeSpec (spec) where import Data.String (IsString) import Test.Hspec import Text.Seonbi.Facade input :: (IsString a, Monoid a) => a input = "

아이들에게 하로의 乾燥한 學課로
" <> "해말간 倦怠가 깃들고,
" <> ""矛盾" 두자를 理解치 못하도록
" <> "머리가 單純하였구나.

" <> "

尹東柱 <이런날>

" output :: (IsString a, Monoid a) => a output = "

아이들에게 하로의 건조한 학과로
" <> "해말간 권태가 깃들고,
" <> "“모순” 두자를 이해치 못하도록
" <> "머리가 단순하였구나.

" <> "

윤동주 〈이런날〉

" spec :: Spec spec = specify "transformHtmlLazyText" $ do let noOp = Configuration { quote = Nothing , cite = Nothing , arrow = Nothing , ellipsis = False , emDash = False , hanja = Nothing , xhtml = False , debugLogger = Nothing } transformHtmlLazyText noOp input `shouldBe` Just input transformHtmlLazyText ko_KR input `shouldBe` Just output