{-# LANGUAGE OverloadedStrings #-} module Main where -- Monoid import Data.Monoid ((<>)) -- Text import Data.Text (Text) import qualified Data.Text.Lazy as TL import Data.Text.Lazy.Builder (Builder) -- Tests import Test.Hspec -- Fmt import Fmt main :: IO () main = hspec $ do let n = 25 :: Int s = "!" :: String it "simple examples" $ do ("a"%%"b") ==%> "a25b" ("a"%%"b"%%"") ==%> "a25b!" (""%%%%"") ==%> "25!" (""%%%%"") ==%> "-25!" (""%%%%"") ==%> "25!" describe "examples with Show/mixed" $ do it "copy of Buildable examples" $ do ("a"%<>%"b") ==%> "a25b" ("a"%<>%%<>%"b") ==%> "a2525b" -- These are mixed, i.e. both Buildable and Show versions are used ("a"%<>%"b"%%"") ==%> "a25b!" (""%<>%%%"") ==%> "25!" (""%<>%%%"") ==%> "-25!" it "examples that don't work with Buildable" $ do (""%<>%"") ==%> "Just 25" (""%<<(n,n)>>%"") ==%> "(25,25)" it "plays nice with other operators" $ do -- If precedence is bad these won't compile (""%%%%"") ==%> "2426" (id $ ""%%%%"") ==%> "2426" it "works with <>" $ do ("number: "%%"\n"<> "string: "%%"") ==%> "number: 25\nstring: !" describe "output as" $ do it "String" $ ("a"%%"b" :: String) `shouldBe` "a25b" it "Text" $ ("a"%%"b" :: Text) `shouldBe` "a25b" it "Lazy Text" $ ("a"%%"b" :: TL.Text) `shouldBe` "a25b" it "Builder" $ ("a"%%"b" :: Builder) `shouldBe` "a25b" ---------------------------------------------------------------------------- -- Utilities ---------------------------------------------------------------------------- (==%>) :: Text -> Text -> Expectation (==%>) = shouldBe