Removed random in favor of future static maps
This commit is contained in:
parent
f7aefb1a54
commit
190c3a029f
|
@ -29,5 +29,4 @@ executable roguelike
|
||||||
matrix,
|
matrix,
|
||||||
unordered-containers,
|
unordered-containers,
|
||||||
microlens-th,
|
microlens-th,
|
||||||
microlens,
|
microlens
|
||||||
random
|
|
||||||
|
|
|
@ -1,7 +1,6 @@
|
||||||
module Dungeon where
|
module Dungeon where
|
||||||
|
|
||||||
import Data.Matrix
|
import Data.Matrix
|
||||||
import System.Random
|
|
||||||
|
|
||||||
data Cell = Solid | Empty
|
data Cell = Solid | Empty
|
||||||
|
|
||||||
|
@ -14,12 +13,8 @@ newtype Dungeon = Dungeon (Matrix Cell)
|
||||||
instance Show Dungeon where
|
instance Show Dungeon where
|
||||||
show (Dungeon m) = unlines . map (concatMap show) $ toLists m
|
show (Dungeon m) = unlines . map (concatMap show) $ toLists m
|
||||||
|
|
||||||
makeDungeon :: (RandomGen r) => r -> Int -> Int -> Dungeon
|
makeDungeon :: Int -> Int -> Dungeon
|
||||||
makeDungeon gen w h = Dungeon $ Data.Matrix.fromList h w (randomCells gen)
|
makeDungeon w h = Dungeon $ matrix h w $ const Empty
|
||||||
where randomCells g = let (c,nGen) = randomR (0 :: Int,1 :: Int) g
|
|
||||||
in case c of 0 -> Solid : randomCells nGen
|
|
||||||
1 -> Empty : randomCells nGen
|
|
||||||
|
|
||||||
|
|
||||||
dungeonToLists :: Dungeon -> [[Cell]]
|
dungeonToLists :: Dungeon -> [[Cell]]
|
||||||
dungeonToLists (Dungeon m) = toLists m
|
dungeonToLists (Dungeon m) = toLists m
|
||||||
|
|
|
@ -2,7 +2,6 @@
|
||||||
|
|
||||||
module Game where
|
module Game where
|
||||||
|
|
||||||
import System.Random
|
|
||||||
import Lens.Micro.TH
|
import Lens.Micro.TH
|
||||||
import Lens.Micro
|
import Lens.Micro
|
||||||
|
|
||||||
|
@ -18,8 +17,8 @@ data Game = Game
|
||||||
|
|
||||||
makeLenses ''Game
|
makeLenses ''Game
|
||||||
|
|
||||||
newGame :: (RandomGen r) => r -> Game
|
newGame :: Game
|
||||||
newGame gen = Game (makeDungeon gen 30 10) (Player (0,0))
|
newGame = Game (makeDungeon 30 10) (Player (0,0))
|
||||||
|
|
||||||
runAction :: Action -> Game -> Maybe Game
|
runAction :: Action -> Game -> Maybe Game
|
||||||
runAction (Walk N) game = Just $ game & player . pos . _2 -~ 1
|
runAction (Walk N) game = Just $ game & player . pos . _2 -~ 1
|
||||||
|
|
|
@ -1,7 +1,6 @@
|
||||||
module Main where
|
module Main where
|
||||||
|
|
||||||
import Graphics.Vty
|
import Graphics.Vty
|
||||||
import System.Random
|
|
||||||
|
|
||||||
import Game
|
import Game
|
||||||
import Rendering
|
import Rendering
|
||||||
|
@ -11,8 +10,7 @@ main :: IO ()
|
||||||
main = do
|
main = do
|
||||||
cfg <- standardIOConfig
|
cfg <- standardIOConfig
|
||||||
vty <- mkVty cfg
|
vty <- mkVty cfg
|
||||||
gen <- getStdGen
|
loop vty newGame
|
||||||
loop vty $ newGame gen
|
|
||||||
shutdown vty
|
shutdown vty
|
||||||
where loop vty game = do
|
where loop vty game = do
|
||||||
update vty $ renderGame game
|
update vty $ renderGame game
|
||||||
|
|
|
@ -17,6 +17,6 @@ dungeonToImg :: Dungeon -> Image
|
||||||
dungeonToImg = vertCat . map (string defAttr . concatMap show) . dungeonToLists
|
dungeonToImg = vertCat . map (string defAttr . concatMap show) . dungeonToLists
|
||||||
|
|
||||||
playerToImg :: Player -> Image
|
playerToImg :: Player -> Image
|
||||||
playerToImg p = (translateX px . translateY py $ char defAttr '@')
|
playerToImg p = translateX px . translateY py $ char defAttr '@'
|
||||||
where px = p ^. pos . _1
|
where px = p ^. pos . _1
|
||||||
py = p ^. pos . _2
|
py = p ^. pos . _2
|
||||||
|
|
Loading…
Reference in New Issue