Skip to content

Commit

Permalink
Game.Geometry.Cube
Browse files Browse the repository at this point in the history
  • Loading branch information
alt-romes committed Jul 11, 2024
1 parent 5979a8b commit c4605b7
Show file tree
Hide file tree
Showing 9 changed files with 100 additions and 68 deletions.
6 changes: 3 additions & 3 deletions cabal.project
Original file line number Diff line number Diff line change
Expand Up @@ -14,9 +14,9 @@ packages:
-- ~/Developer/fir/
-- ~/Developer/gl-block/

profiling: true
package *
profiling-detail: late
-- profiling: true
-- package *
-- profiling-detail: late

package ghengin-core
flags: +enable-culling
Expand Down
62 changes: 3 additions & 59 deletions examples/simple-camera/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,6 +7,7 @@
{-# OPTIONS_GHC -Wno-name-shadowing #-}
module Main where

import qualified Prelude
import GHC.Generics
import Geomancy.Vec3
import Geomancy.Mat4
Expand All @@ -28,68 +29,11 @@ import qualified Prelude
import qualified Math.Linear as FIR
import qualified FIR

import Game.Geometry.Cube (coloredCube)
import Shaders

type CubeMesh = Mesh '[Vec3, Vec3] '[Transform]

cubeVertices :: [Vertex '[Vec3, Vec3]]
cubeVertices = [

-- left face (white)
vec3 (-0.5) (-0.5) (-0.5) :&: white,
vec3 (-0.5) (-0.5) (0.5) :&: white,
vec3 (-0.5) (0.5) (0.5) :&: white,
vec3 (-0.5) (0.5) (0.5) :&: white,
vec3 (-0.5) (0.5) (-0.5) :&: white,
vec3 (-0.5) (-0.5) (-0.5) :&: white,

-- right face (yellow)
vec3 (-0.5) (-0.5) (-0.5) :&: yellow,
vec3 0.5 (0.5) (-0.5) :&: yellow,
vec3 0.5 (-0.5) (-0.5) :&: yellow,
vec3 (-0.5) (-0.5) (-0.5) :&: yellow,
vec3 (-0.5) (0.5) (-0.5) :&: yellow,
vec3 0.5 (0.5) (-0.5) :&: yellow,

-- top face (orange, remember y axis points down)
vec3 (-0.5) (-0.5) (-0.5) :&: orange,
vec3 (0.5) (-0.5) (-0.5) :&: orange,
vec3 (0.5) (-0.5) (0.5) :&: orange,
vec3 (-0.5) (-0.5) (-0.5) :&: orange,
vec3 (0.5) (-0.5) (0.5) :&: orange,
vec3 (-0.5) (-0.5) (0.5) :&: orange,

-- bottom face (red)
vec3 (-0.5) (0.5) (-0.5) :&: red,
vec3 (-0.5) (0.5) (0.5) :&: red,
vec3 (0.5) (0.5) (0.5) :&: red,
vec3 (-0.5) (0.5) (-0.5) :&: red,
vec3 (0.5) (0.5) (0.5) :&: red,
vec3 (0.5) (0.5) (-0.5) :&: red,

-- nose face (blue)
vec3 (0.5) (0.5) (-0.5) :&: blue,
vec3 (0.5) (0.5) (0.5) :&: blue,
vec3 (0.5) (-0.5) (0.5) :&: blue,
vec3 (0.5) (-0.5) (0.5) :&: blue,
vec3 (0.5) (-0.5) (-0.5) :&: blue,
vec3 (0.5) (0.5) (-0.5) :&: blue,

-- tail face (green)
vec3 (-0.5) (0.5) (0.5) :&: green,
vec3 (-0.5) (-0.5) (0.5) :&: green,
vec3 (0.5) (0.5) (0.5) :&: green,
vec3 (-0.5) (-0.5) (0.5) :&: green,
vec3 (0.5) (-0.5) (0.5) :&: green,
vec3 (0.5) (0.5) (0.5) :&: green]
where
white = vec3 0.9 0.9 0.9
yellow = vec3 0.8 0.8 0.1
orange = vec3 0.9 0.6 0.1
red = vec3 0.8 0.1 0.1
blue = vec3 0.1 0.1 0.8
green = vec3 0.1 0.8 0.1

data Camera
= Camera { view :: Mat4
, proj :: Mat4
Expand Down Expand Up @@ -128,7 +72,7 @@ main = do
pipeline <- (makeRenderPipeline shaderPipeline (StaticBinding (Ur defaultCamera) :## GHNil) )
(emptyMat, pipeline) <- (material GHNil pipeline )
(mesh :: CubeMesh, pipeline) <-
(createMesh pipeline (DynamicBinding (Ur (rotateY (pi/4))) :## GHNil) cubeVertices )
(createMesh pipeline (DynamicBinding (Ur (rotateY (pi/4))) :## GHNil) coloredCube )
(rq, Ur pkey) <- pure (insertPipeline pipeline LMon.mempty)
(rq, Ur mkey) <- pure (insertMaterial pkey emptyMat rq)
(rq, Ur mshkey) <- pure (insertMesh mkey mesh rq)
Expand Down
4 changes: 2 additions & 2 deletions examples/simple-camera/Shaders.hs
Original file line number Diff line number Diff line change
Expand Up @@ -36,8 +36,8 @@ shaderPipeline
G.:>-> fragment

type VertexDefs =
'[ "in_position" ':-> Input '[ Location 0 ] (V 3 Float)
, "in_color" ':-> Input '[ Location 1 ] (V 3 Float)
'[ "in_position" ':-> Input '[ Location 1 ] (V 3 Float) -- position comes after color (location=1)
, "in_color" ':-> Input '[ Location 0 ] (V 3 Float) -- color comes first (location=0)
, "frag_color" ':-> Output '[ Location 0 ] (V 3 Float)
, "model" ':-> Uniform '[ DescriptorSet 2, Binding 0 ] (Struct '[ "m" ':-> M 4 4 Float ])
, "camera" ':-> Uniform '[ DescriptorSet 0, Binding 0 ]
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -187,7 +187,7 @@ createGraphicsPipeline ppstages pushConstantRanges = Unsafe.toLinearN @2 \render
, cullMode = Vk.CULL_MODE_NONE
#endif

, frontFace = Vk.FRONT_FACE_COUNTER_CLOCKWISE -- Default vertice front face to be defined clock wise
, frontFace = Vk.FRONT_FACE_COUNTER_CLOCKWISE -- Default vertice front face to be defined counter clock wise
-- , frontFace = Vk.FRONT_FACE_CLOCKWISE
, depthBiasEnable = False -- Biasing depth values based on a fragment's slope (could be used for shadow mapping)
, depthBiasConstantFactor = 0
Expand Down
68 changes: 68 additions & 0 deletions ghengin/ghengin-geometry/Game/Geometry/Cube.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,68 @@
-- |
--
-- Assumptions:
--
-- * Using a cartesian coordinate space XYZ where Y points "up" and Z points "outwards":
-- ZX is parallel to the floor/ceiling, YX is parallel to the screen, YZ is
-- perpendicular to the screen...
--
-- * Using triangle list primitive topology
--
-- * Using COUNTER_CLOCKWISE order for front facing triangles
module Game.Geometry.Cube where

import Prelude -- We often don't need linearity here.
import Ghengin.Core.Mesh.Vertex
import Game.Geometry.Transform

-- | A unit cube centered at (0,0,0).
cube :: [Vertex '[Vec3]]
cube = concatMap (`transform` square)
[ translateV (vec3 0 0 (-0.5)) -- front face
, rotateY pi <> translateV (vec3 0 0 0.5 ) -- back face
, rotateY (pi/2) <> translateV (vec3 0.5 0 0 ) -- right face
, rotateY (-pi/2) <> translateV (vec3 (-0.5) 0 0 ) -- left face
, rotateX (-pi/2) <> translateV (vec3 0 0.5 0 ) -- top face
, rotateX (pi/2) <> translateV (vec3 0 (-0.5) 0 ) -- bottom face
]
-- recall, matrix mult MVP order on CPU


-- | A unit square centered at (0,0,0) along the YZ plane with its front side
-- normal along the X coordinate axis (ie "facing forward").
square :: [Vertex '[Vec3]]
square = Prelude.map Sin
[ vec3 0.5 0.5 0 -- 1,6
, vec3 0.5 (-0.5) 0 -- 2
, vec3 (-0.5) (-0.5) 0 -- 3,4
, vec3 (-0.5) (-0.5) 0 -- 3,4
, vec3 (-0.5) 0.5 0 -- 5
, vec3 0.5 0.5 0 -- 1,6
]

--------------------------------------------------------------------------------
-- * Colored

type Color = Vec3

-- | A colored 'cube'.
-- Note that color is in location=0, and position in location=1
coloredCube :: [Vertex '[Color, Vec3]]
coloredCube = zipWith paint cube [1..] where
paint face (ix::Int)
-- every six vertices we get a new face
| ix <= 6 = blue :& face
| ix <= 6*2 = green :& face
| ix <= 6*3 = yellow :& face
| ix <= 6*4 = white :& face
| ix <= 6*5 = orange :& face
| ix <= 6*6 = red :& face
| otherwise = error "unexpected vertice unit cube"

white = vec3 0.9 0.9 0.9
yellow = vec3 0.8 0.8 0.1
orange = vec3 0.9 0.6 0.1
red = vec3 0.8 0.1 0.1
blue = vec3 0.1 0.1 0.8
green = vec3 0.1 0.8 0.1

2 changes: 1 addition & 1 deletion ghengin/ghengin-geometry/Game/Geometry/Sphere.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# OPTIONS_GHC -Wno-name-shadowing -Wno-incomplete-uni-patterns #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE BlockArguments #-}
Expand All @@ -18,7 +19,6 @@ import qualified Data.Vector.Storable as SV
import qualified Data.IntMap as IM
import qualified Data.Map as M

import Data.Foldable (foldl')
import Data.List (sort)
import Data.List.Split (chunksOf)

Expand Down
20 changes: 20 additions & 0 deletions ghengin/ghengin-geometry/Game/Geometry/Transform.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,20 @@
module Game.Geometry.Transform
( transform
, module Geomancy.Transform
, module Geomancy.Vec3
)
where

import Ghengin.Core.Mesh.Vertex
import Geomancy.Vec3
import Geomancy.Transform

-- | Transform a list of vertices.
-- Use with functions re-exported from Geomancy.Transform
--
-- Recall, from Geomancy's documentation:
-- CPU-side matrices compose in MVP order, optimized for mconcat (local1 : local2 : ... : root) operation.
-- GPU-side, in GLSL, it is PVM * v.
transform :: Transform -> [Vertex '[Vec3]] -> [Vertex '[Vec3]]
transform tr vs = [ Sin (v `apply` tr) | Sin v <- vs ]

3 changes: 2 additions & 1 deletion ghengin/ghengin.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -226,7 +226,8 @@ library camera
library geometry
import: common-flags
visibility: public
exposed-modules: Game.Geometry, Game.Geometry.Sphere
exposed-modules: Game.Geometry, Game.Geometry.Sphere, Game.Geometry.Cube,
Game.Geometry.Transform
build-depends: base >=4.19.0.0, ghengin-core:backend-independent-bits, ghengin-core, vector, containers, split, geomancy
hs-source-dirs: ghengin-geometry
default-language: GHC2021
Expand Down
1 change: 0 additions & 1 deletion utils/live
Original file line number Diff line number Diff line change
Expand Up @@ -2,4 +2,3 @@

ghcid --test "Main.main" --command "cabal repl --semaphore --ghc-options=-fno-ghci-sandbox $@"


0 comments on commit c4605b7

Please sign in to comment.