Skip to content

Commit

Permalink
move Dungeon type to Dungeon.hs
Browse files Browse the repository at this point in the history
  • Loading branch information
Mikolaj committed Mar 24, 2011
1 parent 11dea08 commit 83c6b31
Show file tree
Hide file tree
Showing 4 changed files with 27 additions and 24 deletions.
25 changes: 25 additions & 0 deletions src/Dungeon.hs
Expand Up @@ -3,6 +3,7 @@ module Dungeon where
import Prelude hiding (floor)
import Control.Monad

import Data.Binary
import Data.Map as M
import Data.List as L
import Data.Ratio
Expand All @@ -13,6 +14,30 @@ import Level
import Item
import Random

-- | The complete dungeon is a map from level names to levels.
-- We usually store all but the current level in this data structure.
data Dungeon = Dungeon (M.Map LevelName Level)
deriving Show

-- | Create a dungeon from a list of levels.
dungeon :: [Level] -> Dungeon
dungeon = Dungeon . M.fromList . L.map (\ l -> (lname l, l))

-- | Extract a level from a dungeon.
getDungeonLevel :: LevelName -> Dungeon -> (Level, Dungeon)
getDungeonLevel ln (Dungeon dng) = (dng ! ln, Dungeon (M.delete ln dng))

-- | Put a level into a dungeon.
putDungeonLevel :: Level -> Dungeon -> Dungeon
putDungeonLevel lvl (Dungeon dng) = Dungeon (M.insert (lname lvl) lvl dng)

sizeDungeon :: Dungeon -> Int
sizeDungeon (Dungeon dng) = M.size dng

instance Binary Dungeon where
put (Dungeon dng) = put (M.elems dng)
get = liftM dungeon get

type Corridor = [(Y,X)]
type Room = Area

Expand Down
24 changes: 0 additions & 24 deletions src/Level.hs
Expand Up @@ -46,30 +46,6 @@ levelName (LambdaCave n) = "The Lambda Cave " ++ show n
levelNumber :: LevelName -> Int
levelNumber (LambdaCave n) = n

-- | The complete dungeon is a map from level names to levels.
-- We usually store all but the current level in this data structure.
data Dungeon = Dungeon (M.Map LevelName Level)
deriving Show

-- | Create a dungeon from a list of levels.
dungeon :: [Level] -> Dungeon
dungeon = Dungeon . M.fromList . L.map (\ l -> (lname l, l))

-- | Extract a level from a dungeon.
getDungeonLevel :: LevelName -> Dungeon -> (Level, Dungeon)
getDungeonLevel ln (Dungeon dng) = (dng ! ln, Dungeon (M.delete ln dng))

-- | Put a level into a dungeon.
putDungeonLevel :: Level -> Dungeon -> Dungeon
putDungeonLevel lvl (Dungeon dng) = Dungeon (M.insert (lname lvl) lvl dng)

sizeDungeon :: Dungeon -> Int
sizeDungeon (Dungeon dng) = M.size dng

instance Binary Dungeon where
put (Dungeon dng) = put (M.elems dng)
get = liftM dungeon get

-- | A dungeon location is a level together with a location on that level.
type DungeonLoc = (LevelName, Loc)

Expand Down
1 change: 1 addition & 0 deletions src/MovableState.hs
Expand Up @@ -10,6 +10,7 @@ import Data.Maybe
import Geometry
import Movable
import Level
import Dungeon
import State

-- The operations with "Any", and those that use them, consider all the dungeon.
Expand Down
1 change: 1 addition & 0 deletions src/State.hs
Expand Up @@ -9,6 +9,7 @@ import qualified Config
import Movable
import Geometry
import Level
import Dungeon
import Item
import Message

Expand Down

0 comments on commit 83c6b31

Please sign in to comment.