Improved the code and made it more readable
This commit is contained in:
parent
3f88d88ad7
commit
3dd14699f4
|
@ -2,11 +2,11 @@
|
||||||
module Dungeon where
|
module Dungeon where
|
||||||
|
|
||||||
import Data.Aeson
|
import Data.Aeson
|
||||||
import Data.Aeson.Types
|
|
||||||
import Data.Matrix
|
import Data.Matrix
|
||||||
import Linear.V2
|
import Linear.V2
|
||||||
import Data.Tuple
|
import Data.Tuple
|
||||||
import Data.Maybe
|
import Data.Maybe
|
||||||
|
import Data.Either
|
||||||
|
|
||||||
data Cell = Solid
|
data Cell = Solid
|
||||||
| Empty
|
| Empty
|
||||||
|
@ -26,20 +26,20 @@ 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
|
||||||
|
|
||||||
makeDungeonFromFile :: String -> IO Dungeon
|
instance FromJSON Dungeon where
|
||||||
makeDungeonFromFile f = do
|
parseJSON = withObject "Dungeon" $ \v -> do
|
||||||
--contents <- readFile f
|
stringMap <- v .: "map"
|
||||||
ef <- eitherDecodeFileStrict f :: IO (Either String Object)
|
|
||||||
let obj = case ef of (Right o) -> o
|
|
||||||
(Left l) -> error l
|
|
||||||
let stringMap = case parse (.: "map") obj :: Result [String] of
|
|
||||||
(Success m) -> m
|
|
||||||
(Error s) -> error s
|
|
||||||
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 . fromLists $ cellLists
|
||||||
|
|
||||||
|
|
||||||
|
makeDungeonFromFile :: FilePath -> IO Dungeon
|
||||||
|
makeDungeonFromFile f = do
|
||||||
|
eithDun <- eitherDecodeFileStrict f
|
||||||
|
return $ fromRight (error "") eithDun
|
||||||
|
|
||||||
dungeonToLists :: Dungeon -> [[Cell]]
|
dungeonToLists :: Dungeon -> [[Cell]]
|
||||||
dungeonToLists (Dungeon m) = toLists m
|
dungeonToLists (Dungeon m) = toLists m
|
||||||
|
|
||||||
|
|
|
@ -1,7 +0,0 @@
|
||||||
module Dungeon.Loader where
|
|
||||||
|
|
||||||
import Data.Aeson
|
|
||||||
import Data.ByteString.Lazy.UTF8 (fromString)
|
|
||||||
|
|
||||||
loadDungeon :: String -> IO (Either String Object)
|
|
||||||
loadDungeon = eitherDecodeFileStrict
|
|
|
@ -20,7 +20,7 @@ makeLenses ''Game
|
||||||
newGame :: IO Game
|
newGame :: IO Game
|
||||||
newGame = do
|
newGame = do
|
||||||
dun <- makeDungeonFromFile "maps/test.json"
|
dun <- makeDungeonFromFile "maps/test.json"
|
||||||
return $ Game dun (Player $ V2 1 24)
|
return $ Game dun (Player $ V2 1 23)
|
||||||
|
|
||||||
runAction :: Action -> Game -> Maybe Game
|
runAction :: Action -> Game -> Maybe Game
|
||||||
runAction (Move vec) game = Just $ if ableToMove
|
runAction (Move vec) game = Just $ if ableToMove
|
||||||
|
|
Loading…
Reference in New Issue