2013-11-29 13:21:58 +04:00
|
|
|
{-# LANGUAGE TemplateHaskell #-}
|
2013-10-25 01:40:48 +04:00
|
|
|
module Main where
|
|
|
|
|
|
|
|
import Graphics.Vty
|
|
|
|
|
|
|
|
import Data.Array
|
2014-01-27 01:25:13 +04:00
|
|
|
import Data.Default (def)
|
2013-10-25 01:40:48 +04:00
|
|
|
|
|
|
|
import Control.Applicative
|
|
|
|
import Control.Monad
|
|
|
|
import Control.Monad.RWS
|
|
|
|
|
|
|
|
import System.Random
|
|
|
|
|
2014-08-02 02:34:25 +04:00
|
|
|
data Player = Player
|
|
|
|
{ playerX :: Int
|
|
|
|
, playerY :: Int
|
2013-11-20 23:43:13 +04:00
|
|
|
} deriving (Show,Eq)
|
2013-10-25 01:40:48 +04:00
|
|
|
|
|
|
|
data World = World
|
2014-08-02 02:34:25 +04:00
|
|
|
{ player :: Player
|
2013-10-25 01:40:48 +04:00
|
|
|
, level :: Level
|
|
|
|
}
|
|
|
|
deriving (Show,Eq)
|
|
|
|
|
|
|
|
data Level = Level
|
2014-08-02 02:28:16 +04:00
|
|
|
{ levelStart :: (Int, Int)
|
|
|
|
, levelEnd :: (Int, Int)
|
2014-08-02 02:32:09 +04:00
|
|
|
, levelGeo :: Geo
|
2014-08-02 02:35:02 +04:00
|
|
|
-- building the geo image is expensive. Cache it. Though VTY should go
|
|
|
|
-- through greater lengths to avoid the need to cache images.
|
2014-08-02 02:28:16 +04:00
|
|
|
, levelGeoImage :: Image
|
2013-10-25 01:40:48 +04:00
|
|
|
}
|
|
|
|
deriving (Show,Eq)
|
|
|
|
|
|
|
|
data LevelPiece
|
|
|
|
= EmptySpace
|
|
|
|
| Rock
|
|
|
|
deriving (Show, Eq)
|
|
|
|
|
|
|
|
type Game = RWST Vty () World IO
|
2014-08-02 02:32:09 +04:00
|
|
|
type Geo = Array (Int, Int) LevelPiece
|
2013-10-25 01:40:48 +04:00
|
|
|
|
2014-08-02 02:28:16 +04:00
|
|
|
main :: IO ()
|
2014-08-02 02:28:37 +04:00
|
|
|
main = do
|
2014-01-27 01:25:13 +04:00
|
|
|
vty <- mkVty def
|
2014-04-12 04:51:13 +04:00
|
|
|
level0 <- mkLevel 1
|
2014-08-02 02:34:25 +04:00
|
|
|
let world0 = World (Player (fst $ levelStart level0) (snd $ levelStart level0)) level0
|
2014-04-12 04:51:13 +04:00
|
|
|
(_finalWorld, ()) <- execRWST (play >> updateDisplay) vty world0
|
2013-10-25 01:40:48 +04:00
|
|
|
shutdown vty
|
|
|
|
|
2014-08-02 02:28:16 +04:00
|
|
|
mkLevel :: Int -> IO Level
|
2013-11-25 07:48:40 +04:00
|
|
|
mkLevel difficulty = do
|
|
|
|
let size = 80 * difficulty
|
2014-04-12 04:51:13 +04:00
|
|
|
[levelWidth, levelHeight] <- replicateM 2 $ randomRIO (size,size)
|
|
|
|
let randomP = (,) <$> randomRIO (2, levelWidth-3) <*> randomRIO (2, levelHeight-3)
|
2013-11-25 07:48:40 +04:00
|
|
|
start <- randomP
|
|
|
|
end <- randomP
|
2013-10-26 20:43:16 +04:00
|
|
|
-- first the base geography: all rocks
|
2014-08-02 02:13:34 +04:00
|
|
|
let baseGeo = array ((0,0), (levelWidth-1, levelHeight-1))
|
2014-04-12 04:51:13 +04:00
|
|
|
[((x,y),Rock) | x <- [0..levelWidth-1], y <- [0..levelHeight-1]]
|
2013-11-20 23:43:13 +04:00
|
|
|
-- next the empty spaces that make the rooms
|
2013-11-25 07:48:40 +04:00
|
|
|
-- for this we generate a number of center points
|
|
|
|
centers <- replicateM (2 ^ difficulty + difficulty) randomP
|
|
|
|
-- generate rooms for all those points, plus the start and end
|
2014-04-12 04:51:13 +04:00
|
|
|
geo <- foldM (addRoom levelWidth levelHeight) baseGeo (start : end : centers)
|
|
|
|
return $ Level start end geo (buildGeoImage geo)
|
2013-11-20 23:43:13 +04:00
|
|
|
|
2014-08-02 02:32:09 +04:00
|
|
|
addRoom :: Int -> Int -> Geo -> (Int, Int) -> IO Geo
|
2014-04-12 04:51:13 +04:00
|
|
|
addRoom levelWidth levelHeight geo (centerX, centerY) = do
|
2013-11-20 23:43:13 +04:00
|
|
|
size <- randomRIO (5,15)
|
2014-04-12 04:51:13 +04:00
|
|
|
let xMin = max 1 (centerX - size)
|
|
|
|
xMax = min (levelWidth - 1) (centerX + size)
|
|
|
|
yMin = max 1 (centerY - size)
|
|
|
|
yMax = min (levelHeight - 1) (centerY + size)
|
|
|
|
let room = [((x,y), EmptySpace) | x <- [xMin..xMax - 1], y <- [yMin..yMax - 1]]
|
2013-11-20 23:56:27 +04:00
|
|
|
return (geo // room)
|
2013-10-25 01:40:48 +04:00
|
|
|
|
2014-08-02 02:28:16 +04:00
|
|
|
pieceA, dumpA :: Attr
|
2014-04-12 04:51:13 +04:00
|
|
|
pieceA = defAttr `withForeColor` blue `withBackColor` green
|
|
|
|
dumpA = defAttr `withStyle` reverseVideo
|
2013-10-25 01:40:48 +04:00
|
|
|
|
2014-08-02 02:28:16 +04:00
|
|
|
play :: Game ()
|
2013-10-25 01:40:48 +04:00
|
|
|
play = do
|
2014-04-12 04:51:13 +04:00
|
|
|
updateDisplay
|
|
|
|
done <- processEvent
|
2013-10-25 01:40:48 +04:00
|
|
|
unless done play
|
|
|
|
|
2014-08-02 02:28:16 +04:00
|
|
|
processEvent :: Game Bool
|
2014-04-12 04:51:13 +04:00
|
|
|
processEvent = do
|
|
|
|
k <- ask >>= liftIO . nextEvent
|
2013-10-25 01:40:48 +04:00
|
|
|
if k == EvKey KEsc []
|
|
|
|
then return True
|
|
|
|
else do
|
|
|
|
case k of
|
2014-01-19 12:19:56 +04:00
|
|
|
EvKey (KChar 'r') [MCtrl] -> ask >>= liftIO . refresh
|
2014-08-02 02:34:25 +04:00
|
|
|
EvKey KLeft [] -> movePlayer (-1) 0
|
|
|
|
EvKey KRight [] -> movePlayer 1 0
|
|
|
|
EvKey KUp [] -> movePlayer 0 (-1)
|
|
|
|
EvKey KDown [] -> movePlayer 0 1
|
2013-10-25 01:40:48 +04:00
|
|
|
_ -> return ()
|
|
|
|
return False
|
|
|
|
|
2014-08-02 02:34:25 +04:00
|
|
|
movePlayer :: Int -> Int -> Game ()
|
|
|
|
movePlayer dx dy = do
|
2013-10-25 01:40:48 +04:00
|
|
|
world <- get
|
2014-08-02 02:34:25 +04:00
|
|
|
let Player x y = player world
|
2013-11-20 23:56:27 +04:00
|
|
|
let x' = x + dx
|
|
|
|
y' = y + dy
|
2014-08-02 02:35:02 +04:00
|
|
|
-- this is only valid because the level generation assures the border is
|
|
|
|
-- always Rock
|
2014-08-02 02:28:16 +04:00
|
|
|
case levelGeo (level world) ! (x',y') of
|
2014-08-02 02:34:25 +04:00
|
|
|
EmptySpace -> put $ world { player = Player x' y' }
|
2013-11-20 23:56:27 +04:00
|
|
|
_ -> return ()
|
2013-10-25 01:40:48 +04:00
|
|
|
|
2014-04-12 04:51:13 +04:00
|
|
|
updateDisplay :: Game ()
|
|
|
|
updateDisplay = do
|
|
|
|
let info = string defAttr "Move with the arrows keys. Press ESC to exit."
|
2014-08-02 02:34:25 +04:00
|
|
|
-- determine offsets to place the player in the center of the level.
|
2014-04-12 04:51:13 +04:00
|
|
|
(w,h) <- asks outputIface >>= liftIO . displayBounds
|
2014-08-02 02:34:25 +04:00
|
|
|
thePlayer <- gets player
|
|
|
|
let ox = (w `div` 2) - playerX thePlayer
|
|
|
|
oy = (h `div` 2) - playerY thePlayer
|
2014-08-02 02:35:02 +04:00
|
|
|
-- translate the world images to place the player in the center of the
|
|
|
|
-- level.
|
2014-08-02 02:28:16 +04:00
|
|
|
world' <- map (translate ox oy) <$> worldImages
|
2014-04-12 04:51:13 +04:00
|
|
|
let pic = picForLayers $ info : world'
|
2013-11-20 23:43:13 +04:00
|
|
|
vty <- ask
|
|
|
|
liftIO $ update vty pic
|
|
|
|
|
2014-08-02 02:37:08 +04:00
|
|
|
--
|
|
|
|
-- Image-generation functions
|
|
|
|
--
|
|
|
|
|
2014-08-02 02:28:16 +04:00
|
|
|
worldImages :: Game [Image]
|
|
|
|
worldImages = do
|
2014-08-02 02:34:25 +04:00
|
|
|
thePlayer <- gets player
|
2014-04-12 04:51:13 +04:00
|
|
|
theLevel <- gets level
|
2014-08-02 02:34:25 +04:00
|
|
|
let playerImage = translate (playerX thePlayer) (playerY thePlayer) (char pieceA '@')
|
|
|
|
return [playerImage, levelGeoImage theLevel]
|
2013-11-21 03:53:15 +04:00
|
|
|
|
2014-08-02 02:37:08 +04:00
|
|
|
imageForGeo :: LevelPiece -> Image
|
|
|
|
imageForGeo EmptySpace = char (defAttr `withBackColor` green) ' '
|
|
|
|
imageForGeo Rock = char defAttr 'X'
|
|
|
|
|
2014-08-02 02:32:09 +04:00
|
|
|
buildGeoImage :: Geo -> Image
|
2014-04-12 04:51:13 +04:00
|
|
|
buildGeoImage geo =
|
|
|
|
let (geoWidth, geoHeight) = snd $ bounds geo
|
2014-08-02 02:35:02 +04:00
|
|
|
-- seems like a the repeated index operation should be removable. This is
|
|
|
|
-- not performing random access but (presumably) access in order of index.
|
2014-04-12 04:51:13 +04:00
|
|
|
in vertCat [ geoRow
|
|
|
|
| y <- [0..geoHeight-1]
|
|
|
|
, let geoRow = horizCat [ i
|
|
|
|
| x <- [0..geoWidth-1]
|
|
|
|
, let i = imageForGeo (geo ! (x,y))
|
|
|
|
]
|
|
|
|
]
|