module Penny.Cabin.TextFormat (
Lines(Lines, unLines),
Words(Words, unWords),
CharsPerLine(unCharsPerLine),
txtWords,
wordWrap,
Target(Target, unTarget),
Shortest(Shortest, unShortest),
shorten) where
import qualified Control.Monad.Trans.State as St
import qualified Data.Foldable as F
import Data.Sequence ((|>), ViewR((:>)), ViewL((:<)))
import qualified Data.Sequence as S
import qualified Data.Text as X
import qualified Data.Traversable as T
data Lines = Lines { unLines :: S.Seq Words } deriving Show
data Words = Words { unWords :: S.Seq X.Text } deriving Show
newtype CharsPerLine =
CharsPerLine { unCharsPerLine :: Int } deriving Show
txtWords :: X.Text -> Words
txtWords = Words . S.fromList . X.words
wordWrap :: Int -> Words -> Lines
wordWrap l (Words wsq) =
if l < 1
then Lines (S.empty)
else F.foldl f (Lines S.empty) wsq where
f (Lines sws) w = let
(back, ws) = case S.viewr sws of
S.EmptyR -> (S.empty, Words S.empty)
(b :> x) -> (b, x)
in case addWord l ws w of
(Just ws') -> Lines $ back |> ws'
Nothing ->
if X.length w > l
then addPartialWords l (Lines sws) w
else Lines (back |> ws |> (Words (S.singleton w)))
lenWords :: Words -> Int
lenWords (Words s) = case S.length s of
0 -> 0
l -> (F.sum . fmap X.length $ s) + (l 1)
addWord :: Int -> Words -> X.Text -> Maybe Words
addWord l (Words ws) w =
let words' = Words (ws |> w)
in if lenWords words' > l
then Nothing
else Just words'
addPartialWord :: Int -> Words -> X.Text -> (Words, X.Text)
addPartialWord l (Words ws) t = case addWord l (Words ws) t of
(Just ws') -> (ws', X.empty)
Nothing ->
let maxChars =
if S.null ws then l
else max 0 (l lenWords (Words ws) 1)
(begin, end) = X.splitAt maxChars t
in (Words (if X.null begin then ws else ws |> begin), end)
addPartialWords :: Int -> Lines -> X.Text -> Lines
addPartialWords l (Lines wsq) t = let
(back, ws) = case S.viewr wsq of
S.EmptyR -> (S.empty, Words S.empty)
(b :> x) -> (b, x)
(rw, rt) = addPartialWord l ws t
in if X.null rt
then Lines (back |> rw)
else addPartialWords l (Lines (back |> rw |> Words (S.empty))) rt
newtype Target = Target { unTarget :: Int } deriving Show
newtype Shortest = Shortest { unShortest :: Int } deriving Show
shorten :: Shortest -> Target -> Words -> Words
shorten (Shortest s) (Target t) wsa@(Words wsq) = let
nToRemove = max (lenWords wsa t) 0
(allWords, _) = shortenUntilOne s nToRemove wsq
in stripWordsUntil t (Words allWords)
shortenUntil :: Int -> Int -> X.Text -> (X.Text, Int)
shortenUntil by shortest t = let
removable = max (X.length t shortest) 0
toRemove = min removable (max by 0)
prefix = X.length t toRemove
in (X.take prefix t, toRemove)
shortenSt :: Int -> X.Text -> St.State Int X.Text
shortenSt shortest t = do
by <- St.get
let (r, nRemoved) = shortenUntil by shortest t
St.put (by nRemoved)
return r
shortenEachInList ::
T.Traversable t
=> Int
-> Int
-> t X.Text
-> (t X.Text, Int)
shortenEachInList shortest by ts = (r, left) where
k = T.mapM (shortenSt shortest) ts
(r, left) = St.runState k by
shortenUntilOne ::
T.Traversable t
=> Int
-> Int
-> t X.Text
-> (t X.Text, Int)
shortenUntilOne shortest by ts = let
r@(ts', left) = shortenEachInList shortest by ts
in if shortest == 1 || left == 0
then r
else shortenUntilOne (pred shortest) left ts'
stripWordsUntil :: Int -> Words -> Words
stripWordsUntil i wsa@(Words ws) = case S.viewl ws of
S.EmptyL -> Words (S.empty)
(_ :< rest) ->
if lenWords wsa <= (max i 0)
then wsa
else stripWordsUntil (max i 0) (Words rest)
_words :: Words
_words = Words . S.fromList . map X.pack $ ws where
ws = [ "these", "are", "fragilisticwonderfulgood",
"good", "", "x", "xy", "xyza",
"longlonglongword" ]