parabox/app/Rendering.hs

99 lines
3.0 KiB
Haskell
Raw Normal View History

2022-12-02 10:54:31 -08:00
module Rendering where
import Data.Array
import Data.Map (Map)
import Data.Map qualified as Map
import Data.Set qualified as Set
import Graphics.Vty
import Model
2022-12-02 11:48:03 -08:00
unit :: Attr -> Int -> Char -> Image
unit a scale x =
vertCat (replicate scale (string a (replicate (2*scale) x)))
2022-12-02 10:54:31 -08:00
2022-12-02 11:48:03 -08:00
renderCell :: World -> Map Location Char -> Char -> Box -> Int -> Int -> Int -> Image
renderCell world locMap name box y x scale =
2022-12-02 15:28:05 -08:00
if boxWalls world box ! (y,x) then unit (boxColor box) scale wallChar
else case Map.lookup (Location name' y x) locMap of
2022-12-02 11:48:03 -08:00
Nothing -> unit (boxColor box) scale '░'
Just n ->
if scale == 1
then unit (boxColor (worldBoxes world Map.! n)) scale n
else renderBox world locMap (worldBoxes world Map.! n) n
2022-12-02 15:28:05 -08:00
(scale `div` boxSize world box)
where
name' =
case boxType box of
Original{} -> name
Link c -> c
wallChar =
case boxType box of
Original{} -> '▓'
Link{} -> '▒'
2022-12-02 10:54:31 -08:00
2022-12-02 11:48:03 -08:00
renderBox :: World -> Map Location Char -> Box -> Char -> Int -> Image
renderBox world locMap box name scale =
2022-12-02 10:54:31 -08:00
vertCat
[
horizCat
[
2022-12-02 11:48:03 -08:00
renderCell world locMap name box y x scale
2022-12-02 10:54:31 -08:00
| x <- [xlo .. xhi]
]
2022-12-02 15:28:05 -08:00
| let ((ylo,xlo),(yhi,xhi)) = bounds (boxWalls world box)
2022-12-02 10:54:31 -08:00
, y <- [ylo .. yhi]
]
drawNestedWorld :: World -> Image
drawNestedWorld world =
2022-12-02 15:46:42 -08:00
-- (3*81) + 81 + (3*81)
cropTop (81 + 2*border) $
cropLeft (2*(81 + 2*border)) $
cropBottom (2*81 + border) $
cropRight (2*(2*81 + border)) $
2022-12-02 10:54:31 -08:00
vertCat [
horizCat [
2022-12-02 11:48:03 -08:00
case stackedLoc world (Location name1 y_ x_) of
2022-12-02 15:46:42 -08:00
Nothing -> unit (withForeColor defAttr black) 81 '?'
2022-12-02 10:54:31 -08:00
Just (Location n y x) ->
2022-12-02 11:48:03 -08:00
let box = worldBoxes world Map.! n in
2022-12-02 15:46:42 -08:00
renderCell world locMap n box y x 81
2022-12-02 11:48:03 -08:00
| x_ <- [x1-1 .. x1+1]
2022-12-02 10:54:31 -08:00
]
2022-12-02 11:48:03 -08:00
| y_ <- [y1-1 .. y1+1]
2022-12-02 10:54:31 -08:00
]
where
border = 20
locMap = Map.fromList [(boxLocation loc, n) | (n, loc) <- Map.toList (worldBoxes world)]
-- name1 is the box the player is standing in
Location name0 _ _ = boxLocation (worldBoxes world Map.! worldMe world)
Location name1 y1 x1 = boxLocation (worldBoxes world Map.! name0)
stackedLoc :: World -> Location -> Maybe Location
stackedLoc world = go Set.empty
where
go visited loc | Set.member loc visited = Nothing
go visited loc@(Location b y x) =
do box <- Map.lookup b (worldBoxes world)
2022-12-02 15:28:05 -08:00
let bnds@((ylo,xlo),(yhi,xhi)) = bounds (boxWalls world box)
2022-12-02 10:54:31 -08:00
if inRange bnds (y, x)
then Just loc
else
let dx = overflow (xlo,xhi) x
dy = overflow (ylo,yhi) y
Location parent py px = boxLocation box
in go (Set.insert loc visited) (Location parent (py+dy) (px+dx))
overflow :: (Int, Int) -> Int -> Int
overflow (lo,hi) x
| x < lo = x - lo
| x > hi = x - hi
| otherwise = 0