Restructuring, #9
This commit is contained in:
parent
2055ef234e
commit
dab6fadad4
41 changed files with 941 additions and 680 deletions
|
@ -1,24 +1,21 @@
|
|||
module RPGEngine.Render.Core where
|
||||
module RPGEngine.Render.Core
|
||||
( Renderer
|
||||
|
||||
import Graphics.Gloss ( Picture, translate, pictures )
|
||||
import GHC.IO (unsafePerformIO)
|
||||
import Graphics.Gloss.Juicy (loadJuicyPNG)
|
||||
import Data.Maybe (fromJust)
|
||||
import Graphics.Gloss.Data.Picture (scale)
|
||||
import Graphics.Gloss.Data.Bitmap (BitmapData(..))
|
||||
, getRender
|
||||
, setRenderPos
|
||||
, overlay
|
||||
) where
|
||||
|
||||
import RPGEngine.Config
|
||||
|
||||
import Data.Maybe
|
||||
import Graphics.Gloss
|
||||
import GHC.IO
|
||||
import Graphics.Gloss.Juicy
|
||||
|
||||
----------------------------- Constants ------------------------------
|
||||
|
||||
-- Default scale
|
||||
zoom :: Float
|
||||
zoom = 5.0
|
||||
|
||||
-- Resolution of the texture
|
||||
resolution :: Float
|
||||
resolution = 16
|
||||
|
||||
assetsFolder :: FilePath
|
||||
assetsFolder = "assets/"
|
||||
type Renderer a = a -> Picture
|
||||
|
||||
unknownImage :: FilePath
|
||||
unknownImage = "unknown.png"
|
||||
|
@ -54,11 +51,7 @@ library = unknown:entities ++ environment ++ gui ++ items
|
|||
gui = []
|
||||
items = map (\(f, s) -> (f, renderPNG (assetsFolder ++ "items/" ++ s))) allItems
|
||||
|
||||
----------------------------------------------------------------------
|
||||
|
||||
-- Turn a path to a .png file into a Picture.
|
||||
renderPNG :: FilePath -> Picture
|
||||
renderPNG path = scale zoom zoom $ fromJust $ unsafePerformIO $ loadJuicyPNG path
|
||||
------------------------------ Exported ------------------------------
|
||||
|
||||
-- Retrieve an image from the library. If the library does not contain
|
||||
-- the requested image, a default is returned.
|
||||
|
@ -82,4 +75,10 @@ overlay = setRenderPos offX offY $ pictures voids
|
|||
height = round $ 4320 / resolution / zoom
|
||||
width = round $ 7680 / resolution / zoom
|
||||
offX = negate (width `div` 2)
|
||||
offY = negate (height `div` 2)
|
||||
offY = negate (height `div` 2)
|
||||
|
||||
----------------------------------------------------------------------
|
||||
|
||||
-- Turn a path to a .png file into a Picture.
|
||||
renderPNG :: FilePath -> Picture
|
||||
renderPNG path = scale zoom zoom $ fromJust $ unsafePerformIO $ loadJuicyPNG path
|
|
@ -1,10 +0,0 @@
|
|||
module RPGEngine.Render.GUI
|
||||
( renderGUI
|
||||
) where
|
||||
|
||||
import RPGEngine.Data (Game)
|
||||
import Graphics.Gloss (Picture, blank)
|
||||
|
||||
-- TODO
|
||||
renderGUI :: Game -> Picture
|
||||
renderGUI _ = blank
|
33
lib/RPGEngine/Render/LevelSelection.hs
Normal file
33
lib/RPGEngine/Render/LevelSelection.hs
Normal file
|
@ -0,0 +1,33 @@
|
|||
module RPGEngine.Render.LevelSelection
|
||||
( renderLevelSelection
|
||||
) where
|
||||
|
||||
import RPGEngine.Config ( resolution, zoom )
|
||||
import RPGEngine.Data ( Game (..), State (..) )
|
||||
import RPGEngine.Data.Level ( getLevelList )
|
||||
import RPGEngine.Render.Core ( Renderer )
|
||||
|
||||
import Graphics.Gloss
|
||||
( pictures, text, translate, blank, Picture, color )
|
||||
import Graphics.Gloss.Data.Picture (scale)
|
||||
import RPGEngine.Input.Core (ListSelector (..))
|
||||
import Graphics.Gloss.Data.Color (red)
|
||||
|
||||
------------------------------ Exported ------------------------------
|
||||
|
||||
renderLevelSelection :: Renderer Game
|
||||
renderLevelSelection Game{ state = state } = result
|
||||
where result = renderLevelList state
|
||||
|
||||
----------------------------------------------------------------------
|
||||
|
||||
renderLevelList :: Renderer State
|
||||
renderLevelList LevelSelection{ levelList = list, selector = selector } = everything
|
||||
where everything = pictures $ map render entries
|
||||
sel = selection selector
|
||||
entries = zip [0::Int .. ] list
|
||||
render (i, path) | i == sel = color red $ scale zoomed zoomed $ translate 0 (offset i) $ text path
|
||||
| otherwise = scale zoomed zoomed $ translate 0 (offset i) $ text path
|
||||
zoomed = 0.1 * zoom
|
||||
offset i = negate (2 * resolution * zoom * fromIntegral i)
|
||||
renderLevelList _ = blank
|
14
lib/RPGEngine/Render/Lose.hs
Normal file
14
lib/RPGEngine/Render/Lose.hs
Normal file
|
@ -0,0 +1,14 @@
|
|||
module RPGEngine.Render.Lose
|
||||
( renderLose
|
||||
) where
|
||||
|
||||
import RPGEngine.Render.Core ( Renderer )
|
||||
|
||||
import RPGEngine.Data ( Game )
|
||||
import Graphics.Gloss ( text )
|
||||
|
||||
----------------------------------------------------------------------
|
||||
|
||||
-- TODO
|
||||
renderLose :: Renderer Game
|
||||
renderLose _ = text "Win"
|
|
@ -1,15 +0,0 @@
|
|||
module RPGEngine.Render.LvlSelect
|
||||
( renderLvlList
|
||||
) where
|
||||
|
||||
import Graphics.Gloss ( Picture, pictures, translate, scale )
|
||||
import Graphics.Gloss.Data.Picture (blank, text)
|
||||
import RPGEngine.Render.Core (resolution, zoom)
|
||||
|
||||
-- Render all level names, under each other.
|
||||
renderLvlList :: [FilePath] -> Picture
|
||||
renderLvlList list = pictures $ map render entries
|
||||
where entries = zip [0::Int .. ] list
|
||||
render (i, path) = scale zoomed zoomed $ translate 0 (offset i) $ text path
|
||||
zoomed = 0.1 * zoom
|
||||
offset i = negate (2 * resolution * zoom * fromIntegral i)
|
14
lib/RPGEngine/Render/Menu.hs
Normal file
14
lib/RPGEngine/Render/Menu.hs
Normal file
|
@ -0,0 +1,14 @@
|
|||
module RPGEngine.Render.Menu
|
||||
( renderMenu
|
||||
) where
|
||||
|
||||
import RPGEngine.Render.Core ( Renderer )
|
||||
|
||||
import RPGEngine.Data ( Game )
|
||||
import Graphics.Gloss (text)
|
||||
|
||||
----------------------------------------------------------------------
|
||||
|
||||
-- TODO
|
||||
renderMenu :: Renderer Game
|
||||
renderMenu _ = text "[Press any key to start]"
|
20
lib/RPGEngine/Render/Paused.hs
Normal file
20
lib/RPGEngine/Render/Paused.hs
Normal file
|
@ -0,0 +1,20 @@
|
|||
module RPGEngine.Render.Paused
|
||||
( renderPaused
|
||||
) where
|
||||
|
||||
import RPGEngine.Render.Core ( Renderer, overlay )
|
||||
|
||||
import RPGEngine.Data ( Game )
|
||||
import Graphics.Gloss ( pictures, scale, text )
|
||||
import RPGEngine.Render.Playing ( renderPlaying )
|
||||
import Graphics.Gloss.Data.Picture (color)
|
||||
import Graphics.Gloss.Data.Color (white)
|
||||
|
||||
------------------------------ Exported ------------------------------
|
||||
|
||||
renderPaused :: Renderer Game
|
||||
renderPaused g = pictures [renderPlaying g, pause]
|
||||
where pause = pictures [
|
||||
overlay,
|
||||
color white $ scale 0.5 0.5 $ text "[Press any key to continue]"
|
||||
]
|
|
@ -1,17 +0,0 @@
|
|||
module RPGEngine.Render.Player
|
||||
( renderPlayer
|
||||
, focusPlayer
|
||||
) where
|
||||
|
||||
import RPGEngine.Data (Player(..), Game(..))
|
||||
import Graphics.Gloss (Picture, text)
|
||||
import RPGEngine.Render.Core (getRender, setRenderPos, zoom, resolution)
|
||||
import Graphics.Gloss.Data.Picture (translate)
|
||||
|
||||
renderPlayer :: Player -> Picture
|
||||
renderPlayer Player{ position = (x, y) } = setRenderPos x y $ getRender "player"
|
||||
|
||||
focusPlayer :: Game -> Picture -> Picture
|
||||
focusPlayer Game{ player = Player{ position = (x, y)}} = translate centerX centerY
|
||||
where centerX = resolution * zoom * fromIntegral (negate x)
|
||||
centerY = resolution * zoom * fromIntegral (negate y)
|
|
@ -1,12 +1,48 @@
|
|||
module RPGEngine.Render.Level
|
||||
( renderLevel
|
||||
module RPGEngine.Render.Playing
|
||||
( renderPlaying
|
||||
) where
|
||||
|
||||
import Graphics.Gloss
|
||||
import RPGEngine.Data
|
||||
import RPGEngine.Render.Core (getRender, setRenderPos, zoom, resolution)
|
||||
import RPGEngine.Render.Core ( Renderer, getRender, setRenderPos )
|
||||
|
||||
renderLevel :: Level -> Picture
|
||||
import RPGEngine.Data
|
||||
( Player(..),
|
||||
Entity(..),
|
||||
Item(..),
|
||||
Physical(..),
|
||||
Layout,
|
||||
Level(..),
|
||||
State(..),
|
||||
Game(..) )
|
||||
import Graphics.Gloss ( Picture, pictures )
|
||||
import Graphics.Gloss.Data.Picture (translate)
|
||||
import RPGEngine.Config (resolution, zoom)
|
||||
|
||||
------------------------------ Exported ------------------------------
|
||||
|
||||
renderPlaying :: Renderer Game
|
||||
renderPlaying g@Game{ state = Playing { level = lvl }, player = player } = pictures [
|
||||
renderLevel lvl,
|
||||
renderPlayer player
|
||||
]
|
||||
|
||||
------------------------------- Player -------------------------------
|
||||
|
||||
renderPlayer :: Renderer Player
|
||||
renderPlayer Player{ position = (x, y) } = move picture
|
||||
where move = setRenderPos x y
|
||||
picture = getRender "player"
|
||||
|
||||
-- Center the player in the middle of the screen.
|
||||
-- Not in use at the moment, might be useful later.
|
||||
focusPlayer :: Game -> Picture -> Picture
|
||||
focusPlayer Game{ player = Player{ position = (x, y)}} = move
|
||||
where move = translate centerX centerY
|
||||
centerX = resolution * zoom * fromIntegral (negate x)
|
||||
centerY = resolution * zoom * fromIntegral (negate y)
|
||||
|
||||
------------------------------- Level --------------------------------
|
||||
|
||||
renderLevel :: Renderer Level
|
||||
renderLevel Level{ layout = l, items = i, entities = e } = level
|
||||
where level = pictures [void, layout, items, entities]
|
||||
void = createVoid
|
||||
|
@ -28,6 +64,18 @@ renderStrip list = pictures physicals
|
|||
image Exit = pictures [getRender "tile", getRender "exit"]
|
||||
count = length list - 1
|
||||
|
||||
createVoid :: Picture
|
||||
createVoid = setRenderPos offX offY $ pictures voids
|
||||
where voids = [setRenderPos x y void | x <- [0 .. width], y <- [0 .. height]]
|
||||
void = getRender "void"
|
||||
intZoom = round zoom :: Int
|
||||
height = round $ 4320 / resolution / zoom
|
||||
width = round $ 7680 / resolution / zoom
|
||||
offX = negate (width `div` 2)
|
||||
offY = negate (height `div` 2)
|
||||
|
||||
-------------------------- Items & Entities --------------------------
|
||||
|
||||
renderItems :: [Item] -> Picture
|
||||
renderItems list = pictures $ map renderItem list
|
||||
|
||||
|
@ -40,14 +88,4 @@ renderEntities list = pictures $ map renderEntity list
|
|||
|
||||
renderEntity :: Entity -> Picture
|
||||
renderEntity Entity{ entityId = id, entityX = x, entityY = y} = setRenderPos x y image
|
||||
where image = getRender id
|
||||
|
||||
createVoid :: Picture
|
||||
createVoid = setRenderPos offX offY $ pictures voids
|
||||
where voids = [setRenderPos x y void | x <- [0 .. width], y <- [0 .. height]]
|
||||
void = getRender "void"
|
||||
intZoom = round zoom :: Int
|
||||
height = round $ 4320 / resolution / zoom
|
||||
width = round $ 7680 / resolution / zoom
|
||||
offX = negate (width `div` 2)
|
||||
offY = negate (height `div` 2)
|
||||
where image = getRender id
|
14
lib/RPGEngine/Render/Win.hs
Normal file
14
lib/RPGEngine/Render/Win.hs
Normal file
|
@ -0,0 +1,14 @@
|
|||
module RPGEngine.Render.Win
|
||||
( renderWin
|
||||
) where
|
||||
|
||||
import RPGEngine.Render.Core ( Renderer )
|
||||
|
||||
import RPGEngine.Data ( Game )
|
||||
import Graphics.Gloss (text)
|
||||
|
||||
----------------------------------------------------------------------
|
||||
|
||||
-- TODO
|
||||
renderWin :: Renderer Game
|
||||
renderWin _ = text "Win"
|
Reference in a new issue