module Client.Image.LineWrap
  ( lineWrap
  , lineWrapPrefix
  , fullLineWrap
  , terminate
  ) where
import           Client.Image.PackedImage
import qualified Graphics.Vty.Image as Vty
import           Graphics.Vty.Attributes
import qualified Data.Text.Lazy as L
terminate ::
  Int        ->
  Vty.Image  ->
  Vty.Image 
terminate n img
  | Vty.imageWidth img == n = img
  | otherwise               = img Vty.<|> Vty.char defAttr ' '
fullLineWrap ::
  Int        ->
  Image'     ->
  [Image']  
fullLineWrap w img
  | iw <= w = [img]
  | otherwise = l : fullLineWrap w r
  where
    iw = imageWidth img
    (l,r) = splitImage w img
lineWrapPrefix ::
  Int        ->
  Image'     ->
  Image'     ->
  [Image']  
lineWrapPrefix w pfx img
  | 3*pfxW <= w = pfx <> char defAttr ' ' <> x :
                  map (pad<>) xs
  where
    pfxW = imageWidth pfx
    x:xs = lineWrap (w - pfxW - 1) img
    pad  = string defAttr (replicate (pfxW + 1) ' ')
lineWrapPrefix w pfx img = lineWrap w (pfx <> char defAttr ' ' <> img)
lineWrap ::
  Int       ->
  Image'    ->
  [Image'] 
lineWrap w img
  | imageWidth img <= w = [img] 
  | otherwise           = lineWrap' w img
lineWrap' ::
  Int       ->
  Image'    ->
  [Image'] 
lineWrap' w img
  | imgW == 0 = []
  | imgW <= w = [img]
  | otherwise = l : lineWrap' w (dropSpaces r)
  where
    imgW = imageWidth img
    x:xs = splitOptions img
    (l,r) = splitImage width img
    width
      | x <= w = go x xs
      | otherwise = w
    go y [] = min y w
    go y (z:zs)
      | z-y > w = w
      | z > w = y
      | otherwise = go z zs
splitOptions :: Image' -> [Int]
splitOptions
  = dropWhile (0==)
  . scanl1 (\x y -> 1 + x + y)
  . map (Vty.wcswidth . L.unpack)
  . L.split (' '==)
  . imageText
dropSpaces :: Image' -> Image'
dropSpaces img
  | n == 0    = img
  | otherwise = snd (splitImage n img)
  where
    n = fromIntegral $ L.length $ L.takeWhile (' '==) $ imageText img