{-# LANGUAGE OverloadedLists #-} {-# LANGUAGE OverloadedStrings #-} {-# OPTIONS_GHC -Wno-orphans #-} module Text.PrettyPrint.Avh4.BlockSpec where import qualified Data.ByteString.Builder as B import Data.ByteString.Lazy.Char8 (ByteString) import qualified Data.ByteString.Lazy.Char8 as BS import Test.Hspec import Test.Hspec.QuickCheck import Test.QuickCheck import Text.PrettyPrint.Avh4.Block spec :: Spec spec = describe "Block" $ do describe "Line" $ do describe "Semigroup instance" $ do prop "associativity" $ \x y z -> renderLine (x <> (y <> z)) `shouldBe` renderLine ((x <> y) <> z) it "trims trailing whitespace" $ line (space <> space <> space) `shouldFormatAs` [""] it "formats a trivial line" $ do line (string7 "word") `shouldFormatAs` ["word"] describe "rowOrStack" $ do it "joins single lines" $ rowOrStack (Just $ char7 ':') [line $ string7 "a", line $ string7 "b"] `shouldFormatAs` ["a:b"] it "splits when the first is multiline" $ rowOrStack (Just $ char7 ':') [mustBreak $ string7 "a", line $ string7 "b"] `shouldFormatAs` [ "a", "b" ] it "combines when only second is multiline" $ rowOrStack (Just $ char7 ':') [line $ string7 "a", mustBreak $ string7 "b"] `shouldFormatAs` ["a:b"] it "can result in single line" $ rowOrStack (Just $ char7 '-') [ rowOrStack (Just $ char7 '+') [ line $ string7 "a", line $ string7 "b" ], line $ string7 "c" ] `shouldFormatAs` ["a+b-c"] it "retains multiline" $ rowOrStack (Just $ char7 '-') [ rowOrStack (Just $ char7 '+') [ mustBreak $ string7 "a", line $ string7 "b" ], line $ string7 "c" ] `shouldFormatAs` [ "a", "b", "c" ] it "retains mustBreak" $ rowOrStack (Just $ char7 '-') [ rowOrStack (Just $ char7 '+') [ line $ string7 "a", mustBreak $ string7 "b" ], line $ string7 "c" ] `shouldFormatAs` ["a+b", "c"] describe "rowOrIndent" $ do it "joins single lines" $ rowOrIndent (Just $ char7 ':') [line $ string7 "a", line $ string7 "b"] `shouldFormatAs` ["a:b"] it "splits when the first is multiline" $ rowOrIndent (Just $ char7 ':') [mustBreak $ string7 "a", line $ string7 "b"] `shouldFormatAs` [ "a", " b" ] describe "prefix" $ do it "prefixes a single line" $ prefix 3 (string7 "::" <> space) (line $ string7 "A") `shouldFormatAs` [":: A"] it "pads remaining lines" $ prefix 3 (string7 "::" <> space) (stack $ fmap (line . string7) ["A", "B"]) `shouldFormatAs` [ ":: A", " B" ] describe "addSuffix" $ do it "suffixes a single line" $ addSuffix (string7 "...") (line $ string7 "A") `shouldFormatAs` ["A..."] it "suffixes the last line of a multiline block" $ addSuffix (string7 "...") (stack $ fmap (line . string7) ["A", "B"]) `shouldFormatAs` [ "A", "B..." ] shouldFormatAs :: Block -> [ByteString] -> IO () shouldFormatAs actual expected = B.toLazyByteString (render actual) `shouldBe` BS.unlines expected renderLine :: Line -> ByteString renderLine = B.toLazyByteString . render . line instance Arbitrary Line where arbitrary = oneof [ stringUtf8 <$> listOf1 (oneof $ fmap pure "ABC"), pure space, (<>) <$> arbitrary <*> arbitrary ]