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
|
2022-12-06 13:39:30 -08:00
|
|
|
import Data.List (intersperse, group)
|
2022-12-02 10:54:31 -08:00
|
|
|
import Graphics.Vty
|
|
|
|
import Model
|
|
|
|
|
2022-12-03 11:50:06 -08:00
|
|
|
border :: Int
|
|
|
|
border = 20
|
|
|
|
|
2022-12-06 13:39:30 -08:00
|
|
|
unit :: Attr -> Int -> Int -> Char -> Image
|
|
|
|
unit a h w c =
|
|
|
|
vertCat (replicate h (string a (replicate w c)))
|
2022-12-02 10:54:31 -08:00
|
|
|
|
2022-12-03 11:50:06 -08:00
|
|
|
drawBox :: Attr -> Int {- ^ width -} -> Int {- ^ height -} -> Image
|
2022-12-06 13:39:30 -08:00
|
|
|
drawBox a 2 1 = string a "[]"
|
|
|
|
drawBox a w 1 = string a ("[" ++ replicate (w-2) '-' ++ "]")
|
2022-12-03 11:50:06 -08:00
|
|
|
drawBox a w h = vertCat $
|
|
|
|
string a ('┌' : replicate (w-2) '─' ++ "┐") :
|
|
|
|
replicate (h-2) (string a ('│' : replicate (w-2) ' ' ++ "│")) ++
|
|
|
|
[string a ('└' : replicate (w-2) '─' ++ "┘")]
|
|
|
|
|
2022-12-06 13:39:30 -08:00
|
|
|
button :: Attr -> Int -> Int -> Image
|
|
|
|
button a 1 2 = string a "[]"
|
|
|
|
button a 1 n = string a ("[" ++ replicate (n-2) '-' ++ "]")
|
|
|
|
button a h w = vertCat $
|
|
|
|
string a ('┌' : replicate (w-2) '─' ++ "┐") :
|
|
|
|
replicate (h-2) (string a ('│' : replicate (w-2) '░' ++ "│")) ++
|
|
|
|
[string a ('└' : replicate (w-2) '─' ++ "┘")]
|
|
|
|
|
|
|
|
home :: Attr -> Int -> Int -> Image
|
|
|
|
home a 1 2 = string a "<>"
|
|
|
|
home a 1 w = string a ("<" ++ replicate (w-2) '=' ++ ">")
|
|
|
|
home a h w = vertCat $
|
|
|
|
string a ('╔' : replicate (w-2) '═' ++ "╗") :
|
|
|
|
replicate (h-2) (string a ('║' : replicate (w-2) '░' ++ "║")) ++
|
|
|
|
[string a ('╚' : replicate (w-2) '═' ++ "╝")]
|
|
|
|
|
|
|
|
renderCell :: World -> Map Location Char -> Char -> Box -> Int -> Int -> Int -> Int -> Image
|
|
|
|
renderCell world locMap name box y x h w =
|
|
|
|
if boxWalls world box ! (y,x) then unit (boxColor box) h w wallChar
|
2022-12-02 15:28:05 -08:00
|
|
|
else case Map.lookup (Location name' y x) locMap of
|
2022-12-02 11:48:03 -08:00
|
|
|
Just n ->
|
2022-12-06 13:39:30 -08:00
|
|
|
let box' = worldBoxes world Map.! n
|
|
|
|
in if h < boxSize world box'
|
|
|
|
then unit (boxColor box') h w n
|
|
|
|
else renderBox world locMap box' n
|
|
|
|
h w
|
2022-12-02 20:53:45 -08:00
|
|
|
Nothing
|
2022-12-06 13:39:30 -08:00
|
|
|
| Set.member loc (worldButtons world) -> button (boxColor box) h w
|
|
|
|
| loc == worldHome world -> home (boxColor box) h w
|
|
|
|
| otherwise -> unit (boxColor box) h w floorChar
|
2022-12-02 15:28:05 -08:00
|
|
|
where
|
2022-12-02 20:53:45 -08:00
|
|
|
loc = Location name' y x
|
2022-12-04 17:16:43 -08:00
|
|
|
name' = contentName world name box
|
2022-12-02 20:53:45 -08:00
|
|
|
wallChar =
|
|
|
|
case boxType box of
|
|
|
|
Original{} -> '▓'
|
|
|
|
Link{} -> '▒'
|
2022-12-04 15:59:22 -08:00
|
|
|
Infinity {} -> '▓'
|
|
|
|
Epsilon {} -> '▓'
|
|
|
|
floorChar =
|
|
|
|
case boxType box of
|
|
|
|
Original{} -> '░'
|
|
|
|
Link{} -> '·'
|
|
|
|
Infinity {} -> '∞'
|
|
|
|
Epsilon {} -> 'ε'
|
2022-12-02 10:54:31 -08:00
|
|
|
|
2022-12-04 17:16:43 -08:00
|
|
|
contentName :: World -> Char -> Box -> Char
|
|
|
|
contentName world name box =
|
|
|
|
case boxType box of
|
|
|
|
Original{} -> name
|
|
|
|
Link c -> c
|
|
|
|
Infinity c -> contentName world c (worldBoxes world Map.! c)
|
|
|
|
Epsilon{} -> name
|
|
|
|
|
2022-12-06 13:39:30 -08:00
|
|
|
renderBox :: World -> Map Location Char -> Box -> Char -> Int -> Int -> Image
|
|
|
|
renderBox world locMap box name h w =
|
2022-12-02 21:33:44 -08:00
|
|
|
vertCat [
|
|
|
|
horizCat [
|
2022-12-06 13:39:30 -08:00
|
|
|
renderCell world locMap name box y x h w
|
|
|
|
| (x,w) <- zip [xlo .. xhi] (divisions boxWidth w)
|
2022-12-02 10:54:31 -08:00
|
|
|
]
|
2022-12-06 13:39:30 -08:00
|
|
|
| (y,h) <- zip [ylo .. yhi] (divisions boxHeight h)
|
2022-12-02 10:54:31 -08:00
|
|
|
]
|
2022-12-06 13:39:30 -08:00
|
|
|
where
|
|
|
|
((ylo,xlo),(yhi,xhi)) = bounds (boxWalls world box)
|
|
|
|
boxWidth = xhi - xlo + 1
|
|
|
|
boxHeight = yhi - ylo + 1
|
2022-12-03 13:33:02 -08:00
|
|
|
|
2022-12-03 11:50:06 -08:00
|
|
|
render ::
|
|
|
|
Bool {- ^ show flat overlay -} ->
|
|
|
|
World ->
|
|
|
|
Picture
|
|
|
|
render flat world = picForLayers $
|
|
|
|
[ pad 98 12 0 0 $
|
2022-12-02 21:33:44 -08:00
|
|
|
string defAttr "██╗ ██╗██╗███╗ ██╗███╗ ██╗███████╗██████╗ " <->
|
|
|
|
string defAttr "██║ ██║██║████╗ ██║████╗ ██║██╔════╝██╔══██╗" <->
|
|
|
|
string defAttr "██║ █╗ ██║██║██╔██╗ ██║██╔██╗ ██║█████╗ ██████╔╝" <->
|
|
|
|
string defAttr "██║███╗██║██║██║╚██╗██║██║╚██╗██║██╔══╝ ██╔══██╗" <->
|
|
|
|
string defAttr "╚███╔███╔╝██║██║ ╚████║██║ ╚████║███████╗██║ ██║" <->
|
|
|
|
string defAttr " ╚══╝╚══╝ ╚═╝╚═╝ ╚═══╝╚═╝ ╚═══╝╚══════╝╚═╝ ╚═╝"
|
|
|
|
| winCondition world ] ++
|
2022-12-03 11:50:06 -08:00
|
|
|
(if flat then renderFlat locMap world else []) ++
|
|
|
|
[drawNestedWorld locMap world]
|
|
|
|
where
|
|
|
|
locMap = Map.fromList [(boxLocation loc, n) | (n, loc) <- Map.toList (worldBoxes world)]
|
|
|
|
|
|
|
|
renderFlat :: Map Location Char -> World -> [Image]
|
|
|
|
renderFlat locMap world =
|
|
|
|
[ pad offset 0 0 0 baseImage
|
|
|
|
, pad offset 0 0 0 $ drawBox borderAttr (imageWidth baseImage) (imageHeight baseImage)
|
|
|
|
]
|
|
|
|
where
|
|
|
|
borderAttr = defAttr `withForeColor` white `withBackColor` black
|
|
|
|
offset = max 0 ( (2*(81+2*border)+2 - imageWidth baseImage) `div` 2)
|
|
|
|
baseImage =
|
|
|
|
pad 2 1 2 1 $
|
|
|
|
horizCat $
|
|
|
|
intersperse (char borderAttr ' ')
|
2022-12-06 13:39:30 -08:00
|
|
|
[renderBox world locMap b n 18 36
|
2022-12-03 11:50:06 -08:00
|
|
|
| (n,b) <- Map.assocs (worldBoxes world)
|
2022-12-03 13:33:02 -08:00
|
|
|
, not (boxBoring b)]
|
2022-12-02 10:54:31 -08:00
|
|
|
|
2022-12-03 11:50:06 -08:00
|
|
|
drawNestedWorld :: Map Location Char -> World -> Image
|
|
|
|
drawNestedWorld locMap 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 21:33:44 -08:00
|
|
|
vertCat $
|
|
|
|
intersperse (char defAttr ' ')
|
|
|
|
[
|
|
|
|
horizCat $
|
|
|
|
intersperse (char defAttr ' ')
|
|
|
|
[
|
2022-12-02 19:33:27 -08:00
|
|
|
case stackedLoc world locMap (Location name1 y_ x_) of
|
2022-12-06 13:39:30 -08:00
|
|
|
Nothing -> unit (withForeColor defAttr black) 81 162 '?'
|
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-06 13:39:30 -08:00
|
|
|
renderCell world locMap n box y x 81 (81*2)
|
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
|
|
|
|
-- name1 is the box the player is standing in
|
2022-12-03 11:50:06 -08:00
|
|
|
Location name0 _ _ = myLocation world
|
2022-12-02 10:54:31 -08:00
|
|
|
Location name1 y1 x1 = boxLocation (worldBoxes world Map.! name0)
|
|
|
|
|
|
|
|
|
2022-12-02 19:33:27 -08:00
|
|
|
stackedLoc :: World -> Map Location Char -> Location -> Maybe Location
|
|
|
|
stackedLoc world locMap = go Set.empty
|
2022-12-02 10:54:31 -08:00
|
|
|
where
|
2022-12-04 15:59:22 -08:00
|
|
|
go visited loc@(Location b y x)
|
|
|
|
| Set.member loc visited =
|
|
|
|
do b' <- findInfinity world b
|
|
|
|
go visited (Location b' y x)
|
2022-12-02 10:54:31 -08:00
|
|
|
|
|
|
|
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
|
2022-12-02 19:33:27 -08:00
|
|
|
in fixup world locMap dy dx y x <$> go (Set.insert loc visited) (Location parent (py+dy) (px+dx))
|
2022-12-02 10:54:31 -08:00
|
|
|
|
|
|
|
|
|
|
|
overflow :: (Int, Int) -> Int -> Int
|
|
|
|
overflow (lo,hi) x
|
|
|
|
| x < lo = x - lo
|
|
|
|
| x > hi = x - hi
|
|
|
|
| otherwise = 0
|
2022-12-02 19:33:27 -08:00
|
|
|
|
|
|
|
fixup :: World ->
|
|
|
|
Map Location Char ->
|
|
|
|
Int ->
|
|
|
|
Int ->
|
|
|
|
Int ->
|
|
|
|
Int ->
|
|
|
|
Location ->
|
|
|
|
Location
|
|
|
|
fixup world locMap dy dx py px loc =
|
|
|
|
case Map.lookup loc locMap of
|
|
|
|
Nothing -> loc
|
|
|
|
Just name -> Location name (fixup1 ylo yhi dy py) (fixup1 xlo xhi dx px)
|
|
|
|
where
|
|
|
|
((ylo,xlo),(yhi,xhi)) = bounds (boxWalls world (worldBoxes world Map.! name))
|
|
|
|
|
|
|
|
fixup1 :: Int -> Int -> Int -> Int -> Int
|
|
|
|
fixup1 _ _ 0 i = i
|
|
|
|
fixup1 _ hi (-1) _ = hi
|
|
|
|
fixup1 lo _ 1 _ = lo
|
2022-12-06 13:39:30 -08:00
|
|
|
fixup1 _ _ _ _ = error "fixup1: bad delta"
|
|
|
|
|
|
|
|
divisions :: Int -> Int -> [Int]
|
|
|
|
divisions divs size =
|
|
|
|
map length $ group
|
|
|
|
[ round (
|
|
|
|
(fromIntegral i + 1 / 2)
|
|
|
|
/ fromIntegral size
|
|
|
|
* fromIntegral divs
|
|
|
|
- 1/2
|
|
|
|
)
|
|
|
|
| i <- [0 ..size-1]
|
|
|
|
]
|