Added basic parser functionality & tests for these functionalites. Split tests in several files
132 lines
3.6 KiB
Haskell
132 lines
3.6 KiB
Haskell
module Parse where
|
|
|
|
-- TODO Maak wrapper module
|
|
-- TODO This module should not be used by anything except for wrapper module and tests
|
|
|
|
import Game
|
|
import Player
|
|
import Text.Parsec
|
|
import Text.Parsec.Char
|
|
import Text.Parsec.String
|
|
import Data.List
|
|
import Data.Maybe
|
|
import Text.Parsec.Error (Message(UnExpect))
|
|
|
|
-- TODO parseFromFile gebruiken
|
|
|
|
-- Parser type
|
|
-- type Parser = Parsec String ()
|
|
|
|
-- A wrapper, which takes a parser and some input and returns a
|
|
-- parsed output.
|
|
parseWith :: Parser a -> String -> Either ParseError a
|
|
parseWith parser = parse parser ""
|
|
|
|
ignoreWS :: Parser a -> Parser a
|
|
ignoreWS parser = spaces >> parser
|
|
|
|
-- Also return anything that has not yet been parsed
|
|
parseWithRest :: Parser a -> String -> Either ParseError (a, String)
|
|
-- fmap (,) over Parser monad and apply to rest
|
|
parseWithRest parser = parse ((,) <$> parser <*> rest) ""
|
|
where rest = manyTill anyToken eof
|
|
|
|
parseToGame :: Game
|
|
parseToGame = undefined
|
|
|
|
-- Info in between brackets, '(..)', '[..]', '{..}' or '<..>'
|
|
data Brackets a = Brackets a
|
|
deriving (Eq, Show)
|
|
|
|
parseToPlayer :: Player
|
|
parseToPlayer = undefined
|
|
|
|
-- any words separated by whitespace
|
|
parseWord :: Parser String
|
|
parseWord = do many alphaNum
|
|
|
|
-- TODO Expand to allow different kinds of brackets, also see Brackets data type.
|
|
-- TODO Check if brackets match order.
|
|
-- TODO Allow nested brackets.
|
|
brackets :: Parser (Brackets String)
|
|
brackets = do
|
|
ignoreWS $ char '('
|
|
e <- ignoreWS $ many1 alphaNum
|
|
ignoreWS $ char ')'
|
|
return $ Brackets e
|
|
|
|
------------------------
|
|
|
|
data Value = String String
|
|
| Integer Int
|
|
| Infinite
|
|
deriving (Show, Eq)
|
|
|
|
-- See documentation for more details, only a short description is
|
|
--provided here.
|
|
data StructureElement = Block [StructureElement]
|
|
| Entry String StructureElement-- Key + Value
|
|
| Regular Value -- Regular value, Integer or String or Infinite
|
|
| ConditionList [StructureElement]
|
|
-- TODO
|
|
| Condition -- inventoryFull() etc.
|
|
-- TODO
|
|
| Action -- leave(), useItem(objectId) etc.
|
|
deriving (Show, Eq)
|
|
|
|
-- TODO Add ConditionList and Action
|
|
structureElement :: Parser StructureElement
|
|
structureElement = choice [block, regular]
|
|
|
|
-- A Block is a list of Entry s
|
|
block :: Parser StructureElement
|
|
block = do
|
|
ignoreWS $ char '{'
|
|
list <- ignoreWS $ many1 entry
|
|
ignoreWS $ char '}'
|
|
return $ Block list
|
|
|
|
entry :: Parser StructureElement
|
|
entry = do
|
|
key <- ignoreWS $ many1 alphaNum
|
|
ignoreWS $ char ':'
|
|
value <- ignoreWS structureElement -- TODO Is this the correct one to use?
|
|
return $ Entry key value
|
|
|
|
regular :: Parser StructureElement
|
|
regular = do
|
|
value <- ignoreWS $ choice [integer, valueString, infinite]
|
|
return $ Regular value
|
|
|
|
integer :: Parser Value
|
|
integer = do
|
|
value <- ignoreWS $ many1 digit
|
|
return $ Integer (read value :: Int)
|
|
|
|
valueString :: Parser Value
|
|
valueString = do
|
|
ignoreWS $ char '"'
|
|
value <- ignoreWS $ many1 (noneOf ['"'])
|
|
ignoreWS $ char '"'
|
|
return $ String value
|
|
|
|
infinite :: Parser Value
|
|
infinite = do
|
|
ignoreWS $ string "infinite"
|
|
notFollowedBy alphaNum
|
|
return Infinite
|
|
|
|
conditionList :: Parser StructureElement
|
|
conditionList = do
|
|
ignoreWS $ char '['
|
|
list <- ignoreWS $ many1 condition
|
|
ignoreWS $ char ']'
|
|
return $ ConditionList list
|
|
|
|
-- TODO
|
|
condition :: Parser StructureElement
|
|
condition = undefined
|
|
|
|
-- TODO YOU ARE HERE
|
|
action :: Parser StructureElement
|
|
action = undefined
|