96 lines
3.3 KiB
Haskell
96 lines
3.3 KiB
Haskell
|
module Util where
|
||
|
|
||
|
import Affection as A
|
||
|
|
||
|
import Data.Matrix as M
|
||
|
|
||
|
-- internal imports
|
||
|
|
||
|
import Types
|
||
|
|
||
|
convertTileToImg :: Matrix TileState -> Matrix (Maybe ImgId)
|
||
|
convertTileToImg mat = fromLists conversion
|
||
|
where
|
||
|
conversion =
|
||
|
map (\(i, ls) -> map (uncurry $ convertTile i) (zip [1..] ls))
|
||
|
(zip [1..] (toLists mat))
|
||
|
convertTile irow icol tile =
|
||
|
case tile of
|
||
|
Wall -> Just (case neighWalls irow icol mat of
|
||
|
4 ->
|
||
|
ImgWallCross
|
||
|
3
|
||
|
| M.safeGet (irow + 1) icol mat /= Just Wall &&
|
||
|
M.safeGet (irow + 1) icol mat /= Just Door ->
|
||
|
ImgWallTNW
|
||
|
| M.safeGet irow (icol + 1) mat /= Just Wall &&
|
||
|
M.safeGet irow (icol + 1) mat /= Just Door ->
|
||
|
ImgWallTSW
|
||
|
| M.safeGet (irow - 1) icol mat /= Just Wall &&
|
||
|
M.safeGet (irow - 1) icol mat /= Just Door ->
|
||
|
ImgWallTSE
|
||
|
| otherwise ->
|
||
|
ImgWallTNE
|
||
|
2
|
||
|
| (M.safeGet (irow + 1) icol mat == Just Wall ||
|
||
|
M.safeGet (irow + 1) icol mat == Just Door) &&
|
||
|
(M.safeGet (irow - 1) icol mat == Just Wall ||
|
||
|
M.safeGet (irow - 1) icol mat == Just Door) ->
|
||
|
ImgWallDesc
|
||
|
| (M.safeGet irow (icol + 1) mat == Just Wall ||
|
||
|
M.safeGet irow (icol + 1) mat == Just Door) &&
|
||
|
(M.safeGet irow (icol - 1) mat == Just Wall ||
|
||
|
M.safeGet irow (icol - 1) mat == Just Door) ->
|
||
|
ImgWallAsc
|
||
|
| (M.safeGet (irow - 1) icol mat == Just Wall ||
|
||
|
M.safeGet (irow - 1) icol mat == Just Door) &&
|
||
|
(M.safeGet irow (icol - 1) mat == Just Wall ||
|
||
|
M.safeGet irow (icol - 1) mat == Just Door) ->
|
||
|
ImgWallCornerW
|
||
|
| (M.safeGet irow (icol - 1) mat == Just Wall ||
|
||
|
M.safeGet irow (icol - 1) mat == Just Door) &&
|
||
|
(M.safeGet (irow + 1) icol mat == Just Wall ||
|
||
|
M.safeGet (irow + 1) icol mat == Just Door) ->
|
||
|
ImgWallCornerS
|
||
|
| (M.safeGet (irow + 1) icol mat == Just Wall ||
|
||
|
M.safeGet (irow + 1) icol mat == Just Door) &&
|
||
|
(M.safeGet irow (icol + 1) mat == Just Wall ||
|
||
|
M.safeGet irow (icol + 1) mat == Just Door) ->
|
||
|
ImgWallCornerE
|
||
|
| otherwise ->
|
||
|
ImgWallCornerN
|
||
|
1
|
||
|
| M.safeGet (irow - 1) icol mat == Just Wall ||
|
||
|
M.safeGet (irow - 1) icol mat == Just Door ->
|
||
|
ImgWallDesc
|
||
|
| M.safeGet (irow + 1) icol mat == Just Wall ||
|
||
|
M.safeGet (irow + 1) icol mat == Just Door ->
|
||
|
ImgWallDesc
|
||
|
| M.safeGet irow (icol + 1) mat == Just Wall ||
|
||
|
M.safeGet irow (icol + 1) mat == Just Door ->
|
||
|
ImgWallAsc
|
||
|
| otherwise ->
|
||
|
ImgWallAsc
|
||
|
0 ->
|
||
|
ImgWallCross
|
||
|
_ ->
|
||
|
error "unexpected number if neighbouring walls"
|
||
|
)
|
||
|
_ ->
|
||
|
Nothing
|
||
|
|
||
|
neighWalls :: Int -> Int -> Matrix TileState -> Int
|
||
|
neighWalls row col mat =
|
||
|
Prelude.foldl (\acc (ir, ic) ->
|
||
|
if M.safeGet (row + ir) (col + ic) mat == Just Wall ||
|
||
|
M.safeGet (row + ir) (col + ic) mat == Just Door
|
||
|
then acc + 1
|
||
|
else acc
|
||
|
)
|
||
|
0
|
||
|
[ (0, -1)
|
||
|
, (-1, 0)
|
||
|
, (0, 1)
|
||
|
, (1, 0)
|
||
|
]
|