Added more parameters in JSON (no functional yet)

This commit is contained in:
Suguivy 2021-02-21 16:59:17 +01:00
parent 520082ab34
commit 71759c028c
2 changed files with 25 additions and 15 deletions

View File

@ -1,6 +1,6 @@
{ {
"map" : [ "name" : "test",
"layout" : [
"#########################", "#########################",
"####......#####....######", "####......#####....######",
"###.........###.....#####", "###.........###.....#####",
@ -26,12 +26,14 @@
"#..###................###", "#..###................###",
"#..................######", "#..................######",
"#########################" "#########################"
], ],
"communications" : { "tunnels" : [
{
"c1" : [[16,0], "c2"] "name" : "a",
"coord" : [16,0],
} "map" : "test2",
"to_tunnel" : "b"
}
]
} }

View File

@ -1,4 +1,4 @@
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings, TemplateHaskell #-}
module Dungeon where module Dungeon where
@ -7,6 +7,8 @@ import Data.Matrix
import Linear.V2 import Linear.V2
import Data.Tuple import Data.Tuple
import Data.Maybe import Data.Maybe
import Lens.Micro.TH
import Lens.Micro
data Cell = Solid data Cell = Solid
| Empty | Empty
@ -21,18 +23,24 @@ cellMapping =
, (Solid, '#') , (Solid, '#')
] ]
newtype Dungeon = Dungeon (Matrix Cell) data Dungeon = Dungeon
{ _name :: String
, _layout :: Matrix Cell
}
makeLenses ''Dungeon
instance Show Dungeon where instance Show Dungeon where
show (Dungeon m) = unlines . map (concatMap show) $ toLists m show dun = unlines . map (concatMap show) $ toLists $ dun ^. layout
instance FromJSON Dungeon where instance FromJSON Dungeon where
parseJSON = withObject "Dungeon" $ \v -> do parseJSON = withObject "Dungeon" $ \v -> do
stringMap <- v .: "map" mapName <- v .: "name"
stringMap <- v .: "layout"
let cellMappingR = map swap cellMapping let cellMappingR = map swap cellMapping
charToCell c = fromMaybe (error "Invalid cell in the .map file") (c `lookup` cellMappingR) charToCell c = fromMaybe (error "Invalid cell in the .map file") (c `lookup` cellMappingR)
cellLists = map charToCell <$> stringMap cellLists = map charToCell <$> stringMap
return . Dungeon . fromLists $ cellLists return $ Dungeon mapName (fromLists cellLists)
makeDungeonFromFile :: FilePath -> IO Dungeon makeDungeonFromFile :: FilePath -> IO Dungeon
@ -43,7 +51,7 @@ makeDungeonFromFile f = do
Right dun -> dun Right dun -> dun
dungeonToLists :: Dungeon -> [[Cell]] dungeonToLists :: Dungeon -> [[Cell]]
dungeonToLists (Dungeon m) = toLists m dungeonToLists dun = toLists $ dun ^. layout
getCell :: V2 Int -> Dungeon -> Cell getCell :: V2 Int -> Dungeon -> Cell
getCell (V2 x y) (Dungeon m) = fromMaybe Solid (safeGet (y+1) (x+1) m) getCell (V2 x y) dun = fromMaybe Solid (safeGet (y+1) (x+1) $ dun ^. layout)