module Terminal.Game.Draw (module Terminal.Game.Draw,
(F.&)
) where
import Terminal.Game.Plane
import Text.LineBreak
import qualified Data.Function as F ( (&) )
import qualified Data.List as L
import qualified System.Console.ANSI as CA
type Draw = Plane -> Plane
(%) :: Coords -> Plane -> Draw
cds % p1 = \p2 -> pastePlane p1 p2 cds
infixl 4 %
(#) :: Plane -> Draw -> Plane
p # sf = sf p
infixl 8 #
mergePlanes :: Plane -> [(Coords, Plane)] -> Plane
mergePlanes p cps = L.foldl' addPlane p cps
where
addPlane :: Plane -> (Coords, Plane) -> Plane
addPlane bp (cs, tp) = bp F.& cs % tp
color :: CA.Color -> CA.ColorIntensity -> Plane -> Plane
color c i p = mapPlane (colorCell c i) p
bold :: Plane -> Plane
bold p = mapPlane boldCell p
invert :: Plane -> Plane
invert p = mapPlane reverseCell p
box :: Char -> Width -> Height -> Plane
box chr w h = seqCellsDim w h cells
where
cells = [((r, c), chr) | r <- [1..h], c <- [1..w]]
cell :: Char -> Plane
cell ch = box ch 1 1
textBox :: String -> Width -> Height -> Plane
textBox cs w h = transparent
where
hyp = Nothing
bf = BreakFormat (fromIntegral w) 4 '-' hyp
hcs = breakStringLn bf (take (fromIntegral $ w*h) cs)
f :: [String] -> [(Coords, Char)]
f css = concatMap (uncurry rf) (zip [1..] css)
where rf :: Integer -> String -> [(Coords, Char)]
rf cr ln = zip (zip (repeat cr) [1..]) ln
out = seqCellsDim w h (f hcs)
transparent = makeTransparent ' ' out
seqCellsDim :: Width -> Height -> [(Coords, Char)] -> Plane
seqCellsDim w h cells = seqCells (blankPlane w h) cells
seqCells :: Plane -> [(Coords, Char)] -> Plane
seqCells p cells = updatePlane p (map f cells)
where
f (cds, chr) = (cds, creaCell chr)