Implement wordWrap and paginate

This commit is contained in:
Alexander Kobjolke 2023-08-25 23:13:00 +02:00
parent 67b691d410
commit b783faef1a
4 changed files with 62 additions and 5 deletions

View file

@ -70,4 +70,5 @@ test-suite spec
, base >=4.13 && <5 , base >=4.13 && <5
, hcat , hcat
, hspec , hspec
, quickcheck-instances
default-language: GHC2021 default-language: GHC2021

View file

@ -52,7 +52,7 @@ tests:
- hcat - hcat
- hspec - hspec
- QuickCheck - QuickCheck
# - quickcheck-instances - quickcheck-instances
# - quickcheck-text # - quickcheck-text
build-tools: hspec-discover build-tools: hspec-discover
verbatim: verbatim:

View file

@ -1,6 +1,9 @@
-- | Internal module in order to facilitate testability. -- | Internal module in order to facilitate testability.
module HCat.Internal where module HCat.Internal where
import Data.Text (Text)
import Data.Text qualified as T
-- | @parseArgs@ takes a list of strings and returns a single FilePath if there was exactly one element. -- | @parseArgs@ takes a list of strings and returns a single FilePath if there was exactly one element.
-- --
-- >>> parseArgs ["foo"] -- >>> parseArgs ["foo"]
@ -28,3 +31,39 @@ chunksOf n xs@(_ : _)
| otherwise = | otherwise =
let (chunk, rest) = splitAt n xs let (chunk, rest) = splitAt n xs
in chunk : chunksOf n rest in chunk : chunksOf n rest
-- | @wordWrap@ splits the given Text if it is longer than the given margin.
--
-- >>> :set -XOverloadedStrings
-- >>> wordWrap 3 "abcdef"
-- ["abc","def"]
--
-- >>> wordWrap 3 "abc"
-- ["abc"]
--
-- >>> wordWrap 3 "ab"
-- ["ab"]
wordWrap :: Int -> Text -> [Text]
wordWrap n text
| n > 0 && T.length text > n =
let (line, rest) = T.splitAt n text
in line : wordWrap n rest
| otherwise = pure text
data ScreenDimensions = ScreenDimensions
{ screenRows :: Int
, screenColumns :: Int
}
deriving (Show)
-- | @paginate@ transforms a given piece of Text into pages of lines that fit
-- onto the screen.
--
-- >>> paginate ScreenDimensions{screenRows = 2, screenColumns = 2} "foo bar baz"
-- ["fo\no \n","ba\nr \n","ba\nz\n"]
paginate :: ScreenDimensions -> Text -> Pages
paginate (ScreenDimensions rows cols) =
fmap T.unlines . chunksOf rows . concatMap (wordWrap cols) . T.lines
type Pages = [Page]
type Page = Text

View file

@ -1,12 +1,12 @@
-- {-# LANGUAGE GHC2021 #-}
module HCatSpec (spec) where module HCatSpec (spec) where
import HCat.Internal (chunksOf, parseArgs) import HCat.Internal
import Test.Hspec import Test.Hspec
import Test.Hspec.QuickCheck (prop) import Test.Hspec.QuickCheck (prop)
import Test.QuickCheck (Positive (getPositive))
import Test.QuickCheck (Positive (getPositive), getNonPositive)
import Test.QuickCheck.Instances.Text ()
spec :: Spec spec :: Spec
spec = do spec = do
@ -15,6 +15,7 @@ spec = do
parseArgs ["foo"] `shouldBe` Right "foo" parseArgs ["foo"] `shouldBe` Right "foo"
parseArgs [] `shouldBe` Left "No filename given!" parseArgs [] `shouldBe` Left "No filename given!"
parseArgs ["foo", "bar"] `shouldBe` Left "Only a single file is supported" parseArgs ["foo", "bar"] `shouldBe` Left "Only a single file is supported"
describe "chunksOf" $ do describe "chunksOf" $ do
prop "each chunk contains at most N items" $ \n xs -> prop "each chunk contains at most N items" $ \n xs ->
let chunkLengths = length <$> chunksOf n (xs :: [Int]) let chunkLengths = length <$> chunksOf n (xs :: [Int])
@ -25,3 +26,19 @@ spec = do
prop "the sum of all lengths is equal to the length of the input" $ \n xs -> prop "the sum of all lengths is equal to the length of the input" $ \n xs ->
let chunkLengths = length <$> chunksOf (getPositive n) (xs :: [Int]) let chunkLengths = length <$> chunksOf (getPositive n) (xs :: [Int])
in sum chunkLengths `shouldBe` length xs in sum chunkLengths `shouldBe` length xs
describe "wordWrap" do
prop "non positive margins result in empty result" $ \margin ->
wordWrap (getNonPositive margin) "abc" `shouldBe` ["abc"]
it "wraps the given text at the given margin" do
wordWrap 4 "abc" `shouldBe` ["abc"]
wordWrap 4 "abcdefg" `shouldBe` ["abcd", "efg"]
prop "concatenating the result equals the input" $ \txt ->
let wrapped = wordWrap 4 txt
in mconcat wrapped `shouldBe` txt
describe "paginate" do
it "wraps the given text at the given margin" do
paginate (ScreenDimensions 3 2) "abcdefghijkl" `shouldBe` ["ab\ncd\nef\n", "gh\nij\nkl\n"]