{-# LANGUAGE DeriveGeneric #-} ------------------------------------------------------------------------------- -- Screen datatypes and functions -- 2017 Francesco Ariis GPLv3 ------------------------------------------------------------------------------- -- a canvas where to draw our stuff module Terminal.Game.Plane where import qualified GHC.Generics as G import qualified Data.Array as A import qualified Data.List as L import qualified Data.List.Split as LS import qualified Data.Tuple as T ---------------- -- DATA TYPES -- ---------------- type Width = Integer type Height = Integer type Row = Integer type Column = Integer type Coords = (Row, Column) -- row, column, from TL (TL = 1, 1) type Bold = Bool type Reversed = Bool -- can be an ASCIIChar or a special, transparent character data Cell = CellChar Char Bold Reversed | Transparent deriving (Show, Eq, Ord, G.Generic) -- | A two-dimensional surface (Row, Column) where to blit stuff. newtype Plane = Plane { fromPlane :: A.Array Coords Cell } deriving (Show, Eq, G.Generic) ---------- -- CREA -- ---------- creaCell :: Char -> Cell creaCell ch = CellChar ch False False boldCell :: Cell -> Cell boldCell (CellChar c _ r) = CellChar c True r boldCell Transparent = Transparent reverseCell :: Cell -> Cell reverseCell (CellChar c b _) = CellChar c b True reverseCell Transparent = Transparent -- | Creates 'Plane' from 'String', good way to import ASCII -- art/diagrams. stringPlane :: String -> Plane stringPlane t = stringPlaneGeneric Nothing t -- | Same as 'stringPlane', but with transparent 'Char'. stringPlaneTrans :: Char -> String -> Plane stringPlaneTrans c t = stringPlaneGeneric (Just c) t -- | Creates an empty, opaque 'Plane'. blankPlane :: Width -> Height -> Plane blankPlane w h = listPlane (h, w) (repeat $ creaCell ' ') -- add transparency to a plane, matching a given character addVitrum :: Char -> Plane -> Plane addVitrum tc p = mapPlane f p where f cl | cellChar cl == tc = Transparent | otherwise = cl ----------- -- SLICE -- ----------- -- paste one plane over the other at a certain position (p1 gets over p2). -- Remember that coordinates start from bottom left! -- Maybe char = possible transparency pastePlane :: Plane -> Plane -> Coords -> Plane pastePlane p1 p2 (r, c) = updatePlane p2 filtered where cs = assocsPlane p1 (w2, h2) = planeSize p2 traslated = fmap (\((r1, c1), cl) -> ((r1 + r - 1, c1 + c -1), cl)) cs filtered = filter (\x -> inside x && solid x) traslated inside ((r1, c1), _) | r1 >= 1 && r1 <= h2 && c1 >= 1 && c1 <= w2 = True | otherwise = False solid (_, Transparent) = False solid _ = True ------------- -- INQUIRE -- ------------- planeSize :: Plane -> (Width, Height) planeSize p = T.swap . snd $ A.bounds (fromPlane p) cellChar :: Cell -> Char cellChar (CellChar ch _ _) = ch cellChar Transparent = ' ' isBold :: Cell -> Bool isBold (CellChar _ b _) = b isBold _ = False isReversed :: Cell -> Bool isReversed (CellChar _ _ r) = r isReversed _ = False assocsPlane :: Plane -> [(Coords, Cell)] assocsPlane p = A.assocs (fromPlane p) -- an '\n' divided (and ended) String ready to be written on file paperPlane :: Plane -> String paperPlane p = unlines . LS.chunksOf w . map cellChar . A.elems $ fromPlane p where w :: Int w = fromIntegral . fst . planeSize $ p ----------------- -- ANCILLARIES -- ----------------- -- faux map mapPlane :: (Cell -> Cell) -> Plane -> Plane mapPlane f (Plane a) = Plane $ fmap f a -- Array.// updatePlane :: Plane -> [(Coords, Cell)] -> Plane updatePlane (Plane a) kcs = Plane $ a A.// kcs listPlane :: Coords -> [Cell] -> Plane listPlane (r, c) cs = Plane $ A.listArray ((1,1), (r, c)) cs stringPlaneGeneric :: Maybe Char -> String -> Plane stringPlaneGeneric mc t = vitrous where lined = lines t h :: Integer h = L.genericLength lined w :: Integer w = maximum (map L.genericLength lined) pad :: Integer -> String -> String pad mw tl = take (fromIntegral mw) (tl ++ repeat ' ') padded :: [String] padded = map (pad w) lined celled :: [Cell] celled = map creaCell . concat $ padded plane :: Plane plane = listPlane (h, w) celled vitrous :: Plane vitrous = case mc of Just c -> addVitrum c plane Nothing -> plane