module Penny.Cabin.Posts.Allocated (payeeAndAcct, Fields(..)) where
import Control.Applicative(Applicative((<*>), pure), (<$>))
import Data.Maybe (catMaybes, isJust)
import Data.List (intersperse)
import qualified Data.Foldable as Fdbl
import qualified Data.Sequence as Seq
import qualified Data.Traversable as T
import qualified Data.Text as X
import qualified Penny.Cabin.Chunk as C
import qualified Penny.Cabin.Row as R
import qualified Penny.Cabin.Posts.Allocate as A
import qualified Penny.Cabin.Colors as PC
import qualified Penny.Cabin.Posts.Fields as F
import qualified Penny.Cabin.Posts.Growers as G
import qualified Penny.Cabin.Posts.Meta as M
import qualified Penny.Cabin.Posts.Options as Options
import qualified Penny.Cabin.Posts.Options as O
import qualified Penny.Cabin.Posts.Spacers as S
import qualified Penny.Cabin.Posts.Spacers as Spacers
import qualified Penny.Cabin.TextFormat as TF
import qualified Penny.Lincoln as L
import qualified Penny.Lincoln.Queries as Q
import qualified Penny.Lincoln.HasText as HT
type Box = L.Box M.PostMeta
data Fields a = Fields {
payee :: a
, account :: a
} deriving (Eq, Show)
payeeAndAcct ::
G.Fields (Maybe Int)
-> Options.T
-> [Box]
-> Fields (Maybe ([R.ColumnSpec], Int))
payeeAndAcct fs os = allocateCells os ws where
ws = fieldWidth os ss fs rw
ss = O.spacers os
rw = O.width os
allocateCells ::
Options.T
-> Fields Int
-> [Box]
-> Fields (Maybe ([R.ColumnSpec], Int))
allocateCells os fs is = let
cellMakers = Fields allocPayee allocAcct
mkCells width maker =
if width > 0
then Just (map (maker width os) is)
else Nothing
unShrunkCells = mkCells <$> fs <*> cellMakers
in fmap (fmap removeExtraSpace) unShrunkCells
removeExtraSpace :: [R.ColumnSpec] -> ([R.ColumnSpec], Int)
removeExtraSpace cs = (trimmed, len) where
len = Fdbl.foldl' f 0 cs where
f acc c = max acc (Fdbl.foldl' g 0 (R.bits c)) where
g inAcc chk = max inAcc (C.unWidth . C.chunkWidth $ chk)
trimmed = map f cs where
f c = c { R.width = C.Width len }
fieldWidth ::
Options.T
-> Spacers.T Int
-> G.Fields (Maybe Int)
-> O.ReportWidth
-> Fields Int
fieldWidth os ss fs (O.ReportWidth rw) = let
flds = optionsToFields os
grownWidth = sumGrowersAndSpacers fs ss
widthForCells = rw grownWidth allocSpacerWidth
payeeSpacerWidth = if payee flds then abs (S.payee ss) else 0
acctSpacerWidth = if account flds then abs (S.account ss) else 0
allocSpacerWidth = payeeSpacerWidth + acctSpacerWidth
allocs = (\bool alloc -> if bool then alloc else A.allocation 0)
<$> flds
<*> Fields (O.payeeAllocation os) (O.accountAllocation os)
in if widthForCells < 1
then pure 0
else A.allocate allocs widthForCells
optionsToFields :: Options.T -> Fields Bool
optionsToFields os = let f = O.fields os in Fields {
payee = F.payee f
, account = F.account f }
sumSpacers ::
G.Fields (Maybe a)
-> Spacers.T Int
-> Int
sumSpacers fs =
sum
. map fst
. appearingSpacers
. catMaybes
. Fdbl.toList
. fmap toWidth
. pairedWithSpacers fs
toWidth :: (Maybe a, Maybe Int, t) -> Maybe (Int, t)
toWidth (maybeShowing, maybeWidth, tag) =
if isJust maybeShowing
then case maybeWidth of
Just w -> Just (w, tag)
Nothing -> Just (0, tag)
else Nothing
appearingSpacers :: [(Int, G.EFields)] -> [(Int, G.EFields)]
appearingSpacers ss = case ss of
[] -> []
l -> case snd $ last l of
G.ETotalQty -> l
t -> if t > G.ENumber
then init l
else l
pairedWithSpacers ::
G.Fields a
-> Spacers.T b
-> G.Fields (a, Maybe b, G.EFields)
pairedWithSpacers f s =
(\(a, b) c -> (a, b, c))
<$> G.pairWithSpacer f s
<*> G.eFields
sumGrowersAndSpacers ::
G.Fields (Maybe Int)
-> Spacers.T Int
-> Int
sumGrowersAndSpacers fs ss = spacers + flds where
spacers = sumSpacers fs ss
flds = Fdbl.foldr f 0 fs where
f maybeI acc = case maybeI of
Nothing -> acc
Just i -> acc + i
allocPayee :: Int -> Options.T -> Box -> R.ColumnSpec
allocPayee w os i = let
pb = L.boxPostFam i
ts = PC.colors (M.visibleNum . L.boxMeta $ i) (O.baseColors os)
c = R.ColumnSpec j (C.Width w) ts sq
j = R.LeftJustify
sq = case Q.payee pb of
Nothing -> []
Just pye -> let
wrapped =
Fdbl.toList
. TF.unLines
. TF.wordWrap w
. TF.txtWords
. HT.text
$ pye
toBit (TF.Words seqTxts) =
C.chunk ts
. X.unwords
. Fdbl.toList
$ seqTxts
in fmap toBit wrapped
in c
allocAcct :: Int -> Options.T -> Box -> R.ColumnSpec
allocAcct aw os i = let
pb = L.boxPostFam i
ts = PC.colors (M.visibleNum . L.boxMeta $ i) (O.baseColors os) in
R.ColumnSpec R.LeftJustify (C.Width aw) ts $ let
target = TF.Target aw
shortest = TF.Shortest . O.subAccountLength $ os
a = Q.account pb
ws = TF.Words . Seq.fromList . HT.textList $ a
(TF.Words shortened) = TF.shorten shortest target ws
in [C.chunk ts
. X.concat
. intersperse (X.singleton ':')
. Fdbl.toList
$ shortened]
instance Functor Fields where
fmap f i = Fields {
payee = f (payee i)
, account = f (account i) }
instance Applicative Fields where
pure a = Fields a a
ff <*> fa = Fields {
payee = payee ff (payee fa)
, account = account ff (account fa) }
instance Fdbl.Foldable Fields where
foldr f z flds =
f (payee flds) (f (account flds) z)
instance T.Traversable Fields where
traverse f flds =
Fields <$> f (payee flds) <*> f (account flds)