{-# LANGUAGE OverloadedLists #-} {-# LANGUAGE OverloadedStrings #-} {-# OPTIONS_GHC -Wno-orphans #-} module Text.PrettyPrint.Avh4.BlockExamplesSpec where import qualified Data.ByteString.Builder as B import Data.ByteString.Lazy.Char8 (ByteString) import qualified Data.ByteString.Lazy.Char8 as BS import Data.List.NonEmpty (NonEmpty (..)) import Test.Hspec import Test.QuickCheck import Text.PrettyPrint.Avh4.Block import Prelude hiding (break) spec :: Spec spec = describe "Block examples" $ do describe "Elm-like examples" $ do describe "function application" $ do let format breakFirst breakRest f (arg0 :| args) = spaceSeparatedOrIndentForce breakRest ( spaceSeparatedOrIndentForce breakFirst [f, arg0] :| args ) it "formats on a single line" $ format False False (line $ string7 "f") (fmap (line . string7) ["a", "b"]) `shouldFormatAs` ["f a b"] it "formats with all arguments split" $ format True False (line $ string7 "f") (fmap (line . string7) ["a", "b"]) `shouldFormatAs` [ "f", " a", " b" ] it "formats with first argument joined" $ format False True (line $ string7 "f") (fmap (line . string7) ["a", "b"]) `shouldFormatAs` [ "f a", " b" ] describe "list" $ do let format break (first :| rest) = spaceSeparatedOrStackForce break [ rowOrStackForce break Nothing ( formatEntry '[' first :| fmap (formatEntry ',') rest ), line (string7 "]") ] where formatEntry open = prefix 2 (char7 open <> space) it "formats single-line" $ format False (fmap (line . string7) ["a", "b", "c"]) `shouldFormatAs` ["[ a, b, c ]"] it "formats multiline" $ format True (fmap (line . string7) ["a", "b", "c"]) `shouldFormatAs` [ "[ a", ", b", ", c", "]" ] describe "record" $ do let format (first :| rest) = stack ( formatEntry '{' first :| fmap (formatEntry ',') rest <> [line (char7 '}')] ) where formatEntry open (key, break, value) = spaceSeparatedOrIndentForce break [ spaceSeparatedOrStack [line $ char7 open, key, line $ char7 '='], value ] it "formats single-line entries" $ format [ (line $ string7 "a", False, line $ string7 "1"), (line $ string7 "b", False, line $ string7 "2") ] `shouldFormatAs` [ "{ a = 1", ", b = 2", "}" ] it "formats multiline entries" $ format [ (line $ string7 "a", True, line $ string7 "1"), (line $ string7 "b", False, line $ string7 "2") ] `shouldFormatAs` [ "{ a =", " 1", ", b = 2", "}" ] describe "Javascript-like examples" $ do describe "if-else" $ do let format breakCond breakBodies (ifCond, ifBody) elseBody = spaceSeparatedOrStack [ spaceSeparatedOrIndentForce breakBodies [ rowOrStack Nothing [ rowOrIndentForce breakCond Nothing [ line $ string7 "if (", ifCond ], line $ string7 ") {" ], ifBody ], spaceSeparatedOrIndentForce (breakBodies || breakCond) [ line $ string7 "} else {", elseBody ], line $ string7 "}" ] it "formats single-line" $ format False False (line $ string7 "p", line $ string7 "a") (line $ string7 "b") `shouldFormatAs` ["if (p) { a } else { b }"] it "formats multiline" $ format False True (line $ string7 "p", line $ string7 "a") (line $ string7 "b") `shouldFormatAs` ["if (p) {", " a", "} else {", " b", "}"] it "formats multiline condition" $ format True False (line $ string7 "p", line $ string7 "a") (line $ string7 "b") `shouldFormatAs` ["if (", " p", ") {", " a", "} else {", " 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 ]