Conversation

type ReturnType<T> = TheirShit | OurShit | YourShit | MyShit | PossiblySomeOtherShit<T> | MightBeAMonad<T> | OrNot | T

1
0
0

@ohmrun I wrote this 2D maze in Haskell circa 2011 (not likely to compile today):

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

Ur welcome ;-)

1
0
1
@ohmrun Helped me to make all conclusions I ever need to make from that language so I guess it was worth it :-)
1
0
1

@jarkko Monads rule but there's always a little juju sprinkled in

1
0
0
@ohmrun I've found for some reason OCaml to be much more digestible at least for my brains. I see it also more in the wild.
1
0
0

@jarkko I've heard Haskell described as a foot bazuka. Haxe, my old favourite, is written in OCaml

1
0
2
@ohmrun Mathematically (as per field of category theory which is sort of "superset" of set theory) Haskell is more "perfect" but as a practical hammer like tool OCaml is IMHO so much more useful ;-)
1
0
1

@jarkko I've not written anything in it, but opam looks really solid

0
0
1