Created
February 10, 2022 12:53
-
-
Save jarkkojs/315c9e64e075073a9d15ca73f7b29de2 to your computer and use it in GitHub Desktop.
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
module Maze where | |
import Control.Monad | |
import Foreign | |
import qualified Graphics.UI.SDL as SDL | |
import System.Random | |
import Data.List | |
import Data.Array | |
data Cell = Cell { | |
top :: Bool, | |
left :: Bool, | |
visited :: Bool | |
} deriving (Show, Eq) | |
type Maze = Array (Int, Int) Cell | |
newCell = Cell {top = True, left = True, visited = False} | |
newMaze :: Int -> Int -> Maze | |
newMaze rows columns = listArray ((0, 0), (rows - 1, columns - 1)) (repeat newCell) | |
genMaze maze (r, c) (seed:seeds) | |
| visited (maze ! (r, c)) == True = maze | |
| otherwise = foldl traverse maze' ((permutations neighbours) !! index) | |
where maze' = maze//[((r, c), (maze ! (r, c)) { visited = True })] | |
locs = [(r - 1, c), (r + 1, c), (r, c - 1), (r, c + 1)] | |
((_, _), (rmax, cmax)) = (bounds maze) | |
neighbours = [(r', c') | (r', c') <- locs, | |
r' >= 0 && r' <= rmax, c' >= 0 && c' <= cmax] | |
index = seed `mod` (length neighbours) | |
moveTo maze (r, c) (r', c') | |
| visited cell' = maze | |
| r' < r = maze//[((r, c), cell { top = False })] | |
| r' > r = maze//[((r', c'), cell' { top = False })] | |
| c' < c = maze//[((r, c), cell { left = False })] | |
| c' > c = maze//[((r', c'), cell' { left = False })] | |
| otherwise = error "Invalid move" | |
where cell = maze ! (r, c) | |
cell' = maze ! (r', c') | |
traverse maze' (r', c') = genMaze (moveTo maze' (r, c) (r', c')) (r', c') seeds | |
hline :: Int -> Int -> Int -> SDL.Pixel -> SDL.Surface -> IO () | |
hline x y width (SDL.Pixel pixel) screen = do | |
screenWidth <- return (SDL.surfaceGetWidth screen) | |
pixels <- castPtr `liftM` SDL.surfaceGetPixels screen | |
forM_ [0..(width - 1)] $ \dx -> do | |
pokeElemOff pixels (y * screenWidth + x + dx) pixel | |
vline :: Int -> Int -> Int -> SDL.Pixel -> SDL.Surface -> IO () | |
vline x y height (SDL.Pixel pixel) screen = do | |
screenWidth <- return (SDL.surfaceGetWidth screen) | |
pixels <- castPtr `liftM` SDL.surfaceGetPixels screen | |
forM_ [0..(height - 1)] $ \dy -> do | |
pokeElemOff pixels ((y + dy) * screenWidth + x) pixel | |
main :: IO() | |
main = do | |
startRow <- randomRIO (0 :: Int, rows - 1) | |
startColumn <- randomRIO (0 :: Int, columns - 1) | |
seeds <- replicateM (rows * columns) (randomRIO (0 :: Int, (max rows columns))) | |
maze <- return (genMaze (newMaze rows columns) (startRow, startColumn) seeds) | |
SDL.init [SDL.InitEverything] | |
screen <- SDL.setVideoMode screenWidth screenHeight 32 [] | |
hline 0 0 screenWidth whitePixel screen | |
hline 0 (screenHeight - 1) screenWidth whitePixel screen | |
vline 0 0 screenHeight whitePixel screen | |
vline (screenWidth - 1) 0 screenHeight whitePixel screen | |
forM (assocs maze) $ \((r, c), cell) -> | |
if (top cell) then do | |
hline (blockWidth * c) (blockHeight * r) blockWidth whitePixel screen | |
else do return () | |
forM (assocs maze) $ \((r, c), cell) -> | |
if (left cell) then do | |
vline (blockWidth * c) (blockHeight * r) blockHeight whitePixel screen | |
else do return () | |
SDL.flip screen | |
eventLoop | |
SDL.quit | |
where | |
eventLoop = SDL.waitEvent >>= checkEvent | |
checkEvent SDL.Quit = return() | |
checkEvent (SDL.KeyUp _) = return() | |
checkEvent _ = eventLoop | |
blockWidth = 32 | |
blockHeight = 32 | |
rows = 16 | |
columns = 16 | |
screenWidth = columns * blockWidth | |
screenHeight = rows * blockHeight | |
whitePixel = SDL.Pixel 0x00FFFFFF |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment