restructure: moved Graphics and Physics into own subfolders
This commit is contained in:
parent
61451a4a10
commit
1ab8befd8f
36 changed files with 100 additions and 175 deletions
|
@ -21,15 +21,9 @@ executable pituicat
|
|||
, Types.Application
|
||||
, Types.Subsystems
|
||||
, Types.Map
|
||||
, Types.Texture
|
||||
, Types.Cast
|
||||
, Types.StageSet
|
||||
, Types.Tangible
|
||||
, Types.Graphics
|
||||
, Types.Graphics.VertexArray
|
||||
, Types.Graphics.VertexBuffer
|
||||
, Types.Graphics.IndexBuffer
|
||||
, Types.Graphics.Shader
|
||||
, Types.Util
|
||||
, Types.Player
|
||||
, Types.PowerUp
|
||||
|
@ -38,14 +32,22 @@ executable pituicat
|
|||
, Classes.Actor
|
||||
, Classes.Prop
|
||||
, Classes.Collectable
|
||||
, Classes.Graphics
|
||||
, Classes.Graphics.Bindable
|
||||
, Classes.Graphics.Buffer
|
||||
, Classes.Graphics.VertexLayout
|
||||
, Classes.Graphics.Drawable
|
||||
, Classes.Physics
|
||||
, Classes.Physics.Mass
|
||||
, Classes.Physics.Collidible
|
||||
, Graphics
|
||||
, Graphics.Types
|
||||
, Graphics.Types.VertexArray
|
||||
, Graphics.Types.VertexBuffer
|
||||
, Graphics.Types.IndexBuffer
|
||||
, Graphics.Types.Shader
|
||||
, Graphics.Types.Texture
|
||||
, Graphics.Classes
|
||||
, Graphics.Classes.Bindable
|
||||
, Graphics.Classes.Buffer
|
||||
, Graphics.Classes.VertexLayout
|
||||
, Graphics.Classes.Drawable
|
||||
, Physics
|
||||
, Physics.Classes
|
||||
, Physics.Classes.Mass
|
||||
, Physics.Classes.Collidible
|
||||
, Scenes.Test
|
||||
, Scenes.Test.Types
|
||||
, Scenes.Test.Util
|
||||
|
|
|
@ -2,9 +2,7 @@ module Classes
|
|||
( module C
|
||||
) where
|
||||
|
||||
import Classes.Graphics as C
|
||||
import Classes.Scene as C
|
||||
import Classes.Prop as C
|
||||
import Classes.Actor as C
|
||||
import Classes.Physics as C
|
||||
import Classes.Collectable as C
|
||||
|
|
|
@ -3,7 +3,7 @@ module Classes.Actor where
|
|||
-- internal imports
|
||||
|
||||
import Classes.Prop
|
||||
import Classes.Physics.Collidible
|
||||
import Physics.Classes.Collidible
|
||||
|
||||
class (Prop a, Collidible a) => Actor a where
|
||||
|
||||
|
|
|
@ -1,6 +1,6 @@
|
|||
module Classes.Collectable where
|
||||
|
||||
import Classes.Physics.Collidible (Collidible)
|
||||
import Physics.Classes.Collidible (Collidible)
|
||||
|
||||
-- | All kinds of Effects present in the game
|
||||
data Effect
|
||||
|
|
|
@ -1,8 +0,0 @@
|
|||
module Classes.Graphics
|
||||
( module G
|
||||
) where
|
||||
|
||||
import Classes.Graphics.Bindable as G
|
||||
import Classes.Graphics.Buffer as G
|
||||
import Classes.Graphics.VertexLayout as G
|
||||
import Classes.Graphics.Drawable as G
|
|
@ -1,6 +0,0 @@
|
|||
module Classes.Physics
|
||||
( module P
|
||||
) where
|
||||
|
||||
import Classes.Physics.Mass as P
|
||||
import Classes.Physics.Collidible as P
|
|
@ -2,7 +2,7 @@ module Classes.Prop where
|
|||
|
||||
-- internal imports
|
||||
|
||||
import Classes.Graphics.Drawable
|
||||
import Graphics.Classes.Drawable
|
||||
|
||||
class (Show a, Drawable a) => Prop a where
|
||||
|
||||
|
|
6
src/Graphics.hs
Normal file
6
src/Graphics.hs
Normal file
|
@ -0,0 +1,6 @@
|
|||
module Graphics
|
||||
( module G
|
||||
) where
|
||||
|
||||
import Graphics.Classes as G
|
||||
import Graphics.Types as G
|
8
src/Graphics/Classes.hs
Normal file
8
src/Graphics/Classes.hs
Normal file
|
@ -0,0 +1,8 @@
|
|||
module Graphics.Classes
|
||||
( module GC
|
||||
) where
|
||||
|
||||
import Graphics.Classes.Bindable as GC
|
||||
import Graphics.Classes.Buffer as GC
|
||||
import Graphics.Classes.VertexLayout as GC
|
||||
import Graphics.Classes.Drawable as GC
|
|
@ -1,4 +1,4 @@
|
|||
module Classes.Graphics.Bindable where
|
||||
module Graphics.Classes.Bindable where
|
||||
|
||||
-- | typeclass for bindable objects like buffers, vertex arrays or shaders
|
||||
class Bindable a where
|
|
@ -1,6 +1,6 @@
|
|||
{-# LANGUAGE TypeFamilies #-}
|
||||
{-# LANGUAGE FlexibleContexts #-}
|
||||
module Classes.Graphics.Buffer where
|
||||
module Graphics.Classes.Buffer where
|
||||
|
||||
import qualified Graphics.Rendering.OpenGL as GL
|
||||
|
||||
|
@ -8,7 +8,7 @@ import Foreign.Storable
|
|||
|
||||
-- internal imports
|
||||
|
||||
import Classes.Graphics.Bindable
|
||||
import Graphics.Classes.Bindable
|
||||
|
||||
-- | this aims to be a typeclass for all used buffer objects throughout the
|
||||
-- game. all buffer objects have to instanciate the Bindable typeclass.
|
|
@ -1,11 +1,11 @@
|
|||
{-# LANGUAGE TypeFamilies #-}
|
||||
module Classes.Graphics.Drawable where
|
||||
module Graphics.Classes.Drawable where
|
||||
|
||||
import qualified Data.Vector as V
|
||||
|
||||
-- iternal imports
|
||||
|
||||
import Types.Graphics.VertexBuffer (Vertex)
|
||||
import Graphics.Types.VertexBuffer (Vertex)
|
||||
|
||||
-- | A typeclass for all drawable objects
|
||||
class Drawable a where
|
|
@ -1,13 +1,13 @@
|
|||
{-# LANGUAGE TypeFamilies #-}
|
||||
{-# LANGUAGE FlexibleContexts #-}
|
||||
{-# LANGUAGE AllowAmbiguousTypes #-}
|
||||
module Classes.Graphics.VertexLayout where
|
||||
module Graphics.Classes.VertexLayout where
|
||||
|
||||
import qualified Graphics.Rendering.OpenGL as GL
|
||||
|
||||
-- internal imports
|
||||
|
||||
import Classes.Graphics.Bindable
|
||||
import Graphics.Classes.Bindable
|
||||
|
||||
class (Bindable (VertBuffer v)) => VertexLayout v where
|
||||
|
9
src/Graphics/Types.hs
Normal file
9
src/Graphics/Types.hs
Normal file
|
@ -0,0 +1,9 @@
|
|||
module Graphics.Types
|
||||
( module GT
|
||||
) where
|
||||
|
||||
import Graphics.Types.VertexArray as GT
|
||||
import Graphics.Types.VertexBuffer as GT
|
||||
import Graphics.Types.IndexBuffer as GT
|
||||
import Graphics.Types.Shader as GT
|
||||
import Graphics.Types.Texture as GT
|
|
@ -1,7 +1,7 @@
|
|||
{-# LANGUAGE TypeFamilies #-}
|
||||
{-# LANGUAGE ScopedTypeVariables #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
module Types.Graphics.IndexBuffer where
|
||||
module Graphics.Types.IndexBuffer where
|
||||
|
||||
import Affection
|
||||
|
||||
|
@ -23,8 +23,8 @@ import Foreign.C.Types
|
|||
|
||||
-- internal imports
|
||||
|
||||
import Classes.Graphics.Bindable
|
||||
import Classes.Graphics.Buffer
|
||||
import Graphics.Classes.Bindable
|
||||
import Graphics.Classes.Buffer
|
||||
|
||||
-- layout of the IndexBuffer data object
|
||||
data IndexBuffer = IndexBuffer
|
|
@ -1,7 +1,7 @@
|
|||
{-# LANGUAGE TypeSynonymInstances #-}
|
||||
{-# LANGUAGE FlexibleInstances #-}
|
||||
|
||||
module Types.Graphics.Shader where
|
||||
module Graphics.Types.Shader where
|
||||
|
||||
import qualified Graphics.Rendering.OpenGL as GL
|
||||
import qualified Graphics.GL as GLRaw
|
||||
|
@ -19,7 +19,7 @@ import Foreign.Storable
|
|||
|
||||
-- internal imports
|
||||
|
||||
import Classes.Graphics.Bindable
|
||||
import Graphics.Classes.Bindable
|
||||
|
||||
data Shader = Shader
|
||||
{ shaderId :: GL.Program
|
|
@ -1,4 +1,4 @@
|
|||
module Types.Texture where
|
||||
module Graphics.Types.Texture where
|
||||
|
||||
import SDL (($=))
|
||||
|
||||
|
@ -15,7 +15,7 @@ import Foreign
|
|||
|
||||
-- internal imports
|
||||
|
||||
import Classes.Graphics.Bindable
|
||||
import Graphics.Classes.Bindable
|
||||
|
||||
data Texture = Texture
|
||||
{ textureId :: GL.TextureObject
|
|
@ -1,5 +1,5 @@
|
|||
{-# LANGUAGE TypeFamilies #-}
|
||||
module Types.Graphics.VertexArray where
|
||||
module Graphics.Types.VertexArray where
|
||||
|
||||
import qualified Graphics.Rendering.OpenGL as GL
|
||||
|
||||
|
@ -7,7 +7,7 @@ import SDL (($=))
|
|||
|
||||
-- internal imports
|
||||
|
||||
import Classes.Graphics.Bindable
|
||||
import Graphics.Classes.Bindable
|
||||
|
||||
newtype VertexArray = VertexArray
|
||||
{ vArrId :: GL.VertexArrayObject
|
|
@ -2,7 +2,7 @@
|
|||
{-# LANGUAGE DeriveGeneric #-}
|
||||
{-# LANGUAGE FlexibleInstances #-}
|
||||
{-# LANGUAGE ScopedTypeVariables #-}
|
||||
module Types.Graphics.VertexBuffer where
|
||||
module Graphics.Types.VertexBuffer where
|
||||
|
||||
import qualified Graphics.Rendering.OpenGL as GL
|
||||
|
||||
|
@ -24,9 +24,9 @@ import GHC.Generics
|
|||
|
||||
-- internal imports
|
||||
|
||||
import Classes.Graphics.Bindable
|
||||
import Classes.Graphics.Buffer
|
||||
import Classes.Graphics.VertexLayout
|
||||
import Graphics.Classes.Bindable
|
||||
import Graphics.Classes.Buffer
|
||||
import Graphics.Classes.VertexLayout
|
||||
|
||||
-- | layout of the VertexBuffer data object
|
||||
data VertexBuffer = VertexBuffer
|
|
@ -15,6 +15,7 @@ import Control.Monad (foldM)
|
|||
-- internal imports
|
||||
|
||||
import Types
|
||||
import Graphics
|
||||
|
||||
constructMap :: LevelDescriptor -> GL.GLuint -> IO LevelMap
|
||||
constructMap desc tilemapSlot = do
|
||||
|
|
5
src/Physics.hs
Normal file
5
src/Physics.hs
Normal file
|
@ -0,0 +1,5 @@
|
|||
module Physics
|
||||
( module P
|
||||
) where
|
||||
|
||||
import Physics.Classes as P
|
6
src/Physics/Classes.hs
Normal file
6
src/Physics/Classes.hs
Normal file
|
@ -0,0 +1,6 @@
|
|||
module Physics.Classes
|
||||
( module PC
|
||||
) where
|
||||
|
||||
import Physics.Classes.Mass as PC
|
||||
import Physics.Classes.Collidible as PC
|
|
@ -1,6 +1,6 @@
|
|||
{-# LANGUAGE AllowAmbiguousTypes #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
module Classes.Physics.Collidible where
|
||||
module Physics.Classes.Collidible where
|
||||
|
||||
import Affection as A
|
||||
|
||||
|
@ -10,7 +10,7 @@ import Data.String (fromString)
|
|||
|
||||
-- internal imports
|
||||
|
||||
import Classes.Physics.Mass
|
||||
import Physics.Classes.Mass
|
||||
|
||||
data CollisionResult time direction
|
||||
= NoCollision
|
|
@ -1,4 +1,4 @@
|
|||
module Classes.Physics.Mass where
|
||||
module Physics.Classes.Mass where
|
||||
|
||||
import Linear
|
||||
|
|
@ -9,8 +9,7 @@ import Foreign.Ptr
|
|||
|
||||
-- internal imports
|
||||
|
||||
import Classes.Graphics
|
||||
import Types.Graphics
|
||||
import Graphics
|
||||
|
||||
draw :: VertexArray -> IndexBuffer -> Shader -> IO ()
|
||||
draw va ib sp = do
|
||||
|
|
|
@ -20,6 +20,7 @@ import Control.Concurrent.STM
|
|||
|
||||
import Types
|
||||
import Classes
|
||||
import Graphics
|
||||
import Renderer as R
|
||||
import Scenes.Test.Types as Test
|
||||
import Scenes.Test.Util as Test
|
||||
|
|
|
@ -16,6 +16,7 @@ import Linear
|
|||
|
||||
import Types
|
||||
import Classes
|
||||
import Graphics
|
||||
import Map
|
||||
import Scenes.Test.Types
|
||||
import Scenes.Test.Util
|
||||
|
|
|
@ -11,6 +11,7 @@ import qualified Data.Vector as V
|
|||
-- internal imports
|
||||
|
||||
import Types
|
||||
import Graphics
|
||||
|
||||
data Test = Test
|
||||
{ testMap :: TMVar LevelMap
|
||||
|
|
|
@ -19,6 +19,7 @@ import Linear
|
|||
import Scenes.Test.Types
|
||||
import Classes
|
||||
import Types
|
||||
import Physics
|
||||
|
||||
update
|
||||
:: Test
|
||||
|
|
|
@ -16,6 +16,7 @@ import Control.Arrow ((***))
|
|||
|
||||
import Classes
|
||||
import Types
|
||||
import Graphics
|
||||
|
||||
testLevelDesc :: LevelDescriptor
|
||||
testLevelDesc = LevelDescriptor
|
||||
|
|
|
@ -5,10 +5,8 @@ module Types
|
|||
import Types.Application as T
|
||||
import Types.Subsystems as T
|
||||
import Types.Map as T
|
||||
import Types.Texture as T
|
||||
import Types.Cast as T
|
||||
import Types.StageSet as T
|
||||
import Types.Graphics as T
|
||||
import Types.Player as T
|
||||
import Types.Util as T
|
||||
import Types.PowerUp as T
|
||||
|
|
|
@ -1,8 +0,0 @@
|
|||
module Types.Graphics
|
||||
( module G
|
||||
) where
|
||||
|
||||
import Types.Graphics.VertexArray as G
|
||||
import Types.Graphics.VertexBuffer as G
|
||||
import Types.Graphics.IndexBuffer as G
|
||||
import Types.Graphics.Shader as G
|
|
@ -1,93 +0,0 @@
|
|||
{-# LANGUAGE OverloadedStrings #-}
|
||||
module Graphics.Texture where
|
||||
|
||||
import SDL (($=), get)
|
||||
|
||||
import qualified Graphics.Rendering.OpenGL as GL
|
||||
|
||||
import Codec.Picture
|
||||
import Codec.Picture.Extra
|
||||
|
||||
import Data.Either
|
||||
|
||||
import Data.Vector.Storable as VS
|
||||
|
||||
import Data.String (fromString)
|
||||
|
||||
import Foreign.Ptr
|
||||
import Foreign.Marshal.Alloc (free)
|
||||
|
||||
import Linear
|
||||
|
||||
-- internal imports
|
||||
|
||||
import Classes.Graphics.Bindable
|
||||
|
||||
data Texture = Texture
|
||||
{ texId :: GL.TextureObject
|
||||
, texSlot :: GL.TextureUnit
|
||||
}
|
||||
|
||||
instance Bindable Texture where
|
||||
|
||||
bind t = do
|
||||
GL.activeTexture $= texSlot t
|
||||
GL.textureBinding GL.Texture2D $= Just (texId t)
|
||||
|
||||
unbind _ = GL.textureBinding GL.Texture2D $= Nothing
|
||||
|
||||
newTexture :: FilePath -> GL.GLuint -> IO (Either String Texture)
|
||||
newTexture fp slot = do
|
||||
|
||||
eimg <- readImage fp
|
||||
|
||||
case eimg of
|
||||
Left err -> do
|
||||
let mesg = ("reading file " <> fp <> " failed: " <> show err)
|
||||
logIO Error (fromString mesg)
|
||||
return $ Left mesg
|
||||
|
||||
Right rawImg -> do
|
||||
|
||||
-- convert image format
|
||||
let img = flipVertically $ convertRGBA8 rawImg
|
||||
|
||||
-- extract the raw pointer from vector
|
||||
unsafeWith (imageData img) $ \ptr -> do
|
||||
-- create texture object
|
||||
tex <- Texture
|
||||
<$> GL.genObjectName
|
||||
<*> (pure $ GL.TextureUnit slot)
|
||||
-- <*> (pure fp)
|
||||
let dimensions = fromIntegral <$> V2 (imageWidth img) (imageHeight img)
|
||||
-- <*> (pure $ componentCount (VS.head $ imageData img))
|
||||
data_ = castPtr ptr
|
||||
|
||||
-- bind texture
|
||||
bind tex
|
||||
|
||||
-- set texture parameters
|
||||
GL.textureFilter GL.Texture2D $= ((GL.Linear', Nothing), GL.Linear')
|
||||
GL.textureWrapMode GL.Texture2D GL.S $= (GL.Repeated, GL.Clamp)
|
||||
GL.textureWrapMode GL.Texture2D GL.T $= (GL.Repeated, GL.Clamp)
|
||||
|
||||
-- put data into GPU memory
|
||||
loadTexture tex dimensions data_
|
||||
|
||||
-- unbind texture
|
||||
unbind tex
|
||||
|
||||
-- pass texture object out
|
||||
return $ Right tex
|
||||
|
||||
loadTexture :: Texture -> V2 GL.GLsizei -> Ptr () -> IO ()
|
||||
loadTexture tex dimensions data_ =
|
||||
let (V2 w h) = dimensions
|
||||
in GL.texImage2D
|
||||
GL.Texture2D
|
||||
GL.NoProxy
|
||||
0
|
||||
GL.RGBA'
|
||||
(GL.TextureSize2D w h)
|
||||
0
|
||||
(GL.PixelData GL.RGBA GL.UnsignedByte data_)
|
|
@ -8,10 +8,10 @@ import Linear
|
|||
|
||||
-- internal imports
|
||||
|
||||
import Types.Texture
|
||||
import Types.Graphics.VertexBuffer
|
||||
import Classes.Graphics.Drawable
|
||||
import Classes.Physics
|
||||
import Graphics.Types.Texture
|
||||
import Graphics.Types.VertexBuffer
|
||||
import Graphics.Classes.Drawable
|
||||
import Physics.Classes
|
||||
|
||||
data LevelMap = LevelMap
|
||||
{ mapLayers :: V.Vector Layer -- ^ Layer stack
|
||||
|
|
|
@ -13,15 +13,17 @@ import Data.String (fromString)
|
|||
|
||||
import Util
|
||||
|
||||
import Classes.Graphics.Drawable
|
||||
import Classes.Graphics.Bindable
|
||||
import Classes.Prop
|
||||
import Classes.Actor
|
||||
import Classes.Physics
|
||||
import Classes.Collectable
|
||||
|
||||
import Types.Graphics.VertexBuffer
|
||||
import Types.Texture
|
||||
import Graphics.Classes.Drawable
|
||||
import Graphics.Classes.Bindable
|
||||
import Graphics.Types.VertexBuffer
|
||||
import Graphics.Types.Texture
|
||||
|
||||
import Physics.Classes
|
||||
|
||||
import Types.Subsystems
|
||||
|
||||
catMoveVelocity :: Double
|
||||
|
|
|
@ -6,15 +6,16 @@ import Linear
|
|||
|
||||
-- internal imports
|
||||
|
||||
import Classes.Graphics.Drawable
|
||||
import Classes.Graphics.Bindable
|
||||
import Classes.Collectable
|
||||
import Classes.Prop
|
||||
import Classes.Actor
|
||||
import Classes.Physics
|
||||
|
||||
import Types.Graphics.VertexBuffer
|
||||
import Types.Texture
|
||||
import Physics.Classes
|
||||
|
||||
import Graphics.Types.VertexBuffer
|
||||
import Graphics.Types.Texture
|
||||
import Graphics.Classes.Drawable
|
||||
import Graphics.Classes.Bindable
|
||||
|
||||
import Util
|
||||
|
||||
|
|
Loading…
Reference in a new issue