Setup
This commit is contained in:
parent
0720f3b719
commit
d4fbcda73b
13 changed files with 412 additions and 169 deletions
|
@ -1,13 +1,33 @@
|
|||
module RPGEngine.Data.Types where
|
||||
module RPGEngine.Data where
|
||||
|
||||
-------------------------------- Game --------------------------------
|
||||
|
||||
-- TODO Add more
|
||||
data Game = Game {
|
||||
-- Current state of the game
|
||||
state :: State
|
||||
state :: State,
|
||||
playing :: Level,
|
||||
levels :: [Level]
|
||||
}
|
||||
|
||||
------------------------------- Level --------------------------------
|
||||
|
||||
data Level = Level {
|
||||
layout :: Layout,
|
||||
items :: [Item],
|
||||
entities :: [Entity]
|
||||
}
|
||||
|
||||
type Layout = [Strip]
|
||||
type Strip = [Physical]
|
||||
|
||||
data Physical = Void
|
||||
| Walkable
|
||||
| Blocked
|
||||
| Entrance
|
||||
| Exit
|
||||
deriving (Show, Eq)
|
||||
|
||||
------------------------------- Player -------------------------------
|
||||
|
||||
data Player = Player {
|
||||
|
@ -108,8 +128,9 @@ data Action = Leave
|
|||
|
||||
------------------------------ Direction -----------------------------
|
||||
|
||||
data Direction = North
|
||||
| East
|
||||
| South
|
||||
data Direction = North
|
||||
| East
|
||||
| South
|
||||
| West
|
||||
deriving (Show)
|
||||
| Center -- Equal to 'stay where you are'
|
||||
deriving (Show, Eq)
|
|
@ -5,7 +5,7 @@ module RPGEngine.Data.Game
|
|||
,initGame
|
||||
) where
|
||||
|
||||
import RPGEngine.Data.Types
|
||||
import RPGEngine.Data
|
||||
import RPGEngine.Data.State
|
||||
|
||||
----------------------------------------------------------------------
|
||||
|
@ -13,5 +13,13 @@ import RPGEngine.Data.State
|
|||
-- Initialize the game
|
||||
initGame :: Game
|
||||
initGame = Game {
|
||||
state = defaultState
|
||||
state = defaultState,
|
||||
playing = head levels,
|
||||
levels = levels
|
||||
}
|
||||
where levels = [emptyLevel]
|
||||
emptyLevel = Level {
|
||||
layout = [],
|
||||
items = [],
|
||||
entities = []
|
||||
}
|
||||
|
|
|
@ -9,7 +9,7 @@ module RPGEngine.Data.State
|
|||
, nextState
|
||||
) where
|
||||
|
||||
import RPGEngine.Data.Types
|
||||
import RPGEngine.Data
|
||||
|
||||
----------------------------- Constants ------------------------------
|
||||
|
||||
|
|
|
@ -4,7 +4,7 @@ module RPGEngine.Input
|
|||
( handleAllInput
|
||||
) where
|
||||
|
||||
import RPGEngine.Data.Types
|
||||
import RPGEngine.Data
|
||||
import RPGEngine.Data.State
|
||||
import RPGEngine.Input.Core
|
||||
|
||||
|
|
|
@ -1,8 +1,19 @@
|
|||
module RPGEngine.Parse where
|
||||
|
||||
import RPGEngine.Data.Types
|
||||
import RPGEngine.Data
|
||||
import RPGEngine.Parse.StructureElement
|
||||
import RPGEngine.Parse.Game
|
||||
|
||||
-- TODO parseFromFile gebruiken
|
||||
import Text.Parsec.String
|
||||
import System.IO.Unsafe
|
||||
|
||||
parseToGame :: Game
|
||||
parseToGame = undefined
|
||||
----------------------------- Constants ------------------------------
|
||||
|
||||
type FileName = String
|
||||
|
||||
----------------------------------------------------------------------
|
||||
|
||||
parseToGame :: FileName -> Game
|
||||
parseToGame filename = structureToGame structure
|
||||
where (Right structure) = unsafePerformIO io
|
||||
io = parseFromFile structureElement filename
|
22
lib/RPGEngine/Parse/Game.hs
Normal file
22
lib/RPGEngine/Parse/Game.hs
Normal file
|
@ -0,0 +1,22 @@
|
|||
module RPGEngine.Parse.Game where
|
||||
|
||||
import RPGEngine.Data
|
||||
import RPGEngine.Parse.StructureElement (StructureElement)
|
||||
|
||||
-------------------------------- Game --------------------------------
|
||||
|
||||
-- TODO
|
||||
structureToGame :: StructureElement -> Game
|
||||
structureToGame = undefined
|
||||
|
||||
------------------------------- Player -------------------------------
|
||||
|
||||
-- TODO
|
||||
structureToPlayer :: StructureElement -> Player
|
||||
structureToPlayer = undefined
|
||||
|
||||
------------------------------- Levels -------------------------------
|
||||
|
||||
-- TODO
|
||||
structureToLevels :: StructureElement -> [Level]
|
||||
structureToLevels = undefined
|
|
@ -1,6 +1,6 @@
|
|||
module RPGEngine.Parse.StructureElement where
|
||||
|
||||
import RPGEngine.Data.Types (Action(..), Condition(..))
|
||||
import RPGEngine.Data (Action(..), Condition(..), Layout, Direction(..), Physical(..), Strip)
|
||||
import RPGEngine.Parse.Core ( ignoreWS )
|
||||
|
||||
import Text.Parsec
|
||||
|
@ -38,7 +38,7 @@ structureElement = try $ choice [block, entry, regular]
|
|||
block :: Parser StructureElement
|
||||
block = try $ do
|
||||
open <- ignoreWS $ oneOf openingBrackets
|
||||
middle <- ignoreWS entry `sepBy` ignoreWS (char ',')
|
||||
middle <- ignoreWS $ choice [entry, block] `sepBy` char ','
|
||||
let closingBracket = getMatchingClosingBracket open
|
||||
ignoreWS $ char closingBracket
|
||||
return $ Block middle
|
||||
|
@ -75,7 +75,7 @@ tag = try $ Tag <$> many1 alphaNum
|
|||
conditionList :: Parser Key
|
||||
conditionList = try $ do
|
||||
open <- ignoreWS $ oneOf openingBrackets
|
||||
list <- try $ ignoreWS condition `sepBy` ignoreWS (char ',')
|
||||
list <- ignoreWS condition `sepBy` char ','
|
||||
let closingBracket = getMatchingClosingBracket open
|
||||
ignoreWS $ char closingBracket
|
||||
return $ ConditionList $ extract list
|
||||
|
@ -102,13 +102,14 @@ data Value = String String
|
|||
| Integer Int
|
||||
| Infinite
|
||||
| Action Action
|
||||
| Layout -- TODO Add element
|
||||
| Direction Direction
|
||||
| Layout Layout
|
||||
deriving (Show, Eq)
|
||||
|
||||
----------------------------------------------------------------------
|
||||
|
||||
value :: Parser Value
|
||||
value = choice [string, integer, infinite, action]
|
||||
value = choice [string, integer, infinite, action, direction]
|
||||
|
||||
string :: Parser Value
|
||||
string = try $ String <$> between (char '\"') (char '\"') reading
|
||||
|
@ -134,13 +135,52 @@ action = try $ do
|
|||
| script == "useItem" = UseItem arg
|
||||
| script == "decreaseHp" = DecreaseHp first second
|
||||
| script == "increasePlayerHp" = IncreasePlayerHp arg
|
||||
| otherwise = RPGEngine.Data.Types.Nothing
|
||||
| otherwise = RPGEngine.Data.Nothing
|
||||
(first, ',':second) = break (== ',') arg
|
||||
return $ Action answer
|
||||
|
||||
-- TODO
|
||||
direction :: Parser Value
|
||||
direction = try $ do
|
||||
value <- choice [
|
||||
ignoreWS $ P.string "up",
|
||||
ignoreWS $ P.string "down",
|
||||
ignoreWS $ P.string "left",
|
||||
ignoreWS $ P.string "right"
|
||||
]
|
||||
notFollowedBy alphaNum
|
||||
return $ Direction $ make value
|
||||
where make "up" = North
|
||||
make "right" = East
|
||||
make "down" = South
|
||||
make "left" = West
|
||||
make _ = Center
|
||||
|
||||
layout :: Parser Value
|
||||
layout = undefined
|
||||
layout = try $ do
|
||||
ignoreWS $ char '|'
|
||||
list <- ignoreWS strip `sepBy` ignoreWS (char '|')
|
||||
return $ Layout list
|
||||
|
||||
strip :: Parser Strip
|
||||
strip = try $ do
|
||||
physical `sepBy` char ' '
|
||||
|
||||
physical :: Parser Physical
|
||||
physical = try $ do
|
||||
value <- choice [
|
||||
char 'x',
|
||||
char '.',
|
||||
char '*',
|
||||
char 's',
|
||||
char 'e'
|
||||
]
|
||||
return $ make value
|
||||
where make '.' = Walkable
|
||||
make '*' = Blocked
|
||||
make 's' = Entrance
|
||||
make 'e' = Exit
|
||||
make _ = Void
|
||||
|
||||
|
||||
------------------------------ Brackets ------------------------------
|
||||
|
||||
|
|
|
@ -7,7 +7,7 @@ module RPGEngine.Render
|
|||
, render
|
||||
) where
|
||||
|
||||
import RPGEngine.Data.Types
|
||||
import RPGEngine.Data
|
||||
import Graphics.Gloss
|
||||
|
||||
----------------------------- Constants ------------------------------
|
||||
|
|
Reference in a new issue