module Client.Image.Layout (scrollAmount, drawLayout) where
import Control.Lens
import Client.State
import Client.State.Focus
import Client.Configuration (LayoutMode(..))
import Client.Image.PackedImage (Image', unpackImage)
import Client.Image.StatusLine (statusLineImage, minorStatusLineImage)
import Client.Image.Textbox
import Client.Image.LineWrap (lineWrap, terminate)
import Client.Image.Palette
import Client.View
import Graphics.Vty.Image
import Graphics.Vty.Attributes (defAttr)
drawLayout ::
ClientState ->
(Int, Int, Int, Image)
drawLayout st =
case view clientLayout st of
TwoColumn | not (null extrafocus) -> drawLayoutTwo st extrafocus
_ -> drawLayoutOne st extrafocus
where
extrafocus = clientExtraFocuses st
drawLayoutOne ::
ClientState ->
[Focus] ->
(Int, Int, Int, Image)
drawLayoutOne st extrafocus =
(overscroll, pos, nextOffset, output)
where
w = view clientWidth st
h:hs = splitHeights (rows - saveRows) (length extraLines)
scroll = view clientScroll st
(overscroll, pos, nextOffset, main) =
drawMain w (saveRows + h) scroll st
output = vertCat $ reverse
$ main
: [ drawExtra st w h' foc imgs
| (h', (foc, imgs)) <- zip hs extraLines]
rows = view clientHeight st
saveRows = 1 + imageHeight (statusLineImage w st)
extraLines = [ (focus', viewLines focus' FocusMessages w st)
| focus' <- extrafocus ]
drawLayoutTwo ::
ClientState ->
[Focus] ->
(Int, Int, Int, Image)
drawLayoutTwo st extrafocus =
(overscroll, pos, nextOffset, output)
where
[wl,wr] = divisions (view clientWidth st - 1) 2
hs = divisions (rows - length extraLines) (length extraLines)
scroll = view clientScroll st
output = main <|> divider <|> extraImgs
extraImgs = vertCat $ reverse
[ drawExtra st wr h' foc imgs
| (h', (foc, imgs)) <- zip hs extraLines]
(overscroll, pos, nextOffset, main) =
drawMain wl rows scroll st
pal = clientPalette st
divider = charFill (view palWindowDivider pal) ' ' 1 rows
rows = view clientHeight st
extraLines = [ (focus', viewLines focus' FocusMessages wr st)
| focus' <- extrafocus ]
drawMain ::
Int ->
Int ->
Int ->
ClientState ->
(Int,Int,Int,Image)
drawMain w h scroll st = (overscroll, pos, nextOffset, msgs <-> bottomImg)
where
focus = view clientFocus st
subfocus = view clientSubfocus st
msgLines = viewLines focus subfocus w st
(overscroll, msgs) = messagePane w h' scroll msgLines
h' = max 0 (h - imageHeight bottomImg)
bottomImg = statusLineImage w st <-> tbImage
(pos, nextOffset, tbImage) = textboxImage w st
drawExtra ::
ClientState ->
Int ->
Int ->
Focus ->
[Image'] ->
Image
drawExtra st w h focus lineImages =
msgImg <-> unpackImage (minorStatusLineImage focus w True st)
where
(_, msgImg) = messagePane w h 0 lineImages
messagePane ::
Int ->
Int ->
Int ->
[Image'] ->
(Int, Image)
messagePane w h scroll images = (overscroll, img)
where
vimg = assemble emptyImage images
vimg1 = cropBottom h vimg
img = charFill defAttr ' ' w (h - imageHeight vimg1)
<-> vimg1
overscroll = vh - imageHeight vimg
vh = h + scroll
assemble acc _ | imageHeight acc >= vh = cropTop vh acc
assemble acc [] = acc
assemble acc (x:xs) = assemble (this <-> acc) xs
where
this = vertCat
$ map (terminate w . unpackImage)
$ lineWrap w x
splitHeights ::
Int ->
Int ->
[Int]
splitHeights h ex = divisions (h - ex) (1 + ex)
divisions ::
Int ->
Int ->
[Int]
divisions x y
| y <= 0 = []
| otherwise = replicate r (q+1) ++ replicate (y-r) q
where
(q,r) = quotRem (max 0 x) y
scrollAmount ::
ClientState ->
Int
scrollAmount st =
case view clientLayout st of
TwoColumn -> h
OneColumn -> head (splitHeights h ex)
where
layout = view clientLayout st
h = view clientHeight st - bottomSize
ex = length (clientExtraFocuses st)
bottomSize = 1
+ imageHeight (statusLineImage mainWidth st)
mainWidth =
case layout of
TwoColumn -> head (divisions (view clientWidth st - 1) 2)
OneColumn -> view clientWidth st