{-# LANGUAGE MultiWayIf #-}
module Text.Layout.Table.Justify
(
justify
, justifyText
, dimorphicSummands
, dimorphicSummandsBy
, mixedDimorphicSummandsBy
) where
import Control.Arrow
import Data.List
import Text.Layout.Table.Internal
import Text.Layout.Table.Primitives.Basic
import Text.Layout.Table.Position.Internal
import Text.Layout.Table.Vertical
justifyText :: Int -> String -> [String]
justifyText w = justify w . words
justify :: Int -> [String] -> [String]
justify width = mapInit pad (\(_, _, line) -> unwords line) . gather 0 0 []
where
pad (len, wCount, line) = unwords $ if len < width
then zipWith (++) line $ mixedDimorphicSpaces (width - len) (pred wCount) ++ [""]
else line
gather lineLen wCount line ws = case ws of
[] | null line -> []
| otherwise -> [(lineLen, wCount, reverse line)]
w : ws' ->
let wLen = length w
newLineLen = lineLen + 1 + wLen
reinit = gather wLen 1 [w] ws'
in if | null line -> reinit
| newLineLen <= width -> gather newLineLen (succ wCount) (w : line) ws'
| otherwise -> (lineLen, wCount, reverse line) : reinit
mapInit :: (a -> b) -> (a -> b) -> [a] -> [b]
mapInit _ _ [] = []
mapInit f g (x : xs) = go x xs
where
go y [] = [g y]
go y (y' : ys) = f y : go y' ys
dimorphicSpaces :: Int -> Int -> [String]
dimorphicSpaces = dimorphicSummandsBy spaces
mixedDimorphicSpaces :: Int -> Int -> [String]
mixedDimorphicSpaces = mixedDimorphicSummandsBy spaces
dimorphicSummands :: Int -> Int -> [Int]
dimorphicSummands = dimorphicSummandsBy id
dimorphicSummandsBy :: (Int -> a) -> Int -> Int -> [a]
dimorphicSummandsBy _ _ 0 = []
dimorphicSummandsBy f n splits = replicate r largeS ++ replicate (splits - r) smallS
where
(q, r) = n `divMod` splits
largeS = f $ succ q
smallS = f q
mixedDimorphicSummandsBy :: (Int -> a) -> Int -> Int -> [a]
mixedDimorphicSummandsBy f n splits = go r (splits - r)
where
go 0 s = replicate s smallS
go l 0 = replicate l largeS
go l s = largeS : smallS : go (pred l) (pred s)
(q, r) = n `divMod` splits
largeS = f $ succ q
smallS = f q