aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--Graphics/Glyph/ExtendedGL.hs44
-rw-r--r--Graphics/Glyph/GlyphObject.hs10
-rw-r--r--Graphics/Glyph/Shaders.hs31
-rw-r--r--Resources.hs10
-rw-r--r--shaders/water.frag36
5 files changed, 86 insertions, 45 deletions
diff --git a/Graphics/Glyph/ExtendedGL.hs b/Graphics/Glyph/ExtendedGL.hs
index 7742ba8..86258e1 100644
--- a/Graphics/Glyph/ExtendedGL.hs
+++ b/Graphics/Glyph/ExtendedGL.hs
@@ -1,6 +1,7 @@
module Graphics.Glyph.ExtendedGL where
-import Graphics.Rendering.OpenGL
+import Graphics.Rendering.OpenGL hiding (Points,Lines,Triangles)
+import qualified Graphics.Rendering.OpenGL as GL
import Graphics.Rendering.OpenGL.Raw.Core31
import Graphics.Rendering.OpenGL.Raw.ARB
@@ -12,20 +13,33 @@ import Foreign.C.Types
import System.IO.Unsafe
import Control.Monad
-marshalPrimitiveMode :: PrimitiveMode -> GLenum
-marshalPrimitiveMode x = case x of
- Points -> 0x0
- Lines -> 0x1
- LineLoop -> 0x2
- LineStrip -> 0x3
- Triangles -> 0x4
- TriangleStrip -> 0x5
- TriangleFan -> 0x6
- Quads -> 0x7
- QuadStrip -> 0x8
- Polygon -> 0x9
-
-drawArraysInstanced :: PrimitiveMode -> ArrayIndex -> NumArrayIndices -> GLsizei -> IO ()
+data ExPrimitiveMode = Points | Triangles | Lines | Patches deriving (Show,Enum)
+
+class IsPrimitiveModeMarshallable a where
+ marshalPrimitiveMode :: a -> GLuint
+
+instance IsPrimitiveModeMarshallable ExPrimitiveMode where
+ marshalPrimitiveMode x = case x of
+ Points -> gl_POINTS
+ Triangles -> gl_TRIANGLES
+ Lines -> gl_LINES
+ Patches -> gl_PATCHES
+
+instance IsPrimitiveModeMarshallable PrimitiveMode where
+ marshalPrimitiveMode x = case x of
+ GL.Points -> 0x0
+ GL.Lines -> 0x1
+ GL.LineLoop -> 0x2
+ GL.LineStrip -> 0x3
+ GL.Triangles -> 0x4
+ GL.TriangleStrip -> 0x5
+ GL.TriangleFan -> 0x6
+ GL.Quads -> 0x7
+ GL.QuadStrip -> 0x8
+ GL.Polygon -> 0x9
+
+drawArraysInstanced ::
+ (IsPrimitiveModeMarshallable a) => a -> ArrayIndex -> NumArrayIndices -> GLsizei -> IO ()
drawArraysInstanced = glDrawArraysInstanced . marshalPrimitiveMode
vertexAttributeDivisor :: AttribLocation -> SettableStateVar GLuint
diff --git a/Graphics/Glyph/GlyphObject.hs b/Graphics/Glyph/GlyphObject.hs
index a000aa7..29d25bb 100644
--- a/Graphics/Glyph/GlyphObject.hs
+++ b/Graphics/Glyph/GlyphObject.hs
@@ -33,7 +33,7 @@ module Graphics.Glyph.GlyphObject (
import Graphics.Glyph.BufferBuilder
import Graphics.Glyph.Util
import Graphics.Rendering.OpenGL
-import Graphics.Glyph.ExtendedGL
+import Graphics.Glyph.ExtendedGL as Ex
import Data.Setters
import Control.Monad
@@ -55,7 +55,7 @@ data GlyphObject a = GlyphObject {
setupRoutine :: (Maybe (GlyphObject a -> IO ())), -- Setup
setupRoutine2 :: (Maybe (GlyphObject a -> IO ())), -- Setup
teardownRoutine :: (Maybe (GlyphObject a -> IO ())), -- Tear down
- primitiveMode :: PrimitiveMode,
+ primitiveMode :: ExPrimitiveMode,
numInstances :: Int
}
@@ -87,7 +87,7 @@ getSetupRoutine = setupRoutine
getTeardownRoutine :: GlyphObject a -> (Maybe (GlyphObject a -> IO ()))
getTeardownRoutine = teardownRoutine
-getPrimitiveMode :: GlyphObject a -> PrimitiveMode
+getPrimitiveMode :: GlyphObject a -> ExPrimitiveMode
getPrimitiveMode = primitiveMode
newGlyphObject :: BuilderM GLfloat x ->
@@ -98,7 +98,7 @@ newGlyphObject :: BuilderM GLfloat x ->
a ->
Maybe (GlyphObject a -> IO ()) ->
Maybe (GlyphObject a -> IO ()) ->
- PrimitiveMode ->
+ ExPrimitiveMode ->
IO (GlyphObject a)
newGlyphObject builder vertAttr normAttr colorAttr textureAttr res setup tear mode = do
@@ -164,7 +164,7 @@ newDefaultGlyphObject builder resources =
resources
Nothing -- setup
Nothing -- teardown
- Triangles -- primitive
+ Ex.Triangles -- primitive
newDefaultGlyphObjectWithClosure :: BuilderM GLfloat x -> a -> (GlyphObject a -> IO ()) -> IO (GlyphObject a)
newDefaultGlyphObjectWithClosure builder res func =
diff --git a/Graphics/Glyph/Shaders.hs b/Graphics/Glyph/Shaders.hs
index c11886d..296e4a8 100644
--- a/Graphics/Glyph/Shaders.hs
+++ b/Graphics/Glyph/Shaders.hs
@@ -18,26 +18,31 @@ class IsShaderSource a where
loadShader :: ShaderType -> a -> IO (String, Maybe Shader)
instance IsShaderSource FilePath where
- loadShader typ path = loadShader typ =<< BS.readFile path
+ loadShader typ path = loadShaderBS path typ =<< BS.readFile path
instance IsShaderSource BS.ByteString where
- loadShader typ src = do
- shader <- createShader typ
- shaderSourceBS shader $= src
- compileShader shader
-
- ok <- get (compileStatus shader)
- infoLog <- get (shaderInfoLog shader)
-
- unless ok $
- deleteObjectNames [shader]
-
- return ( infoLog, if not ok then Nothing else Just shader );
+ loadShader = loadShaderBS "Inlined"
instance IsShaderSource BSL.ByteString where
loadShader typ = loadShader typ . toStrict
where toStrict = BS.concat . BSL.toChunks
+loadShaderBS :: String -> ShaderType -> BS.ByteString -> IO (String, Maybe Shader)
+loadShaderBS ctx typ src = do
+ shader <- createShader typ
+ shaderSourceBS shader $= src
+ compileShader shader
+
+ ok <- get (compileStatus shader)
+ infoLog <- get (shaderInfoLog shader)
+
+ unless ok $
+ deleteObjectNames [shader]
+
+ if not ok then
+ return ( unlines $ map ((ctx ++ " " ++ show typ ++ ": ")++) $ lines infoLog, Nothing )
+ else return ( infoLog, Just shader );
+
{- Load multiple shaders -}
loadShaders :: (IsShaderSource a) => [(ShaderType,a)] -> IO [(String, Maybe Shader)]
diff --git a/Resources.hs b/Resources.hs
index 532878c..4350d06 100644
--- a/Resources.hs
+++ b/Resources.hs
@@ -18,7 +18,7 @@ import Graphics.SDL.SDLHelp
import Graphics.Glyph.BufferBuilder
import Graphics.Glyph.Mat4
import Graphics.Glyph.Util
-import Graphics.Glyph.ExtendedGL
+import Graphics.Glyph.ExtendedGL as Ex
import Graphics.Rendering.OpenGL as GL
import Graphics.Rendering.OpenGL.Raw.Core31
@@ -195,10 +195,13 @@ displayHandle resources = do
return ()
draw $ prepare (waterObj resources) $ \_ -> do
+ patchVertices $= 3
uniform (UniformLocation 4) $= pMatrix resources
uniform (UniformLocation 5) $= l_mvMatrix
uniform (UniformLocation 7) $= normalMatrix
uniform (UniformLocation 8) $= l_mvMatrix `glslMatMul` lightPos
+ uniform (UniformLocation 9) $= Index1 ((fromIntegral $ time resources) / 20::GLfloat)
+ uniform (UniformLocation 10) $= Vec4 (r,g,b,a::GLfloat)
return ()
SDL.glSwapBuffers
@@ -315,7 +318,9 @@ makeResources surf builder forestB jungleB water = do
(Just ("shaders/water.tcs","shaders/water.tes"))
(Nothing::Maybe String) "shaders/water.vert" "shaders/water.frag"
waterTexture <- load "textures/water.jpg" >>= textureFromSurface
+ skyTexture <- load "textures/skybox_top.png" >>= textureFromSurface
location <- get (uniformLocation waterProg "texture")
+ skyLocation <- get (uniformLocation waterProg "skytex")
Resources
<$> pure surf
<*> do CameraPosition
@@ -331,9 +336,10 @@ makeResources surf builder forestB jungleB water = do
<*> buildTerrainObject builder
<*> buildForestObject forestB "tree.obj" "textures/wood_low.png"
<*> buildForestObject jungleB "jungletree.obj" "textures/jungle_tree.png"
- <*> (newDefaultGlyphObjectWithClosure water () $ \_ -> do
+ <*> (liftM (setPrimitiveMode Ex.Patches) $ newDefaultGlyphObjectWithClosure water () $ \_ -> do
currentProgram $= Just waterProg
setupTexturing waterTexture location 0
+ setupTexturing skyTexture skyLocation 1
)
<*> pure 0
<*> pure 1
diff --git a/shaders/water.frag b/shaders/water.frag
index 82b8163..4a73318 100644
--- a/shaders/water.frag
+++ b/shaders/water.frag
@@ -4,7 +4,11 @@
layout(location = 0) out vec4 frag_color ;
layout(location = 8) uniform vec4 lightPos ;
+layout(location = 9) uniform float time ;
+layout(location = 10) uniform vec4 globalAmbient ;
+
uniform sampler2D texture ;
+ uniform sampler2D skytex ;
in vec3 normal ;
in vec4 position ;
@@ -13,7 +17,7 @@ in vec2 texpos ;
float dX = 1 / 512.0 ;
float dY = 1 / 512.0 ;
vec4 sample(float xc,float yc) {
- return texture2D(texture,texpos + vec2(xc,yc));
+ return texture2D(texture,texpos + vec2(xc,yc) - vec2(time/20.0,time/20.0));
}
vec3 calNormChange( vec3 norm, vec3 down, vec3 right ) {
@@ -35,14 +39,26 @@ vec3 calNormChange( vec3 norm, vec3 down, vec3 right ) {
return (right*2 + down*2 + norm) / 5.0 ;
}
+in vec3 original_x ;
+in vec3 original_z ;
void main() {
-// vec3 down = vec3( 0, -1, 0 ) ;
-// vec3 right = normalize(cross( normal, down )) ;
-// down = normalize(cross( normal, right ) );
-// vec3 newNorm = calNormChange( normal, down, right ) ;
-//
-// float coef = dot( normalize(vec3(lightPos) - vec3(position)), normalize(newNorm) ) ;
-// vec4 color = texture2D(texture,texpos) ;
-// frag_color = vec4(color.xyz * vec3(0.0,0.4,0.7) * coef,0.8);
- frag_color = vec4(0,0,1,0.8) ;
+ vec3 down = vec3( 0, -1, 0 ) ;
+ vec3 right = normalize(cross( normal, down )) ;
+ down = normalize(cross( normal, right ) );
+ vec3 newNorm = calNormChange( normal, down, right ) ;
+
+ vec3 camVector = vec3(position) - vec3(0,0,0);
+ vec3 ref = reflect( normalize(camVector), newNorm ) ;
+
+ float tex_x = (dot( ref, original_x ) + 1) / 2;
+ float tex_y = (dot( ref, original_z ) + 1) / 2;
+ vec4 refcolor = texture2D(skytex, vec2(tex_x,tex_y));
+ float coef = dot( normalize(vec3(lightPos) - vec3(position)), normalize(normal) ) * 0.5 + 0.5 ;
+
+
+ // frag_color = vec4( original_z, 1.0 );
+ // frag_color = vec4(tex_x,tex_y,0,1.0) ;
+ // vec4 color = sample(0,0);
+ frag_color = vec4(vec3(refcolor * coef) * vec3(0.6,0.8,1.0),0.8) * vec4(normalize(globalAmbient.xyz),1.0);
+// frag_color = vec4(0,0,1,0.8) ;
}