module Plant where import Input import Tile import Terminal.Game import Lens.Micro.Platform import qualified Data.Map as M import qualified Data.Tuple as T -- Everything non-modifiable (reader-ish) about a Screen. -- Room structure newtype Plant = Plant (M.Map Coords Tile) deriving (Eq, Show) defaultPlant :: Plant defaultPlant = Plant M.empty --------------- -- FUNCTIONS -- --------------- plantBoundaries :: Plant -> Coords plantBoundaries (Plant p) = (maximum rl, maximum cl) where (rl, cl) = unzip (M.keys p) plantList :: Plant -> [(Coords, Tile)] plantList (Plant p) = M.toList p addTile :: Coords -> Tile -> Plant -> Plant addTile cs t (Plant p) = Plant $ M.insert cs t p getTile :: Plant -> Coords -> Maybe Tile getTile (Plant p) cs = M.lookup cs p tickPlant :: Plant -> Plant tickPlant (Plant p) = Plant $ p & each %~ tickTile -- gluePlants is used to generate a "bigger map" (map + neighbours) when -- we perform, e.g., solid checks. Coords: size gluePlants :: Coords -> Plant -> [(Cardinal, Plant)] -> Plant gluePlants (rp, cp) (Plant p) cps = Plant $ M.unions (p : map f cps) where f :: (Cardinal, Plant) -> M.Map Coords Tile f (d, Plant wp) = M.mapKeys (u d) wp u :: Cardinal -> Coords -> Coords u N (r, c) = (r - rp, c ) u S (r, c) = (r + rp, c ) u W (r, c) = (r , c - cp) u E (r, c) = (r , c + cp) ---------- -- DRAW -- ---------- drawPlant :: Plant -> Plane drawPlant p = mergePlanes (blankPlane mw mh) planeCoordPlant where (mw, mh) = T.swap . plantBoundaries $ p planeCoordPlant :: [(Coords, Plane)] planeCoordPlant = plantList p & each . _2 %~ tilePlane