Restructuring, #9

This commit is contained in:
Tibo De Peuter 2022-12-21 23:30:59 +01:00
parent 2055ef234e
commit dab6fadad4
41 changed files with 941 additions and 680 deletions

View file

@ -0,0 +1,67 @@
module RPGEngine.Data.Default
-- Everything is exported
where
import RPGEngine.Data (Entity (..), Game (..), Item (..), Layout, Player (..), Level (..), StateBase (..), State (..), Physical (..), Direction (..))
import RPGEngine.Input.Core (ListSelector(..))
import RPGEngine.Render.LevelSelection (renderLevelSelection)
import RPGEngine.Input.Playing (spawnPlayer)
import RPGEngine.Render.Menu (renderMenu)
------------------------------ Defaults ------------------------------
defaultEntity :: Entity
defaultEntity = Entity {
entityId = "",
entityX = 0,
entityY = 0,
entityName = "Default",
entityDescription = "",
entityActions = [],
entityValue = Prelude.Nothing,
entityHp = Prelude.Nothing,
direction = Stay
}
defaultItem :: Item
defaultItem = Item {
itemId = "",
itemX = 0,
itemY = 0,
itemName = "Default",
itemDescription = "",
itemActions = [],
itemValue = Prelude.Nothing,
useTimes = Prelude.Nothing
}
defaultLayout :: Layout
defaultLayout = [
[Blocked, Blocked, Blocked],
[Blocked, Entrance, Blocked],
[Blocked, Blocked, Blocked]
]
defaultLevel :: Level
defaultLevel = Level {
layout = defaultLayout,
index = [
(0, 0, Blocked),
(0, 1, Blocked),
(0, 2, Blocked),
(1, 0, Blocked),
(1, 1, Entrance),
(1, 2, Blocked),
(2, 0, Blocked),
(2, 1, Blocked),
(2, 2, Blocked)
],
items = [],
entities = []
}
defaultPlayer :: Player
defaultPlayer = Player {
playerHp = Prelude.Nothing, -- Compares to infinity
inventory = [],
position = (0, 0)
}

View file

@ -1,65 +0,0 @@
module RPGEngine.Data.Defaults where
import RPGEngine.Data
import RPGEngine.Input.Player (spawnPlayer)
import RPGEngine.Input.Level (putCoords)
defaultEntity :: Entity
defaultEntity = Entity {
entityId = "",
entityX = 0,
entityY = 0,
entityName = "Default",
entityDescription = "",
entityActions = [],
entityValue = Prelude.Nothing,
entityHp = Prelude.Nothing,
direction = Center
}
-- Initialize the game
initGame :: Game
initGame = Game {
state = defaultState,
playing = defaultLevel,
levels = [defaultLevel],
player = spawnPlayer defaultLevel defaultPlayer
}
defaultItem :: Item
defaultItem = Item {
itemId = "",
itemX = 0,
itemY = 0,
itemName = "Default",
itemDescription = "",
itemActions = [],
itemValue = Prelude.Nothing,
useTimes = Prelude.Nothing
}
defaultLayout :: Layout
defaultLayout = [
[Blocked, Blocked, Blocked, Blocked, Blocked, Blocked, Blocked, Blocked],
[Blocked, Entrance, Walkable, Walkable, Walkable, Walkable, Exit, Blocked],
[Blocked, Blocked, Blocked, Blocked, Blocked, Blocked, Blocked, Blocked]
]
defaultLevel :: Level
defaultLevel = Level {
layout = defaultLayout,
coordlayout = putCoords defaultLevel, -- TODO This should go
items = [],
entities = []
}
defaultPlayer :: Player
defaultPlayer = Player {
playerHp = Prelude.Nothing, -- Compares to infinity
inventory = [],
position = (0, 0)
}
-- Default state of the game, Menu
defaultState :: State
defaultState = Menu

View file

@ -0,0 +1,22 @@
module RPGEngine.Data.Game
( isLegalMove
) where
import RPGEngine.Data
( Player(Player, position),
Direction,
Physical(Exit, Walkable, Entrance),
State(Playing, level),
Game(Game, state, player) )
import RPGEngine.Data.Level (findAt, directionOffsets)
------------------------------ Exported ------------------------------
-- Check if a move is legal by checking what is located at the new position.
isLegalMove :: Direction -> Game -> Bool
isLegalMove dir g@Game{ state = Playing { level = lvl }, player = p@Player{ position = (x, y) }} = legality
where legality = physical `elem` [Walkable, Entrance, Exit]
physical = findAt newPos lvl
newPos = (x + xD, y + yD)
(xD, yD) = directionOffsets dir
isLegalMove _ _ = False

View file

@ -0,0 +1,36 @@
module RPGEngine.Data.Level
-- Everything is exported
where
import GHC.IO (unsafePerformIO)
import System.Directory (getDirectoryContents)
import RPGEngine.Input.Core (ListSelector(..))
import RPGEngine.Data (Level (..), Physical (..), Direction (..), Entity (..), Game (..), Item (..), Player (..), StateBase (..), State (..), X, Y, Layout)
import RPGEngine.Config (levelFolder)
------------------------------ Exported ------------------------------
-- Find first position of a Physical
-- Graceful exit by giving Nothing if there is nothing found.
findFirstOf :: Level -> Physical -> Maybe (X, Y)
findFirstOf l@Level{ index = index } physical = try
where matches = filter (\(x, y, v) -> v == physical) index
try | not (null matches) = Just $ (\(x, y, _) -> (x, y)) $ head matches
| otherwise = Nothing
-- What is located at a given position in the level?
findAt :: (X, Y) -> Level -> Physical
findAt pos lvl@Level{ index = index } = try
where matches = map (\(_, _, v) -> v) $ filter (\(x, y, v) -> (x, y) == pos) index
try | not (null matches) = head matches
| otherwise = Void
directionOffsets :: Direction -> (X, Y)
directionOffsets North = ( 0, 1)
directionOffsets East = ( 1, 0)
directionOffsets South = ( 0, -1)
directionOffsets West = (-1, 0)
directionOffsets Stay = ( 0, 0)
getLevelList :: [FilePath]
getLevelList = drop 2 $ unsafePerformIO $ getDirectoryContents levelFolder

View file

@ -1,22 +0,0 @@
-- Describes the current state of the game,
-- e.g. Main menu, game, pause, win or lose
-- Allows to easily go to a next state and change rendering accordingly
module RPGEngine.Data.State
( State(..)
, nextState
) where
import RPGEngine.Data
----------------------------------------------------------------------
-- Get the next state based on the current state
nextState :: State -> State
nextState Menu = LvlSelect
nextState Playing = Pause
nextState Pause = Playing
nextState _ = Menu
----------------------------------------------------------------------