module Graphics.VinylGL.Uniforms (setAllUniforms, setSomeUniforms, setUniforms,
HasFieldGLTypes(..), SetUniformFields) where
import Control.Applicative ((<$>))
import Data.Foldable (traverse_)
import qualified Data.Map as M
import Data.Maybe (fromMaybe)
import qualified Data.Set as S
import Data.Vinyl (FieldRec, PlainFieldRec, Rec(..))
import Data.Vinyl.Idiom.Identity
import Data.Vinyl.Reflect (HasFieldNames(..))
import Data.Vinyl.Universe ((:::))
import GHC.TypeLits (Symbol)
import Graphics.GLUtil (HasVariableType(..), ShaderProgram(..), AsUniform(..))
import Graphics.Rendering.OpenGL as GL
class HasFieldGLTypes a where
fieldGLTypes :: a -> [GL.VariableType]
instance HasFieldGLTypes (FieldRec f '[]) where
fieldGLTypes _ = []
instance (HasVariableType t, HasFieldGLTypes (PlainFieldRec ts))
=> HasFieldGLTypes (PlainFieldRec ((sy::Symbol):::t ': ts)) where
fieldGLTypes _ = variableType (undefined::t)
: fieldGLTypes (undefined::PlainFieldRec ts)
type UniformFields a = (HasFieldNames a, HasFieldGLTypes a, SetUniformFields a)
setAllUniforms :: forall ts. UniformFields (PlainFieldRec ts)
=> ShaderProgram -> PlainFieldRec ts -> IO ()
setAllUniforms s x = case checks of
Left msg -> error msg
Right _ -> setUniformFields locs x
where fnames = fieldNames (undefined::PlainFieldRec ts)
checks = do namesCheck "record" (M.keys $ uniforms s) fnames
typesCheck True (snd <$> uniforms s) fieldTypes
fieldTypes = M.fromList $
zip fnames (fieldGLTypes (undefined::PlainFieldRec ts))
locs = map (fmap fst . (`M.lookup` uniforms s)) fnames
setUniforms :: forall ts. UniformFields (PlainFieldRec ts)
=> ShaderProgram -> PlainFieldRec ts -> IO ()
setUniforms s x = case checks of
Left msg -> error msg
Right _ -> setUniformFields locs x
where fnames = fieldNames (undefined::PlainFieldRec ts)
checks = do namesCheck "GLSL program" fnames (M.keys $ uniforms s)
typesCheck False fieldTypes (snd <$> uniforms s)
fieldTypes = M.fromList $
zip fnames (fieldGLTypes (undefined::PlainFieldRec ts))
locs = map (fmap fst . (`M.lookup` uniforms s)) fnames
setSomeUniforms :: forall ts. UniformFields (PlainFieldRec ts)
=> ShaderProgram -> PlainFieldRec ts -> IO ()
setSomeUniforms s x = case typesCheck' True (snd <$> uniforms s) fieldTypes of
Left msg -> error msg
Right _ -> setUniformFields locs x
where fnames = fieldNames (undefined::PlainFieldRec ts)
fieldTypes = M.fromList . zip fnames $
fieldGLTypes (undefined::PlainFieldRec ts)
locs = map (fmap fst . (`M.lookup` uniforms s)) fnames
namesCheck :: String -> [String] -> [String] -> Either String ()
namesCheck blame little big = mapM_ aux little
where big' = S.fromList big
aux x | x `S.member` big' = Right ()
| otherwise = Left $ "Field "++x++" not found in "++blame
typesCheck :: Bool
-> M.Map String GL.VariableType -> M.Map String GL.VariableType
-> Either String ()
typesCheck blame little big = mapM_ aux $ M.toList little
where aux (n,t)
| Just True == (glTypeEquiv t <$> M.lookup n big) = return ()
| otherwise = Left $ msg n (show t) (maybe "" show (M.lookup n big))
msg n t t' = let (expected, actual) = if blame
then (t,t')
else (t',t)
in "Record and GLSL type disagreement on field "++n++
": GLSL expected "++expected++
", record provides "++actual
typesCheck' :: Bool
-> M.Map String GL.VariableType -> M.Map String GL.VariableType
-> Either String ()
typesCheck' blame little big = mapM_ aux $ M.toList little
where aux (n,t)
| fromMaybe True (glTypeEquiv t <$> M.lookup n big) = return ()
| otherwise = Left $ msg n (show t) (maybe "" show (M.lookup n big))
msg n t t' = let (expected, actual) = if blame
then (t,t')
else (t',t)
in "Record and GLSL type disagreement on field "++n++
": GLSL expected "++expected++
", record provides "++actual
glTypeEquiv' :: GL.VariableType -> GL.VariableType -> Bool
glTypeEquiv' GL.Sampler1D GL.Int' = True
glTypeEquiv' GL.Sampler2D GL.Int' = True
glTypeEquiv' GL.Sampler3D GL.Int' = True
glTypeEquiv' x y = x == y
glTypeEquiv :: VariableType -> VariableType -> Bool
glTypeEquiv x y = glTypeEquiv' x y || glTypeEquiv' y x
class SetUniformFields a where
setUniformFields :: [Maybe UniformLocation] -> a -> IO ()
instance SetUniformFields (FieldRec f '[]) where
setUniformFields _ _ = return ()
instance (AsUniform t, SetUniformFields (PlainFieldRec ts))
=> SetUniformFields (PlainFieldRec (((sy::Symbol):::t) ': ts)) where
setUniformFields [] _ = error "Ran out of UniformLocations"
setUniformFields (loc:locs) (Identity x :& xs) =
do traverse_ (asUniform x) loc
setUniformFields locs xs