module Text.Layout.Table.Primitives.Basic
    ( 
      spaces
    , concatLines
      
    , fillLeft'
    , fillLeft
    , fillRight
    , fillCenter'
    , fillCenter
      
    , fitRightWith
    , fitLeftWith
    , fitCenterWith
      
    , applyMarkLeftWith
    , applyMarkRightWith
      
      
    , fillStart'
    , fillStart
    , fillEnd
    , fillBoth'
    , fillBoth
    ) where
import Text.Layout.Table.Spec.CutMark
import Data.List
spaces :: Int -> String
spaces = flip replicate ' '
concatLines :: [String] -> String
concatLines = intercalate "\n"
fillStart' :: a -> Int -> Int -> [a] -> [a]
fillStart' x i lenL l = replicate (i - lenL) x ++ l
fillStart :: a -> Int -> [a] -> [a]
fillStart x i l = fillStart' x i (length l) l
fillEnd :: a -> Int -> [a] -> [a]
fillEnd x i l = take i $ l ++ repeat x
fillBoth' :: a -> Int -> Int -> [a] -> [a]
fillBoth' x i lenL l =
    
    filler q ++ l ++ filler (q + r)
  where
    filler  = flip replicate x
    missing = i - lenL
    (q, r)  = missing `divMod` 2
fillBoth :: a -> Int -> [a] -> [a]
fillBoth x i l = fillBoth' x i (length l) l
fillLeft' :: Int -> Int -> String -> String
fillLeft' = fillStart' ' '
fillLeft :: Int -> String -> String
fillLeft = fillStart ' '
fillRight :: Int -> String -> String
fillRight = fillEnd ' '
fillCenter' :: Int -> Int -> String -> String
fillCenter' = fillBoth' ' '
fillCenter :: Int -> String -> String
fillCenter = fillBoth ' '
fitRightWith :: CutMark -> Int -> String -> String
fitRightWith cms i s =
    if length s <= i
    then fillRight i s
    else applyMarkRightWith cms $ take i s
         
fitLeftWith :: CutMark -> Int -> String -> String
fitLeftWith cms i s =
    if lenS <= i
    then fillLeft' i lenS s
    else applyMarkLeftWith cms $ drop (lenS - i) s
  where
    lenS = length s
fitCenterWith :: CutMark -> Int -> String -> String
fitCenterWith cms i s             =
    if diff >= 0
    then fillCenter' i lenS s
    else case splitAt halfLenS s of
        (ls, rs) -> addMarks $ drop (halfLenS - halfI) ls ++ take (halfI + r) rs
  where
    addMarks   = applyMarkLeftWith cms . if diff == (-1) then id else applyMarkRightWith cms
    diff       = i - lenS
    lenS       = length s
    halfLenS   = lenS `div` 2
    (halfI, r) = i `divMod` 2
applyMarkLeftWith :: CutMark -> String -> String
applyMarkLeftWith = applyMarkLeftBy leftMark
applyMarkRightWith :: CutMark -> String -> String
applyMarkRightWith cms = reverse . applyMarkLeftBy (reverse . rightMark) cms . reverse
applyMarkLeftBy :: (a -> String) -> a -> String -> String
applyMarkLeftBy f v = zipWith ($) $ map const (f v) ++ repeat id