Removed random in favor of future static maps

This commit is contained in:
Ivy 2021-02-14 23:14:57 +01:00
parent f7aefb1a54
commit 190c3a029f
5 changed files with 7 additions and 16 deletions

View File

@ -29,5 +29,4 @@ executable roguelike
matrix,
unordered-containers,
microlens-th,
microlens,
random
microlens

View File

@ -1,7 +1,6 @@
module Dungeon where
import Data.Matrix
import System.Random
data Cell = Solid | Empty
@ -14,12 +13,8 @@ newtype Dungeon = Dungeon (Matrix Cell)
instance Show Dungeon where
show (Dungeon m) = unlines . map (concatMap show) $ toLists m
makeDungeon :: (RandomGen r) => r -> Int -> Int -> Dungeon
makeDungeon gen w h = Dungeon $ Data.Matrix.fromList h w (randomCells gen)
where randomCells g = let (c,nGen) = randomR (0 :: Int,1 :: Int) g
in case c of 0 -> Solid : randomCells nGen
1 -> Empty : randomCells nGen
makeDungeon :: Int -> Int -> Dungeon
makeDungeon w h = Dungeon $ matrix h w $ const Empty
dungeonToLists :: Dungeon -> [[Cell]]
dungeonToLists (Dungeon m) = toLists m

View File

@ -2,7 +2,6 @@
module Game where
import System.Random
import Lens.Micro.TH
import Lens.Micro
@ -18,8 +17,8 @@ data Game = Game
makeLenses ''Game
newGame :: (RandomGen r) => r -> Game
newGame gen = Game (makeDungeon gen 30 10) (Player (0,0))
newGame :: Game
newGame = Game (makeDungeon 30 10) (Player (0,0))
runAction :: Action -> Game -> Maybe Game
runAction (Walk N) game = Just $ game & player . pos . _2 -~ 1

View File

@ -1,7 +1,6 @@
module Main where
import Graphics.Vty
import System.Random
import Game
import Rendering
@ -11,8 +10,7 @@ main :: IO ()
main = do
cfg <- standardIOConfig
vty <- mkVty cfg
gen <- getStdGen
loop vty $ newGame gen
loop vty newGame
shutdown vty
where loop vty game = do
update vty $ renderGame game

View File

@ -17,6 +17,6 @@ dungeonToImg :: Dungeon -> Image
dungeonToImg = vertCat . map (string defAttr . concatMap show) . dungeonToLists
playerToImg :: Player -> Image
playerToImg p = (translateX px . translateY py $ char defAttr '@')
playerToImg p = translateX px . translateY py $ char defAttr '@'
where px = p ^. pos . _1
py = p ^. pos . _2