This commit is contained in:
Tibo De Peuter 2022-12-20 16:56:22 +01:00
parent 0720f3b719
commit d4fbcda73b
13 changed files with 412 additions and 169 deletions

View 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

View file

@ -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 ------------------------------