{-# LANGUAGE Arrows #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-# OPTIONS_GHC -Wno-unused-foralls #-}
{-# OPTIONS_GHC -Wno-incomplete-patterns #-}
{-# OPTIONS_GHC -Wno-unused-matches #-}
{-# OPTIONS_GHC -Wno-missing-signatures #-}
{-# OPTIONS_GHC -Wno-type-defaults #-}
module Graphics.GPipe.Internal.PrimitiveStream where
#if __GLASGOW_HASKELL__ < 804
import Data.Semigroup (Semigroup (..))
#endif
import Control.Arrow (Arrow (arr, first),
Kleisli (Kleisli),
returnA)
import Control.Category (Category (..))
import Control.Monad (void, when)
import Control.Monad.Trans.Class (MonadTrans (lift))
import Control.Monad.Trans.Reader (Reader, ask, runReader)
import Control.Monad.Trans.State.Strict (State,
StateT (runStateT),
execState, get, modify,
put)
import Data.IORef (readIORef)
import Data.Int (Int16, Int32, Int8)
import qualified Data.IntMap.Polymorphic as Map
import Data.IntMap.Polymorphic.Lazy (insert)
import Data.Maybe (fromMaybe)
import Data.Text.Lazy (Text)
import Data.Word (Word16, Word32, Word8)
import Foreign.Marshal (alloca)
import Foreign.Marshal.Utils (fromBool)
import Foreign.Ptr (Ptr, castPtr,
intPtrToPtr, plusPtr)
import Foreign.Storable (Storable (peek, poke, sizeOf))
import Graphics.GL.Core45
import Graphics.GL.Types (GLuint)
import Graphics.GPipe.Internal.Buffer (B (..), B2 (..),
B3 (..), B4 (..),
Buffer (bufTransformFeedback),
BufferFormat (HostFormat),
Normalized (..))
import Graphics.GPipe.Internal.Compiler (Binding,
RenderIOState (inputArrayToRenderIO))
import Graphics.GPipe.Internal.Context (VAOKey (VAOKey))
import Graphics.GPipe.Internal.Expr (ExprM, S (S),
SType (..), V, VFloat,
VInt, VWord, scalarS',
useUniform, useVInput,
vec2S, vec3S, vec4S)
import Graphics.GPipe.Internal.PrimitiveArray (IndexArray (iArrName, indexArrayLength, indexType, offset, restart),
Points,
PrimitiveArray (getPrimitiveArray),
PrimitiveArrayInt (..),
PrimitiveTopology (toGLtopology, toPrimitiveSize))
import Graphics.GPipe.Internal.Shader (Shader (..), ShaderM,
askUniformAlignment,
getNewName,
modifyRenderIO)
import Graphics.GPipe.Internal.Uniform (OffsetToSType,
buildUDecl)
import Linear.Affine (Point (..))
import Linear.Plucker (Plucker (..))
import Linear.Quaternion (Quaternion (..))
import Linear.V0 (V0 (..))
import Linear.V1 (V1 (..))
import Linear.V2 (V2 (..))
import Linear.V3 (V3 (..))
import Linear.V4 (V4 (..))
import Prelude hiding (id, length, (.))
type PrimitiveName = Int
type USize = Int
data PrimitiveStreamData = PrimitiveStreamData PrimitiveName USize
newtype PrimitiveStream t a = PrimitiveStream [(a, (Maybe PointSize, PrimitiveStreamData))] deriving (b -> PrimitiveStream t a -> PrimitiveStream t a
NonEmpty (PrimitiveStream t a) -> PrimitiveStream t a
PrimitiveStream t a -> PrimitiveStream t a -> PrimitiveStream t a
(PrimitiveStream t a -> PrimitiveStream t a -> PrimitiveStream t a)
-> (NonEmpty (PrimitiveStream t a) -> PrimitiveStream t a)
-> (forall b.
Integral b =>
b -> PrimitiveStream t a -> PrimitiveStream t a)
-> Semigroup (PrimitiveStream t a)
forall b.
Integral b =>
b -> PrimitiveStream t a -> PrimitiveStream t a
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
forall t a. NonEmpty (PrimitiveStream t a) -> PrimitiveStream t a
forall t a.
PrimitiveStream t a -> PrimitiveStream t a -> PrimitiveStream t a
forall t a b.
Integral b =>
b -> PrimitiveStream t a -> PrimitiveStream t a
stimes :: b -> PrimitiveStream t a -> PrimitiveStream t a
$cstimes :: forall t a b.
Integral b =>
b -> PrimitiveStream t a -> PrimitiveStream t a
sconcat :: NonEmpty (PrimitiveStream t a) -> PrimitiveStream t a
$csconcat :: forall t a. NonEmpty (PrimitiveStream t a) -> PrimitiveStream t a
<> :: PrimitiveStream t a -> PrimitiveStream t a -> PrimitiveStream t a
$c<> :: forall t a.
PrimitiveStream t a -> PrimitiveStream t a -> PrimitiveStream t a
Semigroup, Semigroup (PrimitiveStream t a)
PrimitiveStream t a
Semigroup (PrimitiveStream t a)
-> PrimitiveStream t a
-> (PrimitiveStream t a
-> PrimitiveStream t a -> PrimitiveStream t a)
-> ([PrimitiveStream t a] -> PrimitiveStream t a)
-> Monoid (PrimitiveStream t a)
[PrimitiveStream t a] -> PrimitiveStream t a
PrimitiveStream t a -> PrimitiveStream t a -> PrimitiveStream t a
forall a.
Semigroup a -> a -> (a -> a -> a) -> ([a] -> a) -> Monoid a
forall t a. Semigroup (PrimitiveStream t a)
forall t a. PrimitiveStream t a
forall t a. [PrimitiveStream t a] -> PrimitiveStream t a
forall t a.
PrimitiveStream t a -> PrimitiveStream t a -> PrimitiveStream t a
mconcat :: [PrimitiveStream t a] -> PrimitiveStream t a
$cmconcat :: forall t a. [PrimitiveStream t a] -> PrimitiveStream t a
mappend :: PrimitiveStream t a -> PrimitiveStream t a -> PrimitiveStream t a
$cmappend :: forall t a.
PrimitiveStream t a -> PrimitiveStream t a -> PrimitiveStream t a
mempty :: PrimitiveStream t a
$cmempty :: forall t a. PrimitiveStream t a
$cp1Monoid :: forall t a. Semigroup (PrimitiveStream t a)
Monoid)
instance Functor (PrimitiveStream t) where
fmap :: (a -> b) -> PrimitiveStream t a -> PrimitiveStream t b
fmap a -> b
f (PrimitiveStream [(a, (Maybe PointSize, PrimitiveStreamData))]
xs) = [(b, (Maybe PointSize, PrimitiveStreamData))]
-> PrimitiveStream t b
forall t a.
[(a, (Maybe PointSize, PrimitiveStreamData))]
-> PrimitiveStream t a
PrimitiveStream ([(b, (Maybe PointSize, PrimitiveStreamData))]
-> PrimitiveStream t b)
-> [(b, (Maybe PointSize, PrimitiveStreamData))]
-> PrimitiveStream t b
forall a b. (a -> b) -> a -> b
$ ((a, (Maybe PointSize, PrimitiveStreamData))
-> (b, (Maybe PointSize, PrimitiveStreamData)))
-> [(a, (Maybe PointSize, PrimitiveStreamData))]
-> [(b, (Maybe PointSize, PrimitiveStreamData))]
forall a b. (a -> b) -> [a] -> [b]
map ((a -> b)
-> (a, (Maybe PointSize, PrimitiveStreamData))
-> (b, (Maybe PointSize, PrimitiveStreamData))
forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (b, d) (c, d)
first a -> b
f) [(a, (Maybe PointSize, PrimitiveStreamData))]
xs
class VertexInput a where
type VertexFormat a
toVertex :: ToVertex a (VertexFormat a)
type UniOffset = Int
data ToVertex a b = ToVertex
!( Kleisli
( StateT (Ptr ()) IO
) a b)
!( Kleisli
( StateT
( Int
, UniOffset
, OffsetToSType
)
( Reader
( Int -> ExprM Text
)
)
) a b)
!( Kleisli
( State
[ Binding -> (IO VAOKey, IO ())
]
) a b)
instance Category ToVertex where
{-# INLINE id #-}
id :: ToVertex a a
id = Kleisli (StateT (Ptr ()) IO) a a
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text))) a a
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) a a
-> ToVertex a a
forall a b.
Kleisli (StateT (Ptr ()) IO) a b
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text))) a b
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) a b
-> ToVertex a b
ToVertex Kleisli (StateT (Ptr ()) IO) a a
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text))) a a
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id Kleisli (State [Int -> (IO VAOKey, IO ())]) a a
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
{-# INLINE (.) #-}
ToVertex Kleisli (StateT (Ptr ()) IO) b c
a Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text))) b c
b Kleisli (State [Int -> (IO VAOKey, IO ())]) b c
c . :: ToVertex b c -> ToVertex a b -> ToVertex a c
. ToVertex Kleisli (StateT (Ptr ()) IO) a b
x Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text))) a b
y Kleisli (State [Int -> (IO VAOKey, IO ())]) a b
z = Kleisli (StateT (Ptr ()) IO) a c
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text))) a c
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) a c
-> ToVertex a c
forall a b.
Kleisli (StateT (Ptr ()) IO) a b
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text))) a b
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) a b
-> ToVertex a b
ToVertex (Kleisli (StateT (Ptr ()) IO) b c
aKleisli (StateT (Ptr ()) IO) b c
-> Kleisli (StateT (Ptr ()) IO) a b
-> Kleisli (StateT (Ptr ()) IO) a c
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
.Kleisli (StateT (Ptr ()) IO) a b
x) (Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text))) b c
bKleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text))) b c
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text))) a b
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text))) a c
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
.Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text))) a b
y) (Kleisli (State [Int -> (IO VAOKey, IO ())]) b c
cKleisli (State [Int -> (IO VAOKey, IO ())]) b c
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) a b
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) a c
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
.Kleisli (State [Int -> (IO VAOKey, IO ())]) a b
z)
instance Arrow ToVertex where
{-# INLINE arr #-}
arr :: (b -> c) -> ToVertex b c
arr b -> c
f = Kleisli (StateT (Ptr ()) IO) b c
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text))) b c
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) b c
-> ToVertex b c
forall a b.
Kleisli (StateT (Ptr ()) IO) a b
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text))) a b
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) a b
-> ToVertex a b
ToVertex ((b -> c) -> Kleisli (StateT (Ptr ()) IO) b c
forall (a :: * -> * -> *) b c. Arrow a => (b -> c) -> a b c
arr b -> c
f) ((b -> c)
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text))) b c
forall (a :: * -> * -> *) b c. Arrow a => (b -> c) -> a b c
arr b -> c
f) ((b -> c) -> Kleisli (State [Int -> (IO VAOKey, IO ())]) b c
forall (a :: * -> * -> *) b c. Arrow a => (b -> c) -> a b c
arr b -> c
f)
{-# INLINE first #-}
first :: ToVertex b c -> ToVertex (b, d) (c, d)
first (ToVertex Kleisli (StateT (Ptr ()) IO) b c
a Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text))) b c
b Kleisli (State [Int -> (IO VAOKey, IO ())]) b c
c) = Kleisli (StateT (Ptr ()) IO) (b, d) (c, d)
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(b, d)
(c, d)
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) (b, d) (c, d)
-> ToVertex (b, d) (c, d)
forall a b.
Kleisli (StateT (Ptr ()) IO) a b
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text))) a b
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) a b
-> ToVertex a b
ToVertex (Kleisli (StateT (Ptr ()) IO) b c
-> Kleisli (StateT (Ptr ()) IO) (b, d) (c, d)
forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (b, d) (c, d)
first Kleisli (StateT (Ptr ()) IO) b c
a) (Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text))) b c
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(b, d)
(c, d)
forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (b, d) (c, d)
first Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text))) b c
b) (Kleisli (State [Int -> (IO VAOKey, IO ())]) b c
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) (b, d) (c, d)
forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (b, d) (c, d)
first Kleisli (State [Int -> (IO VAOKey, IO ())]) b c
c)
toPrimitiveStream :: forall os f s a p. (PrimitiveTopology p, VertexInput a) => (s -> PrimitiveArray p a) -> Shader os s (PrimitiveStream p (VertexFormat a))
toPrimitiveStream :: (s -> PrimitiveArray p a)
-> Shader os s (PrimitiveStream p (VertexFormat a))
toPrimitiveStream = Maybe (s -> Buffer os Any)
-> (s -> PrimitiveArray p a)
-> Shader os s (PrimitiveStream p (VertexFormat a))
forall os f s a b p.
(PrimitiveTopology p, VertexInput a) =>
Maybe (s -> Buffer os b)
-> (s -> PrimitiveArray p a)
-> Shader os s (PrimitiveStream p (VertexFormat a))
toPrimitiveStream' Maybe (s -> Buffer os Any)
forall a. Maybe a
Nothing
toPrimitiveStream' :: forall os f s a b p. (PrimitiveTopology p, VertexInput a) => Maybe (s -> Buffer os b) -> (s -> PrimitiveArray p a) -> Shader os s (PrimitiveStream p (VertexFormat a))
toPrimitiveStream' :: Maybe (s -> Buffer os b)
-> (s -> PrimitiveArray p a)
-> Shader os s (PrimitiveStream p (VertexFormat a))
toPrimitiveStream' Maybe (s -> Buffer os b)
getFeedbackBuffer s -> PrimitiveArray p a
sf = ShaderM s (PrimitiveStream p (VertexFormat a))
-> Shader os s (PrimitiveStream p (VertexFormat a))
forall os s a. ShaderM s a -> Shader os s a
Shader (ShaderM s (PrimitiveStream p (VertexFormat a))
-> Shader os s (PrimitiveStream p (VertexFormat a)))
-> ShaderM s (PrimitiveStream p (VertexFormat a))
-> Shader os s (PrimitiveStream p (VertexFormat a))
forall a b. (a -> b) -> a -> b
$ do
Int
n <- ShaderM s Int
forall s. ShaderM s Int
getNewName
Int
uniAl <- ShaderM s Int
forall s. ShaderM s Int
askUniformAlignment
let
err :: a
err = [Char] -> a
forall a. HasCallStack => [Char] -> a
error [Char]
"toPrimitiveStream is creating values that are dependant on the actual HostFormat values, this is not allowed since it doesn't allow static creation of shaders"
(VertexFormat a
x, (Int
_, Int
uSize, OffsetToSType
offToStype)) = Reader
(Int -> ExprM Text) (VertexFormat a, (Int, Int, OffsetToSType))
-> (Int -> ExprM Text)
-> (VertexFormat a, (Int, Int, OffsetToSType))
forall r a. Reader r a -> r -> a
runReader
(StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(VertexFormat a)
-> (Int, Int, OffsetToSType)
-> Reader
(Int -> ExprM Text) (VertexFormat a, (Int, Int, OffsetToSType))
forall s (m :: * -> *) a. StateT s m a -> s -> m (a, s)
runStateT (a
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(VertexFormat a)
makeV a
forall a. a
err) (Int
0, Int
0, OffsetToSType
forall a. Monoid a => a
mempty))
(GlobDeclM () -> UniformId -> Int -> ExprM Text
useUniform (OffsetToSType -> GlobDeclM ()
buildUDecl OffsetToSType
offToStype) UniformId
0)
Int
-> (s -> [([Int], GLuint, Int) -> ((IO [VAOKey], IO ()), IO ())])
-> ShaderM s ()
doForInputArray Int
n ((s -> [([Int], GLuint, Int) -> ((IO [VAOKey], IO ()), IO ())])
-> ShaderM s ())
-> (s -> [([Int], GLuint, Int) -> ((IO [VAOKey], IO ()), IO ())])
-> ShaderM s ()
forall a b. (a -> b) -> a -> b
$ \s
s ->
let
fb :: Maybe (Buffer os b)
fb = Maybe (s -> Buffer os b)
getFeedbackBuffer Maybe (s -> Buffer os b)
-> ((s -> Buffer os b) -> Maybe (Buffer os b))
-> Maybe (Buffer os b)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \s -> Buffer os b
g -> Buffer os b -> Maybe (Buffer os b)
forall (m :: * -> *) a. Monad m => a -> m a
return (s -> Buffer os b
g s
s)
ps :: [PrimitiveArrayInt p a]
ps = PrimitiveArray p a -> [PrimitiveArrayInt p a]
forall p a. PrimitiveArray p a -> [PrimitiveArrayInt p a]
getPrimitiveArray (s -> PrimitiveArray p a
sf s
s)
in
(PrimitiveArrayInt p a
-> ([Int], GLuint, Int) -> ((IO [VAOKey], IO ()), IO ()))
-> [PrimitiveArrayInt p a]
-> [([Int], GLuint, Int) -> ((IO [VAOKey], IO ()), IO ())]
forall a b. (a -> b) -> [a] -> [b]
map ((Maybe (Buffer os b), PrimitiveArrayInt p a)
-> ([Int], GLuint, Int) -> ((IO [VAOKey], IO ()), IO ())
drawcall ((Maybe (Buffer os b), PrimitiveArrayInt p a)
-> ([Int], GLuint, Int) -> ((IO [VAOKey], IO ()), IO ()))
-> (PrimitiveArrayInt p a
-> (Maybe (Buffer os b), PrimitiveArrayInt p a))
-> PrimitiveArrayInt p a
-> ([Int], GLuint, Int)
-> ((IO [VAOKey], IO ()), IO ())
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (Maybe (Buffer os b)
fb,)) [PrimitiveArrayInt p a]
ps
PrimitiveStream p (VertexFormat a)
-> ShaderM s (PrimitiveStream p (VertexFormat a))
forall (m :: * -> *) a. Monad m => a -> m a
return (PrimitiveStream p (VertexFormat a)
-> ShaderM s (PrimitiveStream p (VertexFormat a)))
-> PrimitiveStream p (VertexFormat a)
-> ShaderM s (PrimitiveStream p (VertexFormat a))
forall a b. (a -> b) -> a -> b
$ [(VertexFormat a, (Maybe PointSize, PrimitiveStreamData))]
-> PrimitiveStream p (VertexFormat a)
forall t a.
[(a, (Maybe PointSize, PrimitiveStreamData))]
-> PrimitiveStream t a
PrimitiveStream [(VertexFormat a
x, (Maybe PointSize
forall a. Maybe a
Nothing, Int -> Int -> PrimitiveStreamData
PrimitiveStreamData Int
n Int
uSize))]
where
ToVertex
(Kleisli a -> StateT (Ptr ()) IO (VertexFormat a)
uWriter)
(Kleisli a
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(VertexFormat a)
makeV)
(Kleisli a -> State [Int -> (IO VAOKey, IO ())] (VertexFormat a)
makeBind)
= ToVertex a (VertexFormat a)
forall a. VertexInput a => ToVertex a (VertexFormat a)
toVertex :: ToVertex a (VertexFormat a)
drawcall :: (Maybe (Buffer os b), PrimitiveArrayInt p a)
-> ([Int], GLuint, Int) -> ((IO [VAOKey], IO ()), IO ())
drawcall (Just Buffer os b
feedbackBuffer, PrimitiveArraySimple p
p Int
l Int
s a
a) ([Int], GLuint, Int)
binds = (a -> ([Int], GLuint, Int) -> (IO [VAOKey], IO ())
attribs a
a ([Int], GLuint, Int)
binds, do
Just (GLuint
tfName, GLuint
tfqName) <- IORef (Maybe (GLuint, GLuint)) -> IO (Maybe (GLuint, GLuint))
forall a. IORef a -> IO a
readIORef (Buffer os b -> IORef (Maybe (GLuint, GLuint))
forall os b. Buffer os b -> IORef (Maybe (GLuint, GLuint))
bufTransformFeedback Buffer os b
feedbackBuffer)
if Bool
False
then GLuint -> GLuint -> IO ()
forall (m :: * -> *). MonadIO m => GLuint -> GLuint -> m ()
glDrawTransformFeedback (p -> GLuint
forall p. PrimitiveTopology p => p -> GLuint
toGLtopology p
p) GLuint
tfName
else do
GLint
l' <- (Int -> GLint
forall a b. (Integral a, Num b) => a -> b
fromIntegral (p -> Int
forall p. PrimitiveTopology p => p -> Int
toPrimitiveSize p
p) GLint -> GLint -> GLint
forall a. Num a => a -> a -> a
*) (GLint -> GLint) -> IO GLint -> IO GLint
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Ptr GLint -> IO GLint) -> IO GLint
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca (\Ptr GLint
ptr -> do
GLuint -> GLuint -> Ptr GLint -> IO ()
forall (m :: * -> *).
MonadIO m =>
GLuint -> GLuint -> Ptr GLint -> m ()
glGetQueryObjectiv GLuint
tfqName GLuint
forall a. (Eq a, Num a) => a
GL_QUERY_RESULT Ptr GLint
ptr
Ptr GLint -> IO GLint
forall a. Storable a => Ptr a -> IO a
peek Ptr GLint
ptr)
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (GLint
l' GLint -> GLint -> Bool
forall a. Ord a => a -> a -> Bool
> GLint
0) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
GLuint -> GLint -> GLint -> IO ()
forall (m :: * -> *). MonadIO m => GLuint -> GLint -> GLint -> m ()
glDrawArrays (p -> GLuint
forall p. PrimitiveTopology p => p -> GLuint
toGLtopology p
p) (Int -> GLint
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
s) GLint
l'
)
drawcall (Just Buffer os b
feedbackBuffer, PrimitiveArrayInstanced p
p Int
il Int
l Int
s a
a) ([Int], GLuint, Int)
binds = (a -> ([Int], GLuint, Int) -> (IO [VAOKey], IO ())
attribs a
a ([Int], GLuint, Int)
binds, do
Just (GLuint
tfName, GLuint
_) <- IORef (Maybe (GLuint, GLuint)) -> IO (Maybe (GLuint, GLuint))
forall a. IORef a -> IO a
readIORef (Buffer os b -> IORef (Maybe (GLuint, GLuint))
forall os b. Buffer os b -> IORef (Maybe (GLuint, GLuint))
bufTransformFeedback Buffer os b
feedbackBuffer)
GLuint -> GLuint -> GLint -> IO ()
forall (m :: * -> *).
MonadIO m =>
GLuint -> GLuint -> GLint -> m ()
glDrawTransformFeedbackInstanced (p -> GLuint
forall p. PrimitiveTopology p => p -> GLuint
toGLtopology p
p) GLuint
tfName (Int -> GLint
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
il))
drawcall (Maybe (Buffer os b)
Nothing, PrimitiveArraySimple p
p Int
l Int
s a
a) ([Int], GLuint, Int)
binds = (a -> ([Int], GLuint, Int) -> (IO [VAOKey], IO ())
attribs a
a ([Int], GLuint, Int)
binds, do
GLuint -> GLint -> GLint -> IO ()
forall (m :: * -> *). MonadIO m => GLuint -> GLint -> GLint -> m ()
glDrawArrays (p -> GLuint
forall p. PrimitiveTopology p => p -> GLuint
toGLtopology p
p) (Int -> GLint
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
s) (Int -> GLint
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
l))
drawcall (Maybe (Buffer os b)
Nothing, PrimitiveArrayIndexed p
p IndexArray
i Int
s a
a) ([Int], GLuint, Int)
binds = (a -> ([Int], GLuint, Int) -> (IO [VAOKey], IO ())
attribs a
a ([Int], GLuint, Int)
binds, do
IndexArray -> IO ()
bindIndexBuffer IndexArray
i
GLuint -> GLint -> GLuint -> Ptr () -> GLint -> IO ()
forall (m :: * -> *).
MonadIO m =>
GLuint -> GLint -> GLuint -> Ptr () -> GLint -> m ()
glDrawElementsBaseVertex (p -> GLuint
forall p. PrimitiveTopology p => p -> GLuint
toGLtopology p
p) (Int -> GLint
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> GLint) -> Int -> GLint
forall a b. (a -> b) -> a -> b
$ IndexArray -> Int
indexArrayLength IndexArray
i) (IndexArray -> GLuint
indexType IndexArray
i) (IntPtr -> Ptr ()
forall a. IntPtr -> Ptr a
intPtrToPtr (IntPtr -> Ptr ()) -> IntPtr -> Ptr ()
forall a b. (a -> b) -> a -> b
$ Int -> IntPtr
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> IntPtr) -> Int -> IntPtr
forall a b. (a -> b) -> a -> b
$ IndexArray -> Int
offset IndexArray
i Int -> Int -> Int
forall a. Num a => a -> a -> a
* GLuint -> Int
forall a p. (Eq a, Num a, Num p) => a -> p
glSizeOf (IndexArray -> GLuint
indexType IndexArray
i)) (Int -> GLint
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
s))
drawcall (Maybe (Buffer os b)
Nothing, PrimitiveArrayInstanced p
p Int
il Int
l Int
s a
a) ([Int], GLuint, Int)
binds = (a -> ([Int], GLuint, Int) -> (IO [VAOKey], IO ())
attribs a
a ([Int], GLuint, Int)
binds, do
GLuint -> GLint -> GLint -> GLint -> IO ()
forall (m :: * -> *).
MonadIO m =>
GLuint -> GLint -> GLint -> GLint -> m ()
glDrawArraysInstanced (p -> GLuint
forall p. PrimitiveTopology p => p -> GLuint
toGLtopology p
p) (Int -> GLint
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
s) (Int -> GLint
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
l) (Int -> GLint
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
il))
drawcall (Maybe (Buffer os b)
Nothing, PrimitiveArrayIndexedInstanced p
p IndexArray
i Int
il Int
s a
a) ([Int], GLuint, Int)
binds = (a -> ([Int], GLuint, Int) -> (IO [VAOKey], IO ())
attribs a
a ([Int], GLuint, Int)
binds, do
IndexArray -> IO ()
bindIndexBuffer IndexArray
i
GLuint -> GLint -> GLuint -> Ptr () -> GLint -> GLint -> IO ()
forall (m :: * -> *).
MonadIO m =>
GLuint -> GLint -> GLuint -> Ptr () -> GLint -> GLint -> m ()
glDrawElementsInstancedBaseVertex (p -> GLuint
forall p. PrimitiveTopology p => p -> GLuint
toGLtopology p
p) (Int -> GLint
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> GLint) -> Int -> GLint
forall a b. (a -> b) -> a -> b
$ IndexArray -> Int
indexArrayLength IndexArray
i) (IndexArray -> GLuint
indexType IndexArray
i) (IntPtr -> Ptr ()
forall a. IntPtr -> Ptr a
intPtrToPtr (IntPtr -> Ptr ()) -> IntPtr -> Ptr ()
forall a b. (a -> b) -> a -> b
$ Int -> IntPtr
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> IntPtr) -> Int -> IntPtr
forall a b. (a -> b) -> a -> b
$ IndexArray -> Int
offset IndexArray
i Int -> Int -> Int
forall a. Num a => a -> a -> a
* GLuint -> Int
forall a p. (Eq a, Num a, Num p) => a -> p
glSizeOf (IndexArray -> GLuint
indexType IndexArray
i)) (Int -> GLint
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
il) (Int -> GLint
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
s))
bindIndexBuffer :: IndexArray -> IO ()
bindIndexBuffer IndexArray
i = do
case IndexArray -> Maybe Int
restart IndexArray
i of
Just Int
x -> do
GLuint -> IO ()
forall (m :: * -> *). MonadIO m => GLuint -> m ()
glEnable GLuint
forall a. (Eq a, Num a) => a
GL_PRIMITIVE_RESTART
GLuint -> IO ()
forall (m :: * -> *). MonadIO m => GLuint -> m ()
glPrimitiveRestartIndex (Int -> GLuint
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
x)
Maybe Int
Nothing ->
GLuint -> IO ()
forall (m :: * -> *). MonadIO m => GLuint -> m ()
glDisable GLuint
forall a. (Eq a, Num a) => a
GL_PRIMITIVE_RESTART
GLuint
bname <- IORef GLuint -> IO GLuint
forall a. IORef a -> IO a
readIORef (IndexArray -> IORef GLuint
iArrName IndexArray
i)
GLuint -> GLuint -> IO ()
forall (m :: * -> *). MonadIO m => GLuint -> GLuint -> m ()
glBindBuffer GLuint
forall a. (Eq a, Num a) => a
GL_ELEMENT_ARRAY_BUFFER GLuint
bname
glSizeOf :: a -> p
glSizeOf a
GL_UNSIGNED_INT = p
4
glSizeOf a
GL_UNSIGNED_SHORT = p
2
glSizeOf a
GL_UNSIGNED_BYTE = p
1
glSizeOf a
_ = [Char] -> p
forall a. HasCallStack => [Char] -> a
error [Char]
"toPrimitiveStream: Unknown indexArray type"
assignIxs :: Int -> Binding -> [Int] -> [Binding -> (IO VAOKey, IO ())] -> [(IO VAOKey, IO ())]
assignIxs :: Int
-> Int
-> [Int]
-> [Int -> (IO VAOKey, IO ())]
-> [(IO VAOKey, IO ())]
assignIxs Int
n Int
ix xxs :: [Int]
xxs@(Int
x:[Int]
xs) (Int -> (IO VAOKey, IO ())
f:[Int -> (IO VAOKey, IO ())]
fs) | Int
x Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
n = Int -> (IO VAOKey, IO ())
f Int
ix (IO VAOKey, IO ()) -> [(IO VAOKey, IO ())] -> [(IO VAOKey, IO ())]
forall a. a -> [a] -> [a]
: Int
-> Int
-> [Int]
-> [Int -> (IO VAOKey, IO ())]
-> [(IO VAOKey, IO ())]
assignIxs (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) (Int
ixInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) [Int]
xs [Int -> (IO VAOKey, IO ())]
fs
| Bool
otherwise = Int
-> Int
-> [Int]
-> [Int -> (IO VAOKey, IO ())]
-> [(IO VAOKey, IO ())]
assignIxs (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) Int
ix [Int]
xxs [Int -> (IO VAOKey, IO ())]
fs
assignIxs Int
_ Int
_ [] [Int -> (IO VAOKey, IO ())]
_ = []
assignIxs Int
_ Int
_ [Int]
_ [Int -> (IO VAOKey, IO ())]
_ = [Char] -> [(IO VAOKey, IO ())]
forall a. HasCallStack => [Char] -> a
error [Char]
"Too few attributes generated in toPrimitiveStream"
attribs :: a -> ([Int], GLuint, Int) -> (IO [VAOKey], IO ())
attribs a
a ([Int]
binds, GLuint
uBname, Int
uSize) = let
bindsAssoc :: [Int -> (IO VAOKey, IO ())]
bindsAssoc = State [Int -> (IO VAOKey, IO ())] (VertexFormat a)
-> [Int -> (IO VAOKey, IO ())] -> [Int -> (IO VAOKey, IO ())]
forall s a. State s a -> s -> s
execState (a -> State [Int -> (IO VAOKey, IO ())] (VertexFormat a)
makeBind a
a) []
([IO VAOKey]
ioVaokeys, [IO ()]
ios) = [(IO VAOKey, IO ())] -> ([IO VAOKey], [IO ()])
forall a b. [(a, b)] -> ([a], [b])
unzip ([(IO VAOKey, IO ())] -> ([IO VAOKey], [IO ()]))
-> [(IO VAOKey, IO ())] -> ([IO VAOKey], [IO ()])
forall a b. (a -> b) -> a -> b
$ Int
-> Int
-> [Int]
-> [Int -> (IO VAOKey, IO ())]
-> [(IO VAOKey, IO ())]
assignIxs Int
0 Int
0 [Int]
binds ([Int -> (IO VAOKey, IO ())] -> [(IO VAOKey, IO ())])
-> [Int -> (IO VAOKey, IO ())] -> [(IO VAOKey, IO ())]
forall a b. (a -> b) -> a -> b
$ [Int -> (IO VAOKey, IO ())] -> [Int -> (IO VAOKey, IO ())]
forall a. [a] -> [a]
reverse [Int -> (IO VAOKey, IO ())]
bindsAssoc
in (GLuint -> Int -> a -> IO ()
writeUBuffer GLuint
uBname Int
uSize a
a IO () -> IO [VAOKey] -> IO [VAOKey]
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> [IO VAOKey] -> IO [VAOKey]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence [IO VAOKey]
ioVaokeys, [IO ()] -> IO ()
forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, Monad m) =>
t (m a) -> m ()
sequence_ [IO ()]
ios)
doForInputArray :: Int -> (s -> [([Binding], GLuint, Int) -> ((IO [VAOKey], IO ()), IO ())]) -> ShaderM s ()
doForInputArray :: Int
-> (s -> [([Int], GLuint, Int) -> ((IO [VAOKey], IO ()), IO ())])
-> ShaderM s ()
doForInputArray Int
n s -> [([Int], GLuint, Int) -> ((IO [VAOKey], IO ()), IO ())]
io = (RenderIOState s -> RenderIOState s) -> ShaderM s ()
forall s. (RenderIOState s -> RenderIOState s) -> ShaderM s ()
modifyRenderIO (\RenderIOState s
s -> RenderIOState s
s { inputArrayToRenderIO :: IntMap
Int (s -> [([Int], GLuint, Int) -> ((IO [VAOKey], IO ()), IO ())])
inputArrayToRenderIO = Int
-> (s -> [([Int], GLuint, Int) -> ((IO [VAOKey], IO ()), IO ())])
-> IntMap
Int (s -> [([Int], GLuint, Int) -> ((IO [VAOKey], IO ()), IO ())])
-> IntMap
Int (s -> [([Int], GLuint, Int) -> ((IO [VAOKey], IO ()), IO ())])
forall k v. Integral k => k -> v -> IntMap k v -> IntMap k v
insert Int
n s -> [([Int], GLuint, Int) -> ((IO [VAOKey], IO ()), IO ())]
io (RenderIOState s
-> IntMap
Int (s -> [([Int], GLuint, Int) -> ((IO [VAOKey], IO ()), IO ())])
forall s.
RenderIOState s
-> IntMap
Int (s -> [([Int], GLuint, Int) -> ((IO [VAOKey], IO ()), IO ())])
inputArrayToRenderIO RenderIOState s
s) } )
writeUBuffer :: GLuint -> Int -> a -> IO ()
writeUBuffer GLuint
_ Int
0 a
_ = () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
writeUBuffer GLuint
bname Int
size a
a = do
Any
_ <- [Char] -> IO Any
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail [Char]
"Cannot happen!"
GLuint -> GLuint -> IO ()
forall (m :: * -> *). MonadIO m => GLuint -> GLuint -> m ()
glBindBuffer GLuint
forall a. (Eq a, Num a) => a
GL_COPY_WRITE_BUFFER GLuint
bname
Ptr ()
ptr <- GLuint -> GLintptr -> GLintptr -> GLuint -> IO (Ptr ())
forall (m :: * -> *).
MonadIO m =>
GLuint -> GLintptr -> GLintptr -> GLuint -> m (Ptr ())
glMapBufferRange GLuint
forall a. (Eq a, Num a) => a
GL_COPY_WRITE_BUFFER GLintptr
0 (Int -> GLintptr
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
size) (GLuint
forall a. (Eq a, Num a) => a
GL_MAP_WRITE_BIT GLuint -> GLuint -> GLuint
forall a. Num a => a -> a -> a
+ GLuint
forall a. (Eq a, Num a) => a
GL_MAP_INVALIDATE_BUFFER_BIT)
IO (VertexFormat a, Ptr ()) -> IO ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (IO (VertexFormat a, Ptr ()) -> IO ())
-> IO (VertexFormat a, Ptr ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ StateT (Ptr ()) IO (VertexFormat a)
-> Ptr () -> IO (VertexFormat a, Ptr ())
forall s (m :: * -> *) a. StateT s m a -> s -> m (a, s)
runStateT (a -> StateT (Ptr ()) IO (VertexFormat a)
uWriter a
a) Ptr ()
ptr
IO GLboolean -> IO ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (IO GLboolean -> IO ()) -> IO GLboolean -> IO ()
forall a b. (a -> b) -> a -> b
$ GLuint -> IO GLboolean
forall (m :: * -> *). MonadIO m => GLuint -> m GLboolean
glUnmapBuffer GLuint
forall a. (Eq a, Num a) => a
GL_COPY_WRITE_BUFFER
data InputIndices = InputIndices {
InputIndices -> VInt
inputVertexID :: VInt,
InputIndices -> VInt
inputInstanceID :: VInt
}
withInputIndices :: (a -> InputIndices -> b) -> PrimitiveStream p a -> PrimitiveStream p b
withInputIndices :: (a -> InputIndices -> b)
-> PrimitiveStream p a -> PrimitiveStream p b
withInputIndices a -> InputIndices -> b
f = (a -> b) -> PrimitiveStream p a -> PrimitiveStream p b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\a
a -> a -> InputIndices -> b
f a
a (VInt -> VInt -> InputIndices
InputIndices (Text -> VInt
forall c a. Text -> S c a
scalarS' Text
"gl_VertexID") (Text -> VInt
forall c a. Text -> S c a
scalarS' Text
"gl_InstanceID")))
type PointSize = VFloat
withPointSize :: (a -> PointSize -> (b, PointSize)) -> PrimitiveStream Points a -> PrimitiveStream Points b
withPointSize :: (a -> PointSize -> (b, PointSize))
-> PrimitiveStream Points a -> PrimitiveStream Points b
withPointSize a -> PointSize -> (b, PointSize)
f (PrimitiveStream [(a, (Maybe PointSize, PrimitiveStreamData))]
xs) = [(b, (Maybe PointSize, PrimitiveStreamData))]
-> PrimitiveStream Points b
forall t a.
[(a, (Maybe PointSize, PrimitiveStreamData))]
-> PrimitiveStream t a
PrimitiveStream ([(b, (Maybe PointSize, PrimitiveStreamData))]
-> PrimitiveStream Points b)
-> [(b, (Maybe PointSize, PrimitiveStreamData))]
-> PrimitiveStream Points b
forall a b. (a -> b) -> a -> b
$ ((a, (Maybe PointSize, PrimitiveStreamData))
-> (b, (Maybe PointSize, PrimitiveStreamData)))
-> [(a, (Maybe PointSize, PrimitiveStreamData))]
-> [(b, (Maybe PointSize, PrimitiveStreamData))]
forall a b. (a -> b) -> [a] -> [b]
map (\(a
a, (Maybe PointSize
ps, PrimitiveStreamData
d)) -> let (b
b, PointSize
ps') = a -> PointSize -> (b, PointSize)
f a
a (PointSize -> Maybe PointSize -> PointSize
forall a. a -> Maybe a -> a
fromMaybe (Text -> PointSize
forall c a. Text -> S c a
scalarS' Text
"1") Maybe PointSize
ps) in (b
b, (PointSize -> Maybe PointSize
forall a. a -> Maybe a
Just PointSize
ps', PrimitiveStreamData
d))) [(a, (Maybe PointSize, PrimitiveStreamData))]
xs
append :: Monad m => a -> StateT [a] m ()
append :: a -> StateT [a] m ()
append a
x = ([a] -> [a]) -> StateT [a] m ()
forall (m :: * -> *) s. Monad m => (s -> s) -> StateT s m ()
modify (a
xa -> [a] -> [a]
forall a. a -> [a] -> [a]
:)
makeVertexF :: p
-> (SType -> ExprM Text -> b)
-> SType
-> p
-> StateT (Int, b, c) m b
makeVertexF p
x SType -> ExprM Text -> b
f SType
styp p
_ = do
(Int
n, b
uoffset, c
m) <- StateT (Int, b, c) m (Int, b, c)
forall (m :: * -> *) s. Monad m => StateT s m s
get
(Int, b, c) -> StateT (Int, b, c) m ()
forall (m :: * -> *) s. Monad m => s -> StateT s m ()
put (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1, b
uoffset, c
m)
b -> StateT (Int, b, c) m b
forall (m :: * -> *) a. Monad m => a -> m a
return (SType -> ExprM Text -> b
f SType
styp (ExprM Text -> b) -> ExprM Text -> b
forall a b. (a -> b) -> a -> b
$ SType -> Int -> ExprM Text
useVInput SType
styp Int
n)
makeBindVertexFx :: Bool
-> GLint -> GLuint -> B a -> StateT [a -> (IO VAOKey, IO ())] m b
makeBindVertexFx Bool
norm GLint
x GLuint
typ B a
b = do
let combOffset :: Int
combOffset = B a -> Int
forall a. B a -> Int
bStride B a
b Int -> Int -> Int
forall a. Num a => a -> a -> a
* B a -> Int
forall a. B a -> Int
bSkipElems B a
b Int -> Int -> Int
forall a. Num a => a -> a -> a
+ B a -> Int
forall a. B a -> Int
bOffset B a
b
(a -> (IO VAOKey, IO ())) -> StateT [a -> (IO VAOKey, IO ())] m ()
forall (m :: * -> *) a. Monad m => a -> StateT [a] m ()
append (\a
ix ->
( do GLuint
bn <- IORef GLuint -> IO GLuint
forall a. IORef a -> IO a
readIORef (IORef GLuint -> IO GLuint) -> IORef GLuint -> IO GLuint
forall a b. (a -> b) -> a -> b
$ B a -> IORef GLuint
forall a. B a -> IORef GLuint
bName B a
b
VAOKey -> IO VAOKey
forall (m :: * -> *) a. Monad m => a -> m a
return (VAOKey -> IO VAOKey) -> VAOKey -> IO VAOKey
forall a b. (a -> b) -> a -> b
$ GLuint -> Int -> GLint -> Bool -> Int -> VAOKey
VAOKey GLuint
bn Int
combOffset GLint
x Bool
norm (B a -> Int
forall a. B a -> Int
bInstanceDiv B a
b)
, do GLuint
bn <- IORef GLuint -> IO GLuint
forall a. IORef a -> IO a
readIORef (IORef GLuint -> IO GLuint) -> IORef GLuint -> IO GLuint
forall a b. (a -> b) -> a -> b
$ B a -> IORef GLuint
forall a. B a -> IORef GLuint
bName B a
b
let ix' :: GLuint
ix' = a -> GLuint
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
ix
GLuint -> IO ()
forall (m :: * -> *). MonadIO m => GLuint -> m ()
glEnableVertexAttribArray GLuint
ix'
GLuint -> GLuint -> IO ()
forall (m :: * -> *). MonadIO m => GLuint -> GLuint -> m ()
glBindBuffer GLuint
forall a. (Eq a, Num a) => a
GL_ARRAY_BUFFER GLuint
bn
GLuint -> GLuint -> IO ()
forall (m :: * -> *). MonadIO m => GLuint -> GLuint -> m ()
glVertexAttribDivisor GLuint
ix' (Int -> GLuint
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> GLuint) -> Int -> GLuint
forall a b. (a -> b) -> a -> b
$ B a -> Int
forall a. B a -> Int
bInstanceDiv B a
b)
GLuint -> GLint -> GLuint -> GLboolean -> GLint -> Ptr () -> IO ()
forall (m :: * -> *).
MonadIO m =>
GLuint -> GLint -> GLuint -> GLboolean -> GLint -> Ptr () -> m ()
glVertexAttribPointer GLuint
ix' GLint
x GLuint
typ (Bool -> GLboolean
forall a. Num a => Bool -> a
fromBool Bool
norm) (Int -> GLint
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> GLint) -> Int -> GLint
forall a b. (a -> b) -> a -> b
$ B a -> Int
forall a. B a -> Int
bStride B a
b) (IntPtr -> Ptr ()
forall a. IntPtr -> Ptr a
intPtrToPtr (IntPtr -> Ptr ()) -> IntPtr -> Ptr ()
forall a b. (a -> b) -> a -> b
$ Int -> IntPtr
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
combOffset))
)
b -> StateT [a -> (IO VAOKey, IO ())] m b
forall (m :: * -> *) a. Monad m => a -> m a
return b
forall a. HasCallStack => a
undefined
makeBindVertexFnorm :: GLint
-> GLuint -> B a -> StateT [Int -> (IO VAOKey, IO ())] Identity b
makeBindVertexFnorm = Bool
-> GLint
-> GLuint
-> B a
-> StateT [Int -> (IO VAOKey, IO ())] Identity b
forall (m :: * -> *) a a b.
(Monad m, Integral a) =>
Bool
-> GLint -> GLuint -> B a -> StateT [a -> (IO VAOKey, IO ())] m b
makeBindVertexFx Bool
True
makeBindVertexF :: GLint
-> GLuint -> B a -> StateT [Int -> (IO VAOKey, IO ())] Identity b
makeBindVertexF = Bool
-> GLint
-> GLuint
-> B a
-> StateT [Int -> (IO VAOKey, IO ())] Identity b
forall (m :: * -> *) a a b.
(Monad m, Integral a) =>
Bool
-> GLint -> GLuint -> B a -> StateT [a -> (IO VAOKey, IO ())] m b
makeBindVertexFx Bool
False
makeVertexI :: p
-> (SType -> ExprM Text -> b)
-> SType
-> p
-> StateT (Int, b, c) m b
makeVertexI p
x SType -> ExprM Text -> b
f SType
styp p
_ = do
(Int
n, b
uoffset,c
m) <- StateT (Int, b, c) m (Int, b, c)
forall (m :: * -> *) s. Monad m => StateT s m s
get
(Int, b, c) -> StateT (Int, b, c) m ()
forall (m :: * -> *) s. Monad m => s -> StateT s m ()
put (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1, b
uoffset,c
m)
b -> StateT (Int, b, c) m b
forall (m :: * -> *) a. Monad m => a -> m a
return (SType -> ExprM Text -> b
f SType
styp (ExprM Text -> b) -> ExprM Text -> b
forall a b. (a -> b) -> a -> b
$ SType -> Int -> ExprM Text
useVInput SType
styp Int
n)
makeBindVertexI :: GLint -> GLuint -> B a -> StateT [a -> (IO VAOKey, IO ())] m b
makeBindVertexI GLint
x GLuint
typ B a
b = do
let combOffset :: Int
combOffset = B a -> Int
forall a. B a -> Int
bStride B a
b Int -> Int -> Int
forall a. Num a => a -> a -> a
* B a -> Int
forall a. B a -> Int
bSkipElems B a
b Int -> Int -> Int
forall a. Num a => a -> a -> a
+ B a -> Int
forall a. B a -> Int
bOffset B a
b
(a -> (IO VAOKey, IO ())) -> StateT [a -> (IO VAOKey, IO ())] m ()
forall (m :: * -> *) a. Monad m => a -> StateT [a] m ()
append (\a
ix ->
( do GLuint
bn <- IORef GLuint -> IO GLuint
forall a. IORef a -> IO a
readIORef (IORef GLuint -> IO GLuint) -> IORef GLuint -> IO GLuint
forall a b. (a -> b) -> a -> b
$ B a -> IORef GLuint
forall a. B a -> IORef GLuint
bName B a
b
VAOKey -> IO VAOKey
forall (m :: * -> *) a. Monad m => a -> m a
return (VAOKey -> IO VAOKey) -> VAOKey -> IO VAOKey
forall a b. (a -> b) -> a -> b
$ GLuint -> Int -> GLint -> Bool -> Int -> VAOKey
VAOKey GLuint
bn Int
combOffset GLint
x Bool
False (B a -> Int
forall a. B a -> Int
bInstanceDiv B a
b)
, do GLuint
bn <- IORef GLuint -> IO GLuint
forall a. IORef a -> IO a
readIORef (IORef GLuint -> IO GLuint) -> IORef GLuint -> IO GLuint
forall a b. (a -> b) -> a -> b
$ B a -> IORef GLuint
forall a. B a -> IORef GLuint
bName B a
b
let ix' :: GLuint
ix' = a -> GLuint
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
ix
GLuint -> IO ()
forall (m :: * -> *). MonadIO m => GLuint -> m ()
glEnableVertexAttribArray GLuint
ix'
GLuint -> GLuint -> IO ()
forall (m :: * -> *). MonadIO m => GLuint -> GLuint -> m ()
glBindBuffer GLuint
forall a. (Eq a, Num a) => a
GL_ARRAY_BUFFER GLuint
bn
GLuint -> GLuint -> IO ()
forall (m :: * -> *). MonadIO m => GLuint -> GLuint -> m ()
glVertexAttribDivisor GLuint
ix' (Int -> GLuint
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> GLuint) -> Int -> GLuint
forall a b. (a -> b) -> a -> b
$ B a -> Int
forall a. B a -> Int
bInstanceDiv B a
b)
GLuint -> GLint -> GLuint -> GLint -> Ptr () -> IO ()
forall (m :: * -> *).
MonadIO m =>
GLuint -> GLint -> GLuint -> GLint -> Ptr () -> m ()
glVertexAttribIPointer GLuint
ix' GLint
x GLuint
typ (Int -> GLint
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> GLint) -> Int -> GLint
forall a b. (a -> b) -> a -> b
$ B a -> Int
forall a. B a -> Int
bStride B a
b) (IntPtr -> Ptr ()
forall a. IntPtr -> Ptr a
intPtrToPtr (IntPtr -> Ptr ()) -> IntPtr -> Ptr ()
forall a b. (a -> b) -> a -> b
$ Int -> IntPtr
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
combOffset))
)
b -> StateT [a -> (IO VAOKey, IO ())] m b
forall (m :: * -> *) a. Monad m => a -> m a
return b
forall a. HasCallStack => a
undefined
noWriter :: Kleisli (StateT (Ptr ()) IO) b b
noWriter = (b -> StateT (Ptr ()) IO b) -> Kleisli (StateT (Ptr ()) IO) b b
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli (StateT (Ptr ()) IO b -> b -> StateT (Ptr ()) IO b
forall a b. a -> b -> a
const (StateT (Ptr ()) IO b -> b -> StateT (Ptr ()) IO b)
-> StateT (Ptr ()) IO b -> b -> StateT (Ptr ()) IO b
forall a b. (a -> b) -> a -> b
$ b -> StateT (Ptr ()) IO b
forall (m :: * -> *) a. Monad m => a -> m a
return b
forall a. HasCallStack => a
undefined)
toUniformVertex :: forall a b. Storable a => SType -> ToVertex a (S V b)
toUniformVertex :: SType -> ToVertex a (S V b)
toUniformVertex SType
styp = Kleisli (StateT (Ptr ()) IO) a (S V b)
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
a
(S V b)
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) a (S V b)
-> ToVertex a (S V b)
forall a b.
Kleisli (StateT (Ptr ()) IO) a b
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text))) a b
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) a b
-> ToVertex a b
ToVertex ((a -> StateT (Ptr ()) IO (S V b))
-> Kleisli (StateT (Ptr ()) IO) a (S V b)
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli a -> StateT (Ptr ()) IO (S V b)
uWriter) ((a
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) (S V b))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
a
(S V b)
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli a
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) (S V b)
makeV) ((a -> State [Int -> (IO VAOKey, IO ())] (S V b))
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) a (S V b)
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli a -> State [Int -> (IO VAOKey, IO ())] (S V b)
forall (m :: * -> *) p a. Monad m => p -> m a
makeBind)
where
size :: Int
size = a -> Int
forall a. Storable a => a -> Int
sizeOf (a
forall a. HasCallStack => a
undefined :: a)
uWriter :: a -> StateT (Ptr ()) IO (S V b)
uWriter a
a = do
Ptr ()
ptr <- StateT (Ptr ()) IO (Ptr ())
forall (m :: * -> *) s. Monad m => StateT s m s
get
Ptr () -> StateT (Ptr ()) IO ()
forall (m :: * -> *) s. Monad m => s -> StateT s m ()
put (Ptr ()
ptr Ptr () -> Int -> Ptr ()
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
size)
IO () -> StateT (Ptr ()) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> StateT (Ptr ()) IO ()) -> IO () -> StateT (Ptr ()) IO ()
forall a b. (a -> b) -> a -> b
$ Ptr a -> a -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr () -> Ptr a
forall a b. Ptr a -> Ptr b
castPtr Ptr ()
ptr) a
a
S V b -> StateT (Ptr ()) IO (S V b)
forall (m :: * -> *) a. Monad m => a -> m a
return S V b
forall a. HasCallStack => a
undefined
makeV :: a
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) (S V b)
makeV a
a = do
(Int
n, Int
uoffset,OffsetToSType
m) <- StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(Int, Int, OffsetToSType)
forall (m :: * -> *) s. Monad m => StateT s m s
get
(Int, Int, OffsetToSType)
-> StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) ()
forall (m :: * -> *) s. Monad m => s -> StateT s m ()
put (Int
n, Int
uoffset Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
size, Int -> SType -> OffsetToSType -> OffsetToSType
forall k v. Integral k => k -> v -> IntMap k v -> IntMap k v
Map.insert Int
uoffset SType
styp OffsetToSType
m)
Int -> ExprM Text
useF <- ReaderT (Int -> ExprM Text) Identity (Int -> ExprM Text)
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(Int -> ExprM Text)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift ReaderT (Int -> ExprM Text) Identity (Int -> ExprM Text)
forall (m :: * -> *) r. Monad m => ReaderT r m r
ask
S V b
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) (S V b)
forall (m :: * -> *) a. Monad m => a -> m a
return (S V b
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) (S V b))
-> S V b
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) (S V b)
forall a b. (a -> b) -> a -> b
$ ExprM Text -> S V b
forall x a. ExprM Text -> S x a
S (ExprM Text -> S V b) -> ExprM Text -> S V b
forall a b. (a -> b) -> a -> b
$ Int -> ExprM Text
useF Int
uoffset
makeBind :: p -> m a
makeBind p
a =
a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return a
forall a. HasCallStack => a
undefined
instance VertexInput Float where
type VertexFormat Float = VFloat
toVertex :: ToVertex Float (VertexFormat Float)
toVertex = SType -> ToVertex Float PointSize
forall a b. Storable a => SType -> ToVertex a (S V b)
toUniformVertex SType
STypeFloat
instance VertexInput Int32 where
type VertexFormat Int32 = VInt
toVertex :: ToVertex GLint (VertexFormat GLint)
toVertex = SType -> ToVertex GLint VInt
forall a b. Storable a => SType -> ToVertex a (S V b)
toUniformVertex SType
STypeInt
instance VertexInput Word32 where
type VertexFormat Word32 = VWord
toVertex :: ToVertex GLuint (VertexFormat GLuint)
toVertex = SType -> ToVertex GLuint (S V Word)
forall a b. Storable a => SType -> ToVertex a (S V b)
toUniformVertex SType
STypeUInt
unBnorm :: Normalized t -> t
unBnorm :: Normalized t -> t
unBnorm (Normalized t
a) = t
a
instance VertexInput (B Float) where
type VertexFormat (B Float) = VFloat
toVertex :: ToVertex (B Float) (VertexFormat (B Float))
toVertex = Kleisli (StateT (Ptr ()) IO) (B Float) PointSize
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B Float)
PointSize
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) (B Float) PointSize
-> ToVertex (B Float) PointSize
forall a b.
Kleisli (StateT (Ptr ()) IO) a b
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text))) a b
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) a b
-> ToVertex a b
ToVertex Kleisli (StateT (Ptr ()) IO) (B Float) PointSize
forall b b. Kleisli (StateT (Ptr ()) IO) b b
noWriter ((B Float
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) PointSize)
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B Float)
PointSize
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((B Float
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) PointSize)
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B Float)
PointSize)
-> (B Float
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) PointSize)
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B Float)
PointSize
forall a b. (a -> b) -> a -> b
$ Integer
-> (SType -> ExprM Text -> PointSize)
-> SType
-> B Float
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) PointSize
forall (m :: * -> *) p b p b c.
Monad m =>
p
-> (SType -> ExprM Text -> b)
-> SType
-> p
-> StateT (Int, b, c) m b
makeVertexF Integer
1 ((ExprM Text -> PointSize) -> SType -> ExprM Text -> PointSize
forall a b. a -> b -> a
const ExprM Text -> PointSize
forall x a. ExprM Text -> S x a
S) SType
STypeFloat) ((B Float -> StateT [Int -> (IO VAOKey, IO ())] Identity PointSize)
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) (B Float) PointSize
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((B Float -> StateT [Int -> (IO VAOKey, IO ())] Identity PointSize)
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) (B Float) PointSize)
-> (B Float
-> StateT [Int -> (IO VAOKey, IO ())] Identity PointSize)
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) (B Float) PointSize
forall a b. (a -> b) -> a -> b
$ GLint
-> GLuint
-> B Float
-> StateT [Int -> (IO VAOKey, IO ())] Identity PointSize
forall a b.
GLint
-> GLuint -> B a -> StateT [Int -> (IO VAOKey, IO ())] Identity b
makeBindVertexF GLint
1 GLuint
forall a. (Eq a, Num a) => a
GL_FLOAT)
instance VertexInput (Normalized (B Int32)) where
type VertexFormat (Normalized (B Int32)) = VFloat
toVertex :: ToVertex
(Normalized (B GLint)) (VertexFormat (Normalized (B GLint)))
toVertex = Kleisli (StateT (Ptr ()) IO) (Normalized (B GLint)) PointSize
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B GLint))
PointSize
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B GLint))
PointSize
-> ToVertex (Normalized (B GLint)) PointSize
forall a b.
Kleisli (StateT (Ptr ()) IO) a b
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text))) a b
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) a b
-> ToVertex a b
ToVertex Kleisli (StateT (Ptr ()) IO) (Normalized (B GLint)) PointSize
forall b b. Kleisli (StateT (Ptr ()) IO) b b
noWriter ((Normalized (B GLint)
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) PointSize)
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B GLint))
PointSize
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((Normalized (B GLint)
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) PointSize)
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B GLint))
PointSize)
-> (Normalized (B GLint)
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) PointSize)
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B GLint))
PointSize
forall a b. (a -> b) -> a -> b
$ Integer
-> (SType -> ExprM Text -> PointSize)
-> SType
-> B GLint
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) PointSize
forall (m :: * -> *) p b p b c.
Monad m =>
p
-> (SType -> ExprM Text -> b)
-> SType
-> p
-> StateT (Int, b, c) m b
makeVertexF Integer
1 ((ExprM Text -> PointSize) -> SType -> ExprM Text -> PointSize
forall a b. a -> b -> a
const ExprM Text -> PointSize
forall x a. ExprM Text -> S x a
S) SType
STypeFloat (B GLint
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) PointSize)
-> (Normalized (B GLint) -> B GLint)
-> Normalized (B GLint)
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) PointSize
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Normalized (B GLint) -> B GLint
forall t. Normalized t -> t
unBnorm) ((Normalized (B GLint)
-> StateT [Int -> (IO VAOKey, IO ())] Identity PointSize)
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B GLint))
PointSize
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((Normalized (B GLint)
-> StateT [Int -> (IO VAOKey, IO ())] Identity PointSize)
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B GLint))
PointSize)
-> (Normalized (B GLint)
-> StateT [Int -> (IO VAOKey, IO ())] Identity PointSize)
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B GLint))
PointSize
forall a b. (a -> b) -> a -> b
$ GLint
-> GLuint
-> B GLint
-> StateT [Int -> (IO VAOKey, IO ())] Identity PointSize
forall a b.
GLint
-> GLuint -> B a -> StateT [Int -> (IO VAOKey, IO ())] Identity b
makeBindVertexFnorm GLint
1 GLuint
forall a. (Eq a, Num a) => a
GL_INT (B GLint -> StateT [Int -> (IO VAOKey, IO ())] Identity PointSize)
-> (Normalized (B GLint) -> B GLint)
-> Normalized (B GLint)
-> StateT [Int -> (IO VAOKey, IO ())] Identity PointSize
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Normalized (B GLint) -> B GLint
forall t. Normalized t -> t
unBnorm)
instance VertexInput (Normalized (B Word32)) where
type VertexFormat (Normalized (B Word32)) = VFloat
toVertex :: ToVertex
(Normalized (B GLuint)) (VertexFormat (Normalized (B GLuint)))
toVertex = Kleisli (StateT (Ptr ()) IO) (Normalized (B GLuint)) PointSize
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B GLuint))
PointSize
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B GLuint))
PointSize
-> ToVertex (Normalized (B GLuint)) PointSize
forall a b.
Kleisli (StateT (Ptr ()) IO) a b
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text))) a b
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) a b
-> ToVertex a b
ToVertex Kleisli (StateT (Ptr ()) IO) (Normalized (B GLuint)) PointSize
forall b b. Kleisli (StateT (Ptr ()) IO) b b
noWriter ((Normalized (B GLuint)
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) PointSize)
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B GLuint))
PointSize
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((Normalized (B GLuint)
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) PointSize)
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B GLuint))
PointSize)
-> (Normalized (B GLuint)
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) PointSize)
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B GLuint))
PointSize
forall a b. (a -> b) -> a -> b
$ Integer
-> (SType -> ExprM Text -> PointSize)
-> SType
-> B GLuint
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) PointSize
forall (m :: * -> *) p b p b c.
Monad m =>
p
-> (SType -> ExprM Text -> b)
-> SType
-> p
-> StateT (Int, b, c) m b
makeVertexF Integer
1 ((ExprM Text -> PointSize) -> SType -> ExprM Text -> PointSize
forall a b. a -> b -> a
const ExprM Text -> PointSize
forall x a. ExprM Text -> S x a
S) SType
STypeFloat (B GLuint
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) PointSize)
-> (Normalized (B GLuint) -> B GLuint)
-> Normalized (B GLuint)
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) PointSize
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Normalized (B GLuint) -> B GLuint
forall t. Normalized t -> t
unBnorm) ((Normalized (B GLuint)
-> StateT [Int -> (IO VAOKey, IO ())] Identity PointSize)
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B GLuint))
PointSize
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((Normalized (B GLuint)
-> StateT [Int -> (IO VAOKey, IO ())] Identity PointSize)
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B GLuint))
PointSize)
-> (Normalized (B GLuint)
-> StateT [Int -> (IO VAOKey, IO ())] Identity PointSize)
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B GLuint))
PointSize
forall a b. (a -> b) -> a -> b
$ GLint
-> GLuint
-> B GLuint
-> StateT [Int -> (IO VAOKey, IO ())] Identity PointSize
forall a b.
GLint
-> GLuint -> B a -> StateT [Int -> (IO VAOKey, IO ())] Identity b
makeBindVertexFnorm GLint
1 GLuint
forall a. (Eq a, Num a) => a
GL_UNSIGNED_INT (B GLuint -> StateT [Int -> (IO VAOKey, IO ())] Identity PointSize)
-> (Normalized (B GLuint) -> B GLuint)
-> Normalized (B GLuint)
-> StateT [Int -> (IO VAOKey, IO ())] Identity PointSize
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Normalized (B GLuint) -> B GLuint
forall t. Normalized t -> t
unBnorm)
instance VertexInput (B Int32) where
type VertexFormat (B Int32) = VInt
toVertex :: ToVertex (B GLint) (VertexFormat (B GLint))
toVertex = Kleisli (StateT (Ptr ()) IO) (B GLint) VInt
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B GLint)
VInt
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) (B GLint) VInt
-> ToVertex (B GLint) VInt
forall a b.
Kleisli (StateT (Ptr ()) IO) a b
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text))) a b
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) a b
-> ToVertex a b
ToVertex Kleisli (StateT (Ptr ()) IO) (B GLint) VInt
forall b b. Kleisli (StateT (Ptr ()) IO) b b
noWriter ((B GLint
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) VInt)
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B GLint)
VInt
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((B GLint
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) VInt)
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B GLint)
VInt)
-> (B GLint
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) VInt)
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B GLint)
VInt
forall a b. (a -> b) -> a -> b
$ Integer
-> (SType -> ExprM Text -> VInt)
-> SType
-> B GLint
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) VInt
forall (m :: * -> *) p b p b c.
Monad m =>
p
-> (SType -> ExprM Text -> b)
-> SType
-> p
-> StateT (Int, b, c) m b
makeVertexI Integer
1 ((ExprM Text -> VInt) -> SType -> ExprM Text -> VInt
forall a b. a -> b -> a
const ExprM Text -> VInt
forall x a. ExprM Text -> S x a
S) SType
STypeInt) ((B GLint -> StateT [Int -> (IO VAOKey, IO ())] Identity VInt)
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) (B GLint) VInt
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((B GLint -> StateT [Int -> (IO VAOKey, IO ())] Identity VInt)
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) (B GLint) VInt)
-> (B GLint -> StateT [Int -> (IO VAOKey, IO ())] Identity VInt)
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) (B GLint) VInt
forall a b. (a -> b) -> a -> b
$ GLint
-> GLuint
-> B GLint
-> StateT [Int -> (IO VAOKey, IO ())] Identity VInt
forall (m :: * -> *) a a b.
(Monad m, Integral a) =>
GLint -> GLuint -> B a -> StateT [a -> (IO VAOKey, IO ())] m b
makeBindVertexI GLint
1 GLuint
forall a. (Eq a, Num a) => a
GL_INT)
instance VertexInput (B Word32) where
type VertexFormat (B Word32) = VWord
toVertex :: ToVertex (B GLuint) (VertexFormat (B GLuint))
toVertex = Kleisli (StateT (Ptr ()) IO) (B GLuint) (S V Word)
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B GLuint)
(S V Word)
-> Kleisli
(State [Int -> (IO VAOKey, IO ())]) (B GLuint) (S V Word)
-> ToVertex (B GLuint) (S V Word)
forall a b.
Kleisli (StateT (Ptr ()) IO) a b
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text))) a b
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) a b
-> ToVertex a b
ToVertex Kleisli (StateT (Ptr ()) IO) (B GLuint) (S V Word)
forall b b. Kleisli (StateT (Ptr ()) IO) b b
noWriter ((B GLuint
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) (S V Word))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B GLuint)
(S V Word)
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((B GLuint
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) (S V Word))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B GLuint)
(S V Word))
-> (B GLuint
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) (S V Word))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B GLuint)
(S V Word)
forall a b. (a -> b) -> a -> b
$ Integer
-> (SType -> ExprM Text -> S V Word)
-> SType
-> B GLuint
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) (S V Word)
forall (m :: * -> *) p b p b c.
Monad m =>
p
-> (SType -> ExprM Text -> b)
-> SType
-> p
-> StateT (Int, b, c) m b
makeVertexI Integer
1 ((ExprM Text -> S V Word) -> SType -> ExprM Text -> S V Word
forall a b. a -> b -> a
const ExprM Text -> S V Word
forall x a. ExprM Text -> S x a
S) SType
STypeUInt) ((B GLuint
-> StateT [Int -> (IO VAOKey, IO ())] Identity (S V Word))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())]) (B GLuint) (S V Word)
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((B GLuint
-> StateT [Int -> (IO VAOKey, IO ())] Identity (S V Word))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())]) (B GLuint) (S V Word))
-> (B GLuint
-> StateT [Int -> (IO VAOKey, IO ())] Identity (S V Word))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())]) (B GLuint) (S V Word)
forall a b. (a -> b) -> a -> b
$ GLint
-> GLuint
-> B GLuint
-> StateT [Int -> (IO VAOKey, IO ())] Identity (S V Word)
forall (m :: * -> *) a a b.
(Monad m, Integral a) =>
GLint -> GLuint -> B a -> StateT [a -> (IO VAOKey, IO ())] m b
makeBindVertexI GLint
1 GLuint
forall a. (Eq a, Num a) => a
GL_UNSIGNED_INT)
instance VertexInput (B2 Float) where
type VertexFormat (B2 Float) = V2 VFloat
toVertex :: ToVertex (B2 Float) (VertexFormat (B2 Float))
toVertex = Kleisli (StateT (Ptr ()) IO) (B2 Float) (V2 PointSize)
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B2 Float)
(V2 PointSize)
-> Kleisli
(State [Int -> (IO VAOKey, IO ())]) (B2 Float) (V2 PointSize)
-> ToVertex (B2 Float) (V2 PointSize)
forall a b.
Kleisli (StateT (Ptr ()) IO) a b
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text))) a b
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) a b
-> ToVertex a b
ToVertex Kleisli (StateT (Ptr ()) IO) (B2 Float) (V2 PointSize)
forall b b. Kleisli (StateT (Ptr ()) IO) b b
noWriter ((B2 Float
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V2 PointSize))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B2 Float)
(V2 PointSize)
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((B2 Float
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V2 PointSize))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B2 Float)
(V2 PointSize))
-> (B2 Float
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V2 PointSize))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B2 Float)
(V2 PointSize)
forall a b. (a -> b) -> a -> b
$ Integer
-> (SType -> ExprM Text -> V2 PointSize)
-> SType
-> B Float
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V2 PointSize)
forall (m :: * -> *) p b p b c.
Monad m =>
p
-> (SType -> ExprM Text -> b)
-> SType
-> p
-> StateT (Int, b, c) m b
makeVertexF Integer
2 SType -> ExprM Text -> V2 PointSize
forall c a. SType -> ExprM Text -> V2 (S c a)
vec2S (Int -> SType
STypeVec Int
2) (B Float
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V2 PointSize))
-> (B2 Float -> B Float)
-> B2 Float
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V2 PointSize)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. B2 Float -> B Float
forall a. B2 a -> B a
unB2) ((B2 Float -> State [Int -> (IO VAOKey, IO ())] (V2 PointSize))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())]) (B2 Float) (V2 PointSize)
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((B2 Float -> State [Int -> (IO VAOKey, IO ())] (V2 PointSize))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())]) (B2 Float) (V2 PointSize))
-> (B2 Float -> State [Int -> (IO VAOKey, IO ())] (V2 PointSize))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())]) (B2 Float) (V2 PointSize)
forall a b. (a -> b) -> a -> b
$ GLint
-> GLuint
-> B Float
-> State [Int -> (IO VAOKey, IO ())] (V2 PointSize)
forall a b.
GLint
-> GLuint -> B a -> StateT [Int -> (IO VAOKey, IO ())] Identity b
makeBindVertexF GLint
2 GLuint
forall a. (Eq a, Num a) => a
GL_FLOAT (B Float -> State [Int -> (IO VAOKey, IO ())] (V2 PointSize))
-> (B2 Float -> B Float)
-> B2 Float
-> State [Int -> (IO VAOKey, IO ())] (V2 PointSize)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. B2 Float -> B Float
forall a. B2 a -> B a
unB2)
instance VertexInput (Normalized (B2 Int32)) where
type VertexFormat (Normalized (B2 Int32)) = V2 VFloat
toVertex :: ToVertex
(Normalized (B2 GLint)) (VertexFormat (Normalized (B2 GLint)))
toVertex = Kleisli (StateT (Ptr ()) IO) (Normalized (B2 GLint)) (V2 PointSize)
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B2 GLint))
(V2 PointSize)
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B2 GLint))
(V2 PointSize)
-> ToVertex (Normalized (B2 GLint)) (V2 PointSize)
forall a b.
Kleisli (StateT (Ptr ()) IO) a b
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text))) a b
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) a b
-> ToVertex a b
ToVertex Kleisli (StateT (Ptr ()) IO) (Normalized (B2 GLint)) (V2 PointSize)
forall b b. Kleisli (StateT (Ptr ()) IO) b b
noWriter ((Normalized (B2 GLint)
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V2 PointSize))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B2 GLint))
(V2 PointSize)
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((Normalized (B2 GLint)
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V2 PointSize))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B2 GLint))
(V2 PointSize))
-> (Normalized (B2 GLint)
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V2 PointSize))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B2 GLint))
(V2 PointSize)
forall a b. (a -> b) -> a -> b
$ Integer
-> (SType -> ExprM Text -> V2 PointSize)
-> SType
-> B GLint
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V2 PointSize)
forall (m :: * -> *) p b p b c.
Monad m =>
p
-> (SType -> ExprM Text -> b)
-> SType
-> p
-> StateT (Int, b, c) m b
makeVertexF Integer
2 SType -> ExprM Text -> V2 PointSize
forall c a. SType -> ExprM Text -> V2 (S c a)
vec2S (Int -> SType
STypeVec Int
2) (B GLint
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V2 PointSize))
-> (Normalized (B2 GLint) -> B GLint)
-> Normalized (B2 GLint)
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V2 PointSize)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. B2 GLint -> B GLint
forall a. B2 a -> B a
unB2 (B2 GLint -> B GLint)
-> (Normalized (B2 GLint) -> B2 GLint)
-> Normalized (B2 GLint)
-> B GLint
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Normalized (B2 GLint) -> B2 GLint
forall t. Normalized t -> t
unBnorm) ((Normalized (B2 GLint)
-> State [Int -> (IO VAOKey, IO ())] (V2 PointSize))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B2 GLint))
(V2 PointSize)
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((Normalized (B2 GLint)
-> State [Int -> (IO VAOKey, IO ())] (V2 PointSize))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B2 GLint))
(V2 PointSize))
-> (Normalized (B2 GLint)
-> State [Int -> (IO VAOKey, IO ())] (V2 PointSize))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B2 GLint))
(V2 PointSize)
forall a b. (a -> b) -> a -> b
$ GLint
-> GLuint
-> B GLint
-> State [Int -> (IO VAOKey, IO ())] (V2 PointSize)
forall a b.
GLint
-> GLuint -> B a -> StateT [Int -> (IO VAOKey, IO ())] Identity b
makeBindVertexFnorm GLint
2 GLuint
forall a. (Eq a, Num a) => a
GL_INT (B GLint -> State [Int -> (IO VAOKey, IO ())] (V2 PointSize))
-> (Normalized (B2 GLint) -> B GLint)
-> Normalized (B2 GLint)
-> State [Int -> (IO VAOKey, IO ())] (V2 PointSize)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. B2 GLint -> B GLint
forall a. B2 a -> B a
unB2 (B2 GLint -> B GLint)
-> (Normalized (B2 GLint) -> B2 GLint)
-> Normalized (B2 GLint)
-> B GLint
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Normalized (B2 GLint) -> B2 GLint
forall t. Normalized t -> t
unBnorm)
instance VertexInput (Normalized (B2 Int16)) where
type VertexFormat (Normalized (B2 Int16)) = V2 VFloat
toVertex :: ToVertex
(Normalized (B2 Int16)) (VertexFormat (Normalized (B2 Int16)))
toVertex = Kleisli (StateT (Ptr ()) IO) (Normalized (B2 Int16)) (V2 PointSize)
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B2 Int16))
(V2 PointSize)
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B2 Int16))
(V2 PointSize)
-> ToVertex (Normalized (B2 Int16)) (V2 PointSize)
forall a b.
Kleisli (StateT (Ptr ()) IO) a b
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text))) a b
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) a b
-> ToVertex a b
ToVertex Kleisli (StateT (Ptr ()) IO) (Normalized (B2 Int16)) (V2 PointSize)
forall b b. Kleisli (StateT (Ptr ()) IO) b b
noWriter ((Normalized (B2 Int16)
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V2 PointSize))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B2 Int16))
(V2 PointSize)
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((Normalized (B2 Int16)
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V2 PointSize))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B2 Int16))
(V2 PointSize))
-> (Normalized (B2 Int16)
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V2 PointSize))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B2 Int16))
(V2 PointSize)
forall a b. (a -> b) -> a -> b
$ Integer
-> (SType -> ExprM Text -> V2 PointSize)
-> SType
-> B Int16
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V2 PointSize)
forall (m :: * -> *) p b p b c.
Monad m =>
p
-> (SType -> ExprM Text -> b)
-> SType
-> p
-> StateT (Int, b, c) m b
makeVertexF Integer
2 SType -> ExprM Text -> V2 PointSize
forall c a. SType -> ExprM Text -> V2 (S c a)
vec2S (Int -> SType
STypeVec Int
2) (B Int16
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V2 PointSize))
-> (Normalized (B2 Int16) -> B Int16)
-> Normalized (B2 Int16)
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V2 PointSize)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. B2 Int16 -> B Int16
forall a. B2 a -> B a
unB2 (B2 Int16 -> B Int16)
-> (Normalized (B2 Int16) -> B2 Int16)
-> Normalized (B2 Int16)
-> B Int16
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Normalized (B2 Int16) -> B2 Int16
forall t. Normalized t -> t
unBnorm) ((Normalized (B2 Int16)
-> State [Int -> (IO VAOKey, IO ())] (V2 PointSize))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B2 Int16))
(V2 PointSize)
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((Normalized (B2 Int16)
-> State [Int -> (IO VAOKey, IO ())] (V2 PointSize))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B2 Int16))
(V2 PointSize))
-> (Normalized (B2 Int16)
-> State [Int -> (IO VAOKey, IO ())] (V2 PointSize))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B2 Int16))
(V2 PointSize)
forall a b. (a -> b) -> a -> b
$ GLint
-> GLuint
-> B Int16
-> State [Int -> (IO VAOKey, IO ())] (V2 PointSize)
forall a b.
GLint
-> GLuint -> B a -> StateT [Int -> (IO VAOKey, IO ())] Identity b
makeBindVertexFnorm GLint
2 GLuint
forall a. (Eq a, Num a) => a
GL_SHORT (B Int16 -> State [Int -> (IO VAOKey, IO ())] (V2 PointSize))
-> (Normalized (B2 Int16) -> B Int16)
-> Normalized (B2 Int16)
-> State [Int -> (IO VAOKey, IO ())] (V2 PointSize)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. B2 Int16 -> B Int16
forall a. B2 a -> B a
unB2 (B2 Int16 -> B Int16)
-> (Normalized (B2 Int16) -> B2 Int16)
-> Normalized (B2 Int16)
-> B Int16
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Normalized (B2 Int16) -> B2 Int16
forall t. Normalized t -> t
unBnorm)
instance VertexInput (Normalized (B2 Word32)) where
type VertexFormat (Normalized (B2 Word32)) = V2 VFloat
toVertex :: ToVertex
(Normalized (B2 GLuint)) (VertexFormat (Normalized (B2 GLuint)))
toVertex = Kleisli
(StateT (Ptr ()) IO) (Normalized (B2 GLuint)) (V2 PointSize)
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B2 GLuint))
(V2 PointSize)
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B2 GLuint))
(V2 PointSize)
-> ToVertex (Normalized (B2 GLuint)) (V2 PointSize)
forall a b.
Kleisli (StateT (Ptr ()) IO) a b
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text))) a b
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) a b
-> ToVertex a b
ToVertex Kleisli
(StateT (Ptr ()) IO) (Normalized (B2 GLuint)) (V2 PointSize)
forall b b. Kleisli (StateT (Ptr ()) IO) b b
noWriter ((Normalized (B2 GLuint)
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V2 PointSize))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B2 GLuint))
(V2 PointSize)
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((Normalized (B2 GLuint)
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V2 PointSize))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B2 GLuint))
(V2 PointSize))
-> (Normalized (B2 GLuint)
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V2 PointSize))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B2 GLuint))
(V2 PointSize)
forall a b. (a -> b) -> a -> b
$ Integer
-> (SType -> ExprM Text -> V2 PointSize)
-> SType
-> B GLuint
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V2 PointSize)
forall (m :: * -> *) p b p b c.
Monad m =>
p
-> (SType -> ExprM Text -> b)
-> SType
-> p
-> StateT (Int, b, c) m b
makeVertexF Integer
2 SType -> ExprM Text -> V2 PointSize
forall c a. SType -> ExprM Text -> V2 (S c a)
vec2S (Int -> SType
STypeVec Int
2) (B GLuint
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V2 PointSize))
-> (Normalized (B2 GLuint) -> B GLuint)
-> Normalized (B2 GLuint)
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V2 PointSize)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. B2 GLuint -> B GLuint
forall a. B2 a -> B a
unB2 (B2 GLuint -> B GLuint)
-> (Normalized (B2 GLuint) -> B2 GLuint)
-> Normalized (B2 GLuint)
-> B GLuint
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Normalized (B2 GLuint) -> B2 GLuint
forall t. Normalized t -> t
unBnorm) ((Normalized (B2 GLuint)
-> State [Int -> (IO VAOKey, IO ())] (V2 PointSize))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B2 GLuint))
(V2 PointSize)
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((Normalized (B2 GLuint)
-> State [Int -> (IO VAOKey, IO ())] (V2 PointSize))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B2 GLuint))
(V2 PointSize))
-> (Normalized (B2 GLuint)
-> State [Int -> (IO VAOKey, IO ())] (V2 PointSize))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B2 GLuint))
(V2 PointSize)
forall a b. (a -> b) -> a -> b
$ GLint
-> GLuint
-> B GLuint
-> State [Int -> (IO VAOKey, IO ())] (V2 PointSize)
forall a b.
GLint
-> GLuint -> B a -> StateT [Int -> (IO VAOKey, IO ())] Identity b
makeBindVertexFnorm GLint
2 GLuint
forall a. (Eq a, Num a) => a
GL_UNSIGNED_INT (B GLuint -> State [Int -> (IO VAOKey, IO ())] (V2 PointSize))
-> (Normalized (B2 GLuint) -> B GLuint)
-> Normalized (B2 GLuint)
-> State [Int -> (IO VAOKey, IO ())] (V2 PointSize)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. B2 GLuint -> B GLuint
forall a. B2 a -> B a
unB2 (B2 GLuint -> B GLuint)
-> (Normalized (B2 GLuint) -> B2 GLuint)
-> Normalized (B2 GLuint)
-> B GLuint
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Normalized (B2 GLuint) -> B2 GLuint
forall t. Normalized t -> t
unBnorm)
instance VertexInput (Normalized (B2 Word16)) where
type VertexFormat (Normalized (B2 Word16)) = V2 VFloat
toVertex :: ToVertex
(Normalized (B2 Word16)) (VertexFormat (Normalized (B2 Word16)))
toVertex = Kleisli
(StateT (Ptr ()) IO) (Normalized (B2 Word16)) (V2 PointSize)
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B2 Word16))
(V2 PointSize)
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B2 Word16))
(V2 PointSize)
-> ToVertex (Normalized (B2 Word16)) (V2 PointSize)
forall a b.
Kleisli (StateT (Ptr ()) IO) a b
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text))) a b
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) a b
-> ToVertex a b
ToVertex Kleisli
(StateT (Ptr ()) IO) (Normalized (B2 Word16)) (V2 PointSize)
forall b b. Kleisli (StateT (Ptr ()) IO) b b
noWriter ((Normalized (B2 Word16)
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V2 PointSize))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B2 Word16))
(V2 PointSize)
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((Normalized (B2 Word16)
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V2 PointSize))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B2 Word16))
(V2 PointSize))
-> (Normalized (B2 Word16)
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V2 PointSize))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B2 Word16))
(V2 PointSize)
forall a b. (a -> b) -> a -> b
$ Integer
-> (SType -> ExprM Text -> V2 PointSize)
-> SType
-> B Word16
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V2 PointSize)
forall (m :: * -> *) p b p b c.
Monad m =>
p
-> (SType -> ExprM Text -> b)
-> SType
-> p
-> StateT (Int, b, c) m b
makeVertexF Integer
2 SType -> ExprM Text -> V2 PointSize
forall c a. SType -> ExprM Text -> V2 (S c a)
vec2S (Int -> SType
STypeVec Int
2) (B Word16
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V2 PointSize))
-> (Normalized (B2 Word16) -> B Word16)
-> Normalized (B2 Word16)
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V2 PointSize)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. B2 Word16 -> B Word16
forall a. B2 a -> B a
unB2 (B2 Word16 -> B Word16)
-> (Normalized (B2 Word16) -> B2 Word16)
-> Normalized (B2 Word16)
-> B Word16
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Normalized (B2 Word16) -> B2 Word16
forall t. Normalized t -> t
unBnorm) ((Normalized (B2 Word16)
-> State [Int -> (IO VAOKey, IO ())] (V2 PointSize))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B2 Word16))
(V2 PointSize)
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((Normalized (B2 Word16)
-> State [Int -> (IO VAOKey, IO ())] (V2 PointSize))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B2 Word16))
(V2 PointSize))
-> (Normalized (B2 Word16)
-> State [Int -> (IO VAOKey, IO ())] (V2 PointSize))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B2 Word16))
(V2 PointSize)
forall a b. (a -> b) -> a -> b
$ GLint
-> GLuint
-> B Word16
-> State [Int -> (IO VAOKey, IO ())] (V2 PointSize)
forall a b.
GLint
-> GLuint -> B a -> StateT [Int -> (IO VAOKey, IO ())] Identity b
makeBindVertexFnorm GLint
2 GLuint
forall a. (Eq a, Num a) => a
GL_UNSIGNED_SHORT (B Word16 -> State [Int -> (IO VAOKey, IO ())] (V2 PointSize))
-> (Normalized (B2 Word16) -> B Word16)
-> Normalized (B2 Word16)
-> State [Int -> (IO VAOKey, IO ())] (V2 PointSize)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. B2 Word16 -> B Word16
forall a. B2 a -> B a
unB2 (B2 Word16 -> B Word16)
-> (Normalized (B2 Word16) -> B2 Word16)
-> Normalized (B2 Word16)
-> B Word16
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Normalized (B2 Word16) -> B2 Word16
forall t. Normalized t -> t
unBnorm)
instance VertexInput (B2 Int32) where
type VertexFormat (B2 Int32) = V2 VInt
toVertex :: ToVertex (B2 GLint) (VertexFormat (B2 GLint))
toVertex = Kleisli (StateT (Ptr ()) IO) (B2 GLint) (V2 VInt)
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B2 GLint)
(V2 VInt)
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) (B2 GLint) (V2 VInt)
-> ToVertex (B2 GLint) (V2 VInt)
forall a b.
Kleisli (StateT (Ptr ()) IO) a b
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text))) a b
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) a b
-> ToVertex a b
ToVertex Kleisli (StateT (Ptr ()) IO) (B2 GLint) (V2 VInt)
forall b b. Kleisli (StateT (Ptr ()) IO) b b
noWriter ((B2 GLint
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) (V2 VInt))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B2 GLint)
(V2 VInt)
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((B2 GLint
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) (V2 VInt))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B2 GLint)
(V2 VInt))
-> (B2 GLint
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) (V2 VInt))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B2 GLint)
(V2 VInt)
forall a b. (a -> b) -> a -> b
$ Integer
-> (SType -> ExprM Text -> V2 VInt)
-> SType
-> B GLint
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) (V2 VInt)
forall (m :: * -> *) p b p b c.
Monad m =>
p
-> (SType -> ExprM Text -> b)
-> SType
-> p
-> StateT (Int, b, c) m b
makeVertexI Integer
2 SType -> ExprM Text -> V2 VInt
forall c a. SType -> ExprM Text -> V2 (S c a)
vec2S (Int -> SType
STypeIVec Int
2) (B GLint
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) (V2 VInt))
-> (B2 GLint -> B GLint)
-> B2 GLint
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) (V2 VInt)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. B2 GLint -> B GLint
forall a. B2 a -> B a
unB2) ((B2 GLint -> State [Int -> (IO VAOKey, IO ())] (V2 VInt))
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) (B2 GLint) (V2 VInt)
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((B2 GLint -> State [Int -> (IO VAOKey, IO ())] (V2 VInt))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())]) (B2 GLint) (V2 VInt))
-> (B2 GLint -> State [Int -> (IO VAOKey, IO ())] (V2 VInt))
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) (B2 GLint) (V2 VInt)
forall a b. (a -> b) -> a -> b
$ GLint
-> GLuint -> B GLint -> State [Int -> (IO VAOKey, IO ())] (V2 VInt)
forall (m :: * -> *) a a b.
(Monad m, Integral a) =>
GLint -> GLuint -> B a -> StateT [a -> (IO VAOKey, IO ())] m b
makeBindVertexI GLint
2 GLuint
forall a. (Eq a, Num a) => a
GL_INT (B GLint -> State [Int -> (IO VAOKey, IO ())] (V2 VInt))
-> (B2 GLint -> B GLint)
-> B2 GLint
-> State [Int -> (IO VAOKey, IO ())] (V2 VInt)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. B2 GLint -> B GLint
forall a. B2 a -> B a
unB2)
instance VertexInput (B2 Int16) where
type VertexFormat (B2 Int16) = V2 VInt
toVertex :: ToVertex (B2 Int16) (VertexFormat (B2 Int16))
toVertex = Kleisli (StateT (Ptr ()) IO) (B2 Int16) (V2 VInt)
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B2 Int16)
(V2 VInt)
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) (B2 Int16) (V2 VInt)
-> ToVertex (B2 Int16) (V2 VInt)
forall a b.
Kleisli (StateT (Ptr ()) IO) a b
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text))) a b
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) a b
-> ToVertex a b
ToVertex Kleisli (StateT (Ptr ()) IO) (B2 Int16) (V2 VInt)
forall b b. Kleisli (StateT (Ptr ()) IO) b b
noWriter ((B2 Int16
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) (V2 VInt))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B2 Int16)
(V2 VInt)
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((B2 Int16
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) (V2 VInt))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B2 Int16)
(V2 VInt))
-> (B2 Int16
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) (V2 VInt))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B2 Int16)
(V2 VInt)
forall a b. (a -> b) -> a -> b
$ Integer
-> (SType -> ExprM Text -> V2 VInt)
-> SType
-> B Int16
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) (V2 VInt)
forall (m :: * -> *) p b p b c.
Monad m =>
p
-> (SType -> ExprM Text -> b)
-> SType
-> p
-> StateT (Int, b, c) m b
makeVertexI Integer
2 SType -> ExprM Text -> V2 VInt
forall c a. SType -> ExprM Text -> V2 (S c a)
vec2S (Int -> SType
STypeIVec Int
2) (B Int16
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) (V2 VInt))
-> (B2 Int16 -> B Int16)
-> B2 Int16
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) (V2 VInt)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. B2 Int16 -> B Int16
forall a. B2 a -> B a
unB2) ((B2 Int16 -> State [Int -> (IO VAOKey, IO ())] (V2 VInt))
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) (B2 Int16) (V2 VInt)
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((B2 Int16 -> State [Int -> (IO VAOKey, IO ())] (V2 VInt))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())]) (B2 Int16) (V2 VInt))
-> (B2 Int16 -> State [Int -> (IO VAOKey, IO ())] (V2 VInt))
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) (B2 Int16) (V2 VInt)
forall a b. (a -> b) -> a -> b
$ GLint
-> GLuint -> B Int16 -> State [Int -> (IO VAOKey, IO ())] (V2 VInt)
forall (m :: * -> *) a a b.
(Monad m, Integral a) =>
GLint -> GLuint -> B a -> StateT [a -> (IO VAOKey, IO ())] m b
makeBindVertexI GLint
2 GLuint
forall a. (Eq a, Num a) => a
GL_SHORT (B Int16 -> State [Int -> (IO VAOKey, IO ())] (V2 VInt))
-> (B2 Int16 -> B Int16)
-> B2 Int16
-> State [Int -> (IO VAOKey, IO ())] (V2 VInt)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. B2 Int16 -> B Int16
forall a. B2 a -> B a
unB2)
instance VertexInput (B2 Word32) where
type VertexFormat (B2 Word32) = V2 VWord
toVertex :: ToVertex (B2 GLuint) (VertexFormat (B2 GLuint))
toVertex = Kleisli (StateT (Ptr ()) IO) (B2 GLuint) (V2 (S V Word))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B2 GLuint)
(V2 (S V Word))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())]) (B2 GLuint) (V2 (S V Word))
-> ToVertex (B2 GLuint) (V2 (S V Word))
forall a b.
Kleisli (StateT (Ptr ()) IO) a b
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text))) a b
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) a b
-> ToVertex a b
ToVertex Kleisli (StateT (Ptr ()) IO) (B2 GLuint) (V2 (S V Word))
forall b b. Kleisli (StateT (Ptr ()) IO) b b
noWriter ((B2 GLuint
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V2 (S V Word)))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B2 GLuint)
(V2 (S V Word))
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((B2 GLuint
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V2 (S V Word)))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B2 GLuint)
(V2 (S V Word)))
-> (B2 GLuint
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V2 (S V Word)))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B2 GLuint)
(V2 (S V Word))
forall a b. (a -> b) -> a -> b
$ Integer
-> (SType -> ExprM Text -> V2 (S V Word))
-> SType
-> B GLuint
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V2 (S V Word))
forall (m :: * -> *) p b p b c.
Monad m =>
p
-> (SType -> ExprM Text -> b)
-> SType
-> p
-> StateT (Int, b, c) m b
makeVertexI Integer
2 SType -> ExprM Text -> V2 (S V Word)
forall c a. SType -> ExprM Text -> V2 (S c a)
vec2S (Int -> SType
STypeUVec Int
2) (B GLuint
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V2 (S V Word)))
-> (B2 GLuint -> B GLuint)
-> B2 GLuint
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V2 (S V Word))
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. B2 GLuint -> B GLuint
forall a. B2 a -> B a
unB2) ((B2 GLuint -> State [Int -> (IO VAOKey, IO ())] (V2 (S V Word)))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())]) (B2 GLuint) (V2 (S V Word))
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((B2 GLuint -> State [Int -> (IO VAOKey, IO ())] (V2 (S V Word)))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())]) (B2 GLuint) (V2 (S V Word)))
-> (B2 GLuint -> State [Int -> (IO VAOKey, IO ())] (V2 (S V Word)))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())]) (B2 GLuint) (V2 (S V Word))
forall a b. (a -> b) -> a -> b
$ GLint
-> GLuint
-> B GLuint
-> State [Int -> (IO VAOKey, IO ())] (V2 (S V Word))
forall (m :: * -> *) a a b.
(Monad m, Integral a) =>
GLint -> GLuint -> B a -> StateT [a -> (IO VAOKey, IO ())] m b
makeBindVertexI GLint
2 GLuint
forall a. (Eq a, Num a) => a
GL_UNSIGNED_INT (B GLuint -> State [Int -> (IO VAOKey, IO ())] (V2 (S V Word)))
-> (B2 GLuint -> B GLuint)
-> B2 GLuint
-> State [Int -> (IO VAOKey, IO ())] (V2 (S V Word))
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. B2 GLuint -> B GLuint
forall a. B2 a -> B a
unB2)
instance VertexInput (B2 Word16) where
type VertexFormat (B2 Word16) = V2 VWord
toVertex :: ToVertex (B2 Word16) (VertexFormat (B2 Word16))
toVertex = Kleisli (StateT (Ptr ()) IO) (B2 Word16) (V2 (S V Word))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B2 Word16)
(V2 (S V Word))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())]) (B2 Word16) (V2 (S V Word))
-> ToVertex (B2 Word16) (V2 (S V Word))
forall a b.
Kleisli (StateT (Ptr ()) IO) a b
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text))) a b
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) a b
-> ToVertex a b
ToVertex Kleisli (StateT (Ptr ()) IO) (B2 Word16) (V2 (S V Word))
forall b b. Kleisli (StateT (Ptr ()) IO) b b
noWriter ((B2 Word16
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V2 (S V Word)))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B2 Word16)
(V2 (S V Word))
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((B2 Word16
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V2 (S V Word)))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B2 Word16)
(V2 (S V Word)))
-> (B2 Word16
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V2 (S V Word)))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B2 Word16)
(V2 (S V Word))
forall a b. (a -> b) -> a -> b
$ Integer
-> (SType -> ExprM Text -> V2 (S V Word))
-> SType
-> B Word16
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V2 (S V Word))
forall (m :: * -> *) p b p b c.
Monad m =>
p
-> (SType -> ExprM Text -> b)
-> SType
-> p
-> StateT (Int, b, c) m b
makeVertexI Integer
2 SType -> ExprM Text -> V2 (S V Word)
forall c a. SType -> ExprM Text -> V2 (S c a)
vec2S (Int -> SType
STypeUVec Int
2) (B Word16
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V2 (S V Word)))
-> (B2 Word16 -> B Word16)
-> B2 Word16
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V2 (S V Word))
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. B2 Word16 -> B Word16
forall a. B2 a -> B a
unB2) ((B2 Word16 -> State [Int -> (IO VAOKey, IO ())] (V2 (S V Word)))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())]) (B2 Word16) (V2 (S V Word))
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((B2 Word16 -> State [Int -> (IO VAOKey, IO ())] (V2 (S V Word)))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())]) (B2 Word16) (V2 (S V Word)))
-> (B2 Word16 -> State [Int -> (IO VAOKey, IO ())] (V2 (S V Word)))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())]) (B2 Word16) (V2 (S V Word))
forall a b. (a -> b) -> a -> b
$ GLint
-> GLuint
-> B Word16
-> State [Int -> (IO VAOKey, IO ())] (V2 (S V Word))
forall (m :: * -> *) a a b.
(Monad m, Integral a) =>
GLint -> GLuint -> B a -> StateT [a -> (IO VAOKey, IO ())] m b
makeBindVertexI GLint
2 GLuint
forall a. (Eq a, Num a) => a
GL_UNSIGNED_SHORT (B Word16 -> State [Int -> (IO VAOKey, IO ())] (V2 (S V Word)))
-> (B2 Word16 -> B Word16)
-> B2 Word16
-> State [Int -> (IO VAOKey, IO ())] (V2 (S V Word))
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. B2 Word16 -> B Word16
forall a. B2 a -> B a
unB2)
instance VertexInput (B3 Float) where
type VertexFormat (B3 Float) = V3 VFloat
toVertex :: ToVertex (B3 Float) (VertexFormat (B3 Float))
toVertex = Kleisli (StateT (Ptr ()) IO) (B3 Float) (V3 PointSize)
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B3 Float)
(V3 PointSize)
-> Kleisli
(State [Int -> (IO VAOKey, IO ())]) (B3 Float) (V3 PointSize)
-> ToVertex (B3 Float) (V3 PointSize)
forall a b.
Kleisli (StateT (Ptr ()) IO) a b
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text))) a b
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) a b
-> ToVertex a b
ToVertex Kleisli (StateT (Ptr ()) IO) (B3 Float) (V3 PointSize)
forall b b. Kleisli (StateT (Ptr ()) IO) b b
noWriter ((B3 Float
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V3 PointSize))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B3 Float)
(V3 PointSize)
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((B3 Float
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V3 PointSize))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B3 Float)
(V3 PointSize))
-> (B3 Float
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V3 PointSize))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B3 Float)
(V3 PointSize)
forall a b. (a -> b) -> a -> b
$ Integer
-> (SType -> ExprM Text -> V3 PointSize)
-> SType
-> B Float
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V3 PointSize)
forall (m :: * -> *) p b p b c.
Monad m =>
p
-> (SType -> ExprM Text -> b)
-> SType
-> p
-> StateT (Int, b, c) m b
makeVertexF Integer
3 SType -> ExprM Text -> V3 PointSize
forall c a. SType -> ExprM Text -> V3 (S c a)
vec3S (Int -> SType
STypeVec Int
3) (B Float
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V3 PointSize))
-> (B3 Float -> B Float)
-> B3 Float
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V3 PointSize)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. B3 Float -> B Float
forall a. B3 a -> B a
unB3) ((B3 Float -> State [Int -> (IO VAOKey, IO ())] (V3 PointSize))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())]) (B3 Float) (V3 PointSize)
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((B3 Float -> State [Int -> (IO VAOKey, IO ())] (V3 PointSize))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())]) (B3 Float) (V3 PointSize))
-> (B3 Float -> State [Int -> (IO VAOKey, IO ())] (V3 PointSize))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())]) (B3 Float) (V3 PointSize)
forall a b. (a -> b) -> a -> b
$ GLint
-> GLuint
-> B Float
-> State [Int -> (IO VAOKey, IO ())] (V3 PointSize)
forall a b.
GLint
-> GLuint -> B a -> StateT [Int -> (IO VAOKey, IO ())] Identity b
makeBindVertexF GLint
3 GLuint
forall a. (Eq a, Num a) => a
GL_FLOAT (B Float -> State [Int -> (IO VAOKey, IO ())] (V3 PointSize))
-> (B3 Float -> B Float)
-> B3 Float
-> State [Int -> (IO VAOKey, IO ())] (V3 PointSize)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. B3 Float -> B Float
forall a. B3 a -> B a
unB3)
instance VertexInput (Normalized (B3 Int32)) where
type VertexFormat (Normalized (B3 Int32)) = V3 VFloat
toVertex :: ToVertex
(Normalized (B3 GLint)) (VertexFormat (Normalized (B3 GLint)))
toVertex = Kleisli (StateT (Ptr ()) IO) (Normalized (B3 GLint)) (V3 PointSize)
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B3 GLint))
(V3 PointSize)
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B3 GLint))
(V3 PointSize)
-> ToVertex (Normalized (B3 GLint)) (V3 PointSize)
forall a b.
Kleisli (StateT (Ptr ()) IO) a b
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text))) a b
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) a b
-> ToVertex a b
ToVertex Kleisli (StateT (Ptr ()) IO) (Normalized (B3 GLint)) (V3 PointSize)
forall b b. Kleisli (StateT (Ptr ()) IO) b b
noWriter ((Normalized (B3 GLint)
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V3 PointSize))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B3 GLint))
(V3 PointSize)
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((Normalized (B3 GLint)
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V3 PointSize))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B3 GLint))
(V3 PointSize))
-> (Normalized (B3 GLint)
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V3 PointSize))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B3 GLint))
(V3 PointSize)
forall a b. (a -> b) -> a -> b
$ Integer
-> (SType -> ExprM Text -> V3 PointSize)
-> SType
-> B GLint
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V3 PointSize)
forall (m :: * -> *) p b p b c.
Monad m =>
p
-> (SType -> ExprM Text -> b)
-> SType
-> p
-> StateT (Int, b, c) m b
makeVertexF Integer
3 SType -> ExprM Text -> V3 PointSize
forall c a. SType -> ExprM Text -> V3 (S c a)
vec3S (Int -> SType
STypeVec Int
3) (B GLint
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V3 PointSize))
-> (Normalized (B3 GLint) -> B GLint)
-> Normalized (B3 GLint)
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V3 PointSize)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. B3 GLint -> B GLint
forall a. B3 a -> B a
unB3 (B3 GLint -> B GLint)
-> (Normalized (B3 GLint) -> B3 GLint)
-> Normalized (B3 GLint)
-> B GLint
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Normalized (B3 GLint) -> B3 GLint
forall t. Normalized t -> t
unBnorm) ((Normalized (B3 GLint)
-> State [Int -> (IO VAOKey, IO ())] (V3 PointSize))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B3 GLint))
(V3 PointSize)
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((Normalized (B3 GLint)
-> State [Int -> (IO VAOKey, IO ())] (V3 PointSize))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B3 GLint))
(V3 PointSize))
-> (Normalized (B3 GLint)
-> State [Int -> (IO VAOKey, IO ())] (V3 PointSize))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B3 GLint))
(V3 PointSize)
forall a b. (a -> b) -> a -> b
$ GLint
-> GLuint
-> B GLint
-> State [Int -> (IO VAOKey, IO ())] (V3 PointSize)
forall a b.
GLint
-> GLuint -> B a -> StateT [Int -> (IO VAOKey, IO ())] Identity b
makeBindVertexFnorm GLint
3 GLuint
forall a. (Eq a, Num a) => a
GL_INT (B GLint -> State [Int -> (IO VAOKey, IO ())] (V3 PointSize))
-> (Normalized (B3 GLint) -> B GLint)
-> Normalized (B3 GLint)
-> State [Int -> (IO VAOKey, IO ())] (V3 PointSize)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. B3 GLint -> B GLint
forall a. B3 a -> B a
unB3 (B3 GLint -> B GLint)
-> (Normalized (B3 GLint) -> B3 GLint)
-> Normalized (B3 GLint)
-> B GLint
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Normalized (B3 GLint) -> B3 GLint
forall t. Normalized t -> t
unBnorm)
instance VertexInput (Normalized (B3 Int16)) where
type VertexFormat (Normalized (B3 Int16)) = V3 VFloat
toVertex :: ToVertex
(Normalized (B3 Int16)) (VertexFormat (Normalized (B3 Int16)))
toVertex = Kleisli (StateT (Ptr ()) IO) (Normalized (B3 Int16)) (V3 PointSize)
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B3 Int16))
(V3 PointSize)
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B3 Int16))
(V3 PointSize)
-> ToVertex (Normalized (B3 Int16)) (V3 PointSize)
forall a b.
Kleisli (StateT (Ptr ()) IO) a b
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text))) a b
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) a b
-> ToVertex a b
ToVertex Kleisli (StateT (Ptr ()) IO) (Normalized (B3 Int16)) (V3 PointSize)
forall b b. Kleisli (StateT (Ptr ()) IO) b b
noWriter ((Normalized (B3 Int16)
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V3 PointSize))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B3 Int16))
(V3 PointSize)
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((Normalized (B3 Int16)
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V3 PointSize))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B3 Int16))
(V3 PointSize))
-> (Normalized (B3 Int16)
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V3 PointSize))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B3 Int16))
(V3 PointSize)
forall a b. (a -> b) -> a -> b
$ Integer
-> (SType -> ExprM Text -> V3 PointSize)
-> SType
-> B Int16
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V3 PointSize)
forall (m :: * -> *) p b p b c.
Monad m =>
p
-> (SType -> ExprM Text -> b)
-> SType
-> p
-> StateT (Int, b, c) m b
makeVertexF Integer
3 SType -> ExprM Text -> V3 PointSize
forall c a. SType -> ExprM Text -> V3 (S c a)
vec3S (Int -> SType
STypeVec Int
3) (B Int16
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V3 PointSize))
-> (Normalized (B3 Int16) -> B Int16)
-> Normalized (B3 Int16)
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V3 PointSize)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. B3 Int16 -> B Int16
forall a. B3 a -> B a
unB3 (B3 Int16 -> B Int16)
-> (Normalized (B3 Int16) -> B3 Int16)
-> Normalized (B3 Int16)
-> B Int16
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Normalized (B3 Int16) -> B3 Int16
forall t. Normalized t -> t
unBnorm) ((Normalized (B3 Int16)
-> State [Int -> (IO VAOKey, IO ())] (V3 PointSize))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B3 Int16))
(V3 PointSize)
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((Normalized (B3 Int16)
-> State [Int -> (IO VAOKey, IO ())] (V3 PointSize))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B3 Int16))
(V3 PointSize))
-> (Normalized (B3 Int16)
-> State [Int -> (IO VAOKey, IO ())] (V3 PointSize))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B3 Int16))
(V3 PointSize)
forall a b. (a -> b) -> a -> b
$ GLint
-> GLuint
-> B Int16
-> State [Int -> (IO VAOKey, IO ())] (V3 PointSize)
forall a b.
GLint
-> GLuint -> B a -> StateT [Int -> (IO VAOKey, IO ())] Identity b
makeBindVertexFnorm GLint
3 GLuint
forall a. (Eq a, Num a) => a
GL_SHORT (B Int16 -> State [Int -> (IO VAOKey, IO ())] (V3 PointSize))
-> (Normalized (B3 Int16) -> B Int16)
-> Normalized (B3 Int16)
-> State [Int -> (IO VAOKey, IO ())] (V3 PointSize)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. B3 Int16 -> B Int16
forall a. B3 a -> B a
unB3 (B3 Int16 -> B Int16)
-> (Normalized (B3 Int16) -> B3 Int16)
-> Normalized (B3 Int16)
-> B Int16
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Normalized (B3 Int16) -> B3 Int16
forall t. Normalized t -> t
unBnorm)
instance VertexInput (Normalized (B3 Int8)) where
type VertexFormat (Normalized (B3 Int8)) = V3 VFloat
toVertex :: ToVertex
(Normalized (B3 Int8)) (VertexFormat (Normalized (B3 Int8)))
toVertex = Kleisli (StateT (Ptr ()) IO) (Normalized (B3 Int8)) (V3 PointSize)
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B3 Int8))
(V3 PointSize)
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B3 Int8))
(V3 PointSize)
-> ToVertex (Normalized (B3 Int8)) (V3 PointSize)
forall a b.
Kleisli (StateT (Ptr ()) IO) a b
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text))) a b
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) a b
-> ToVertex a b
ToVertex Kleisli (StateT (Ptr ()) IO) (Normalized (B3 Int8)) (V3 PointSize)
forall b b. Kleisli (StateT (Ptr ()) IO) b b
noWriter ((Normalized (B3 Int8)
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V3 PointSize))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B3 Int8))
(V3 PointSize)
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((Normalized (B3 Int8)
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V3 PointSize))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B3 Int8))
(V3 PointSize))
-> (Normalized (B3 Int8)
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V3 PointSize))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B3 Int8))
(V3 PointSize)
forall a b. (a -> b) -> a -> b
$ Integer
-> (SType -> ExprM Text -> V3 PointSize)
-> SType
-> B Int8
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V3 PointSize)
forall (m :: * -> *) p b p b c.
Monad m =>
p
-> (SType -> ExprM Text -> b)
-> SType
-> p
-> StateT (Int, b, c) m b
makeVertexF Integer
3 SType -> ExprM Text -> V3 PointSize
forall c a. SType -> ExprM Text -> V3 (S c a)
vec3S (Int -> SType
STypeVec Int
3) (B Int8
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V3 PointSize))
-> (Normalized (B3 Int8) -> B Int8)
-> Normalized (B3 Int8)
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V3 PointSize)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. B3 Int8 -> B Int8
forall a. B3 a -> B a
unB3 (B3 Int8 -> B Int8)
-> (Normalized (B3 Int8) -> B3 Int8)
-> Normalized (B3 Int8)
-> B Int8
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Normalized (B3 Int8) -> B3 Int8
forall t. Normalized t -> t
unBnorm) ((Normalized (B3 Int8)
-> State [Int -> (IO VAOKey, IO ())] (V3 PointSize))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B3 Int8))
(V3 PointSize)
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((Normalized (B3 Int8)
-> State [Int -> (IO VAOKey, IO ())] (V3 PointSize))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B3 Int8))
(V3 PointSize))
-> (Normalized (B3 Int8)
-> State [Int -> (IO VAOKey, IO ())] (V3 PointSize))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B3 Int8))
(V3 PointSize)
forall a b. (a -> b) -> a -> b
$ GLint
-> GLuint
-> B Int8
-> State [Int -> (IO VAOKey, IO ())] (V3 PointSize)
forall a b.
GLint
-> GLuint -> B a -> StateT [Int -> (IO VAOKey, IO ())] Identity b
makeBindVertexFnorm GLint
3 GLuint
forall a. (Eq a, Num a) => a
GL_BYTE (B Int8 -> State [Int -> (IO VAOKey, IO ())] (V3 PointSize))
-> (Normalized (B3 Int8) -> B Int8)
-> Normalized (B3 Int8)
-> State [Int -> (IO VAOKey, IO ())] (V3 PointSize)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. B3 Int8 -> B Int8
forall a. B3 a -> B a
unB3 (B3 Int8 -> B Int8)
-> (Normalized (B3 Int8) -> B3 Int8)
-> Normalized (B3 Int8)
-> B Int8
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Normalized (B3 Int8) -> B3 Int8
forall t. Normalized t -> t
unBnorm)
instance VertexInput (Normalized (B3 Word32)) where
type VertexFormat (Normalized (B3 Word32)) = V3 VFloat
toVertex :: ToVertex
(Normalized (B3 GLuint)) (VertexFormat (Normalized (B3 GLuint)))
toVertex = Kleisli
(StateT (Ptr ()) IO) (Normalized (B3 GLuint)) (V3 PointSize)
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B3 GLuint))
(V3 PointSize)
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B3 GLuint))
(V3 PointSize)
-> ToVertex (Normalized (B3 GLuint)) (V3 PointSize)
forall a b.
Kleisli (StateT (Ptr ()) IO) a b
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text))) a b
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) a b
-> ToVertex a b
ToVertex Kleisli
(StateT (Ptr ()) IO) (Normalized (B3 GLuint)) (V3 PointSize)
forall b b. Kleisli (StateT (Ptr ()) IO) b b
noWriter ((Normalized (B3 GLuint)
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V3 PointSize))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B3 GLuint))
(V3 PointSize)
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((Normalized (B3 GLuint)
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V3 PointSize))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B3 GLuint))
(V3 PointSize))
-> (Normalized (B3 GLuint)
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V3 PointSize))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B3 GLuint))
(V3 PointSize)
forall a b. (a -> b) -> a -> b
$ Integer
-> (SType -> ExprM Text -> V3 PointSize)
-> SType
-> B GLuint
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V3 PointSize)
forall (m :: * -> *) p b p b c.
Monad m =>
p
-> (SType -> ExprM Text -> b)
-> SType
-> p
-> StateT (Int, b, c) m b
makeVertexF Integer
3 SType -> ExprM Text -> V3 PointSize
forall c a. SType -> ExprM Text -> V3 (S c a)
vec3S (Int -> SType
STypeVec Int
3) (B GLuint
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V3 PointSize))
-> (Normalized (B3 GLuint) -> B GLuint)
-> Normalized (B3 GLuint)
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V3 PointSize)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. B3 GLuint -> B GLuint
forall a. B3 a -> B a
unB3 (B3 GLuint -> B GLuint)
-> (Normalized (B3 GLuint) -> B3 GLuint)
-> Normalized (B3 GLuint)
-> B GLuint
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Normalized (B3 GLuint) -> B3 GLuint
forall t. Normalized t -> t
unBnorm) ((Normalized (B3 GLuint)
-> State [Int -> (IO VAOKey, IO ())] (V3 PointSize))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B3 GLuint))
(V3 PointSize)
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((Normalized (B3 GLuint)
-> State [Int -> (IO VAOKey, IO ())] (V3 PointSize))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B3 GLuint))
(V3 PointSize))
-> (Normalized (B3 GLuint)
-> State [Int -> (IO VAOKey, IO ())] (V3 PointSize))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B3 GLuint))
(V3 PointSize)
forall a b. (a -> b) -> a -> b
$ GLint
-> GLuint
-> B GLuint
-> State [Int -> (IO VAOKey, IO ())] (V3 PointSize)
forall a b.
GLint
-> GLuint -> B a -> StateT [Int -> (IO VAOKey, IO ())] Identity b
makeBindVertexFnorm GLint
3 GLuint
forall a. (Eq a, Num a) => a
GL_UNSIGNED_INT (B GLuint -> State [Int -> (IO VAOKey, IO ())] (V3 PointSize))
-> (Normalized (B3 GLuint) -> B GLuint)
-> Normalized (B3 GLuint)
-> State [Int -> (IO VAOKey, IO ())] (V3 PointSize)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. B3 GLuint -> B GLuint
forall a. B3 a -> B a
unB3 (B3 GLuint -> B GLuint)
-> (Normalized (B3 GLuint) -> B3 GLuint)
-> Normalized (B3 GLuint)
-> B GLuint
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Normalized (B3 GLuint) -> B3 GLuint
forall t. Normalized t -> t
unBnorm)
instance VertexInput (Normalized (B3 Word16)) where
type VertexFormat (Normalized (B3 Word16)) = V3 VFloat
toVertex :: ToVertex
(Normalized (B3 Word16)) (VertexFormat (Normalized (B3 Word16)))
toVertex = Kleisli
(StateT (Ptr ()) IO) (Normalized (B3 Word16)) (V3 PointSize)
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B3 Word16))
(V3 PointSize)
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B3 Word16))
(V3 PointSize)
-> ToVertex (Normalized (B3 Word16)) (V3 PointSize)
forall a b.
Kleisli (StateT (Ptr ()) IO) a b
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text))) a b
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) a b
-> ToVertex a b
ToVertex Kleisli
(StateT (Ptr ()) IO) (Normalized (B3 Word16)) (V3 PointSize)
forall b b. Kleisli (StateT (Ptr ()) IO) b b
noWriter ((Normalized (B3 Word16)
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V3 PointSize))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B3 Word16))
(V3 PointSize)
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((Normalized (B3 Word16)
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V3 PointSize))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B3 Word16))
(V3 PointSize))
-> (Normalized (B3 Word16)
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V3 PointSize))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B3 Word16))
(V3 PointSize)
forall a b. (a -> b) -> a -> b
$ Integer
-> (SType -> ExprM Text -> V3 PointSize)
-> SType
-> B Word16
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V3 PointSize)
forall (m :: * -> *) p b p b c.
Monad m =>
p
-> (SType -> ExprM Text -> b)
-> SType
-> p
-> StateT (Int, b, c) m b
makeVertexF Integer
3 SType -> ExprM Text -> V3 PointSize
forall c a. SType -> ExprM Text -> V3 (S c a)
vec3S (Int -> SType
STypeVec Int
3) (B Word16
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V3 PointSize))
-> (Normalized (B3 Word16) -> B Word16)
-> Normalized (B3 Word16)
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V3 PointSize)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. B3 Word16 -> B Word16
forall a. B3 a -> B a
unB3 (B3 Word16 -> B Word16)
-> (Normalized (B3 Word16) -> B3 Word16)
-> Normalized (B3 Word16)
-> B Word16
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Normalized (B3 Word16) -> B3 Word16
forall t. Normalized t -> t
unBnorm) ((Normalized (B3 Word16)
-> State [Int -> (IO VAOKey, IO ())] (V3 PointSize))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B3 Word16))
(V3 PointSize)
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((Normalized (B3 Word16)
-> State [Int -> (IO VAOKey, IO ())] (V3 PointSize))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B3 Word16))
(V3 PointSize))
-> (Normalized (B3 Word16)
-> State [Int -> (IO VAOKey, IO ())] (V3 PointSize))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B3 Word16))
(V3 PointSize)
forall a b. (a -> b) -> a -> b
$ GLint
-> GLuint
-> B Word16
-> State [Int -> (IO VAOKey, IO ())] (V3 PointSize)
forall a b.
GLint
-> GLuint -> B a -> StateT [Int -> (IO VAOKey, IO ())] Identity b
makeBindVertexFnorm GLint
3 GLuint
forall a. (Eq a, Num a) => a
GL_UNSIGNED_SHORT (B Word16 -> State [Int -> (IO VAOKey, IO ())] (V3 PointSize))
-> (Normalized (B3 Word16) -> B Word16)
-> Normalized (B3 Word16)
-> State [Int -> (IO VAOKey, IO ())] (V3 PointSize)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. B3 Word16 -> B Word16
forall a. B3 a -> B a
unB3 (B3 Word16 -> B Word16)
-> (Normalized (B3 Word16) -> B3 Word16)
-> Normalized (B3 Word16)
-> B Word16
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Normalized (B3 Word16) -> B3 Word16
forall t. Normalized t -> t
unBnorm)
instance VertexInput (Normalized (B3 Word8)) where
type VertexFormat (Normalized (B3 Word8)) = V3 VFloat
toVertex :: ToVertex
(Normalized (B3 GLboolean))
(VertexFormat (Normalized (B3 GLboolean)))
toVertex = Kleisli
(StateT (Ptr ()) IO) (Normalized (B3 GLboolean)) (V3 PointSize)
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B3 GLboolean))
(V3 PointSize)
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B3 GLboolean))
(V3 PointSize)
-> ToVertex (Normalized (B3 GLboolean)) (V3 PointSize)
forall a b.
Kleisli (StateT (Ptr ()) IO) a b
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text))) a b
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) a b
-> ToVertex a b
ToVertex Kleisli
(StateT (Ptr ()) IO) (Normalized (B3 GLboolean)) (V3 PointSize)
forall b b. Kleisli (StateT (Ptr ()) IO) b b
noWriter ((Normalized (B3 GLboolean)
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V3 PointSize))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B3 GLboolean))
(V3 PointSize)
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((Normalized (B3 GLboolean)
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V3 PointSize))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B3 GLboolean))
(V3 PointSize))
-> (Normalized (B3 GLboolean)
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V3 PointSize))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B3 GLboolean))
(V3 PointSize)
forall a b. (a -> b) -> a -> b
$ Integer
-> (SType -> ExprM Text -> V3 PointSize)
-> SType
-> B GLboolean
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V3 PointSize)
forall (m :: * -> *) p b p b c.
Monad m =>
p
-> (SType -> ExprM Text -> b)
-> SType
-> p
-> StateT (Int, b, c) m b
makeVertexF Integer
3 SType -> ExprM Text -> V3 PointSize
forall c a. SType -> ExprM Text -> V3 (S c a)
vec3S (Int -> SType
STypeVec Int
3) (B GLboolean
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V3 PointSize))
-> (Normalized (B3 GLboolean) -> B GLboolean)
-> Normalized (B3 GLboolean)
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V3 PointSize)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. B3 GLboolean -> B GLboolean
forall a. B3 a -> B a
unB3 (B3 GLboolean -> B GLboolean)
-> (Normalized (B3 GLboolean) -> B3 GLboolean)
-> Normalized (B3 GLboolean)
-> B GLboolean
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Normalized (B3 GLboolean) -> B3 GLboolean
forall t. Normalized t -> t
unBnorm) ((Normalized (B3 GLboolean)
-> State [Int -> (IO VAOKey, IO ())] (V3 PointSize))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B3 GLboolean))
(V3 PointSize)
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((Normalized (B3 GLboolean)
-> State [Int -> (IO VAOKey, IO ())] (V3 PointSize))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B3 GLboolean))
(V3 PointSize))
-> (Normalized (B3 GLboolean)
-> State [Int -> (IO VAOKey, IO ())] (V3 PointSize))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B3 GLboolean))
(V3 PointSize)
forall a b. (a -> b) -> a -> b
$ GLint
-> GLuint
-> B GLboolean
-> State [Int -> (IO VAOKey, IO ())] (V3 PointSize)
forall a b.
GLint
-> GLuint -> B a -> StateT [Int -> (IO VAOKey, IO ())] Identity b
makeBindVertexFnorm GLint
3 GLuint
forall a. (Eq a, Num a) => a
GL_UNSIGNED_BYTE (B GLboolean -> State [Int -> (IO VAOKey, IO ())] (V3 PointSize))
-> (Normalized (B3 GLboolean) -> B GLboolean)
-> Normalized (B3 GLboolean)
-> State [Int -> (IO VAOKey, IO ())] (V3 PointSize)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. B3 GLboolean -> B GLboolean
forall a. B3 a -> B a
unB3 (B3 GLboolean -> B GLboolean)
-> (Normalized (B3 GLboolean) -> B3 GLboolean)
-> Normalized (B3 GLboolean)
-> B GLboolean
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Normalized (B3 GLboolean) -> B3 GLboolean
forall t. Normalized t -> t
unBnorm)
instance VertexInput (B3 Int32) where
type VertexFormat (B3 Int32) = V3 VInt
toVertex :: ToVertex (B3 GLint) (VertexFormat (B3 GLint))
toVertex = Kleisli (StateT (Ptr ()) IO) (B3 GLint) (V3 VInt)
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B3 GLint)
(V3 VInt)
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) (B3 GLint) (V3 VInt)
-> ToVertex (B3 GLint) (V3 VInt)
forall a b.
Kleisli (StateT (Ptr ()) IO) a b
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text))) a b
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) a b
-> ToVertex a b
ToVertex Kleisli (StateT (Ptr ()) IO) (B3 GLint) (V3 VInt)
forall b b. Kleisli (StateT (Ptr ()) IO) b b
noWriter ((B3 GLint
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) (V3 VInt))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B3 GLint)
(V3 VInt)
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((B3 GLint
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) (V3 VInt))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B3 GLint)
(V3 VInt))
-> (B3 GLint
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) (V3 VInt))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B3 GLint)
(V3 VInt)
forall a b. (a -> b) -> a -> b
$ Integer
-> (SType -> ExprM Text -> V3 VInt)
-> SType
-> B GLint
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) (V3 VInt)
forall (m :: * -> *) p b p b c.
Monad m =>
p
-> (SType -> ExprM Text -> b)
-> SType
-> p
-> StateT (Int, b, c) m b
makeVertexI Integer
3 SType -> ExprM Text -> V3 VInt
forall c a. SType -> ExprM Text -> V3 (S c a)
vec3S (Int -> SType
STypeIVec Int
3) (B GLint
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) (V3 VInt))
-> (B3 GLint -> B GLint)
-> B3 GLint
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) (V3 VInt)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. B3 GLint -> B GLint
forall a. B3 a -> B a
unB3) ((B3 GLint -> State [Int -> (IO VAOKey, IO ())] (V3 VInt))
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) (B3 GLint) (V3 VInt)
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((B3 GLint -> State [Int -> (IO VAOKey, IO ())] (V3 VInt))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())]) (B3 GLint) (V3 VInt))
-> (B3 GLint -> State [Int -> (IO VAOKey, IO ())] (V3 VInt))
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) (B3 GLint) (V3 VInt)
forall a b. (a -> b) -> a -> b
$ GLint
-> GLuint -> B GLint -> State [Int -> (IO VAOKey, IO ())] (V3 VInt)
forall (m :: * -> *) a a b.
(Monad m, Integral a) =>
GLint -> GLuint -> B a -> StateT [a -> (IO VAOKey, IO ())] m b
makeBindVertexI GLint
3 GLuint
forall a. (Eq a, Num a) => a
GL_INT (B GLint -> State [Int -> (IO VAOKey, IO ())] (V3 VInt))
-> (B3 GLint -> B GLint)
-> B3 GLint
-> State [Int -> (IO VAOKey, IO ())] (V3 VInt)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. B3 GLint -> B GLint
forall a. B3 a -> B a
unB3)
instance VertexInput (B3 Int16) where
type VertexFormat (B3 Int16) = V3 VInt
toVertex :: ToVertex (B3 Int16) (VertexFormat (B3 Int16))
toVertex = Kleisli (StateT (Ptr ()) IO) (B3 Int16) (V3 VInt)
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B3 Int16)
(V3 VInt)
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) (B3 Int16) (V3 VInt)
-> ToVertex (B3 Int16) (V3 VInt)
forall a b.
Kleisli (StateT (Ptr ()) IO) a b
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text))) a b
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) a b
-> ToVertex a b
ToVertex Kleisli (StateT (Ptr ()) IO) (B3 Int16) (V3 VInt)
forall b b. Kleisli (StateT (Ptr ()) IO) b b
noWriter ((B3 Int16
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) (V3 VInt))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B3 Int16)
(V3 VInt)
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((B3 Int16
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) (V3 VInt))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B3 Int16)
(V3 VInt))
-> (B3 Int16
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) (V3 VInt))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B3 Int16)
(V3 VInt)
forall a b. (a -> b) -> a -> b
$ Integer
-> (SType -> ExprM Text -> V3 VInt)
-> SType
-> B Int16
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) (V3 VInt)
forall (m :: * -> *) p b p b c.
Monad m =>
p
-> (SType -> ExprM Text -> b)
-> SType
-> p
-> StateT (Int, b, c) m b
makeVertexI Integer
3 SType -> ExprM Text -> V3 VInt
forall c a. SType -> ExprM Text -> V3 (S c a)
vec3S (Int -> SType
STypeIVec Int
3) (B Int16
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) (V3 VInt))
-> (B3 Int16 -> B Int16)
-> B3 Int16
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) (V3 VInt)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. B3 Int16 -> B Int16
forall a. B3 a -> B a
unB3) ((B3 Int16 -> State [Int -> (IO VAOKey, IO ())] (V3 VInt))
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) (B3 Int16) (V3 VInt)
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((B3 Int16 -> State [Int -> (IO VAOKey, IO ())] (V3 VInt))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())]) (B3 Int16) (V3 VInt))
-> (B3 Int16 -> State [Int -> (IO VAOKey, IO ())] (V3 VInt))
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) (B3 Int16) (V3 VInt)
forall a b. (a -> b) -> a -> b
$ GLint
-> GLuint -> B Int16 -> State [Int -> (IO VAOKey, IO ())] (V3 VInt)
forall (m :: * -> *) a a b.
(Monad m, Integral a) =>
GLint -> GLuint -> B a -> StateT [a -> (IO VAOKey, IO ())] m b
makeBindVertexI GLint
3 GLuint
forall a. (Eq a, Num a) => a
GL_SHORT (B Int16 -> State [Int -> (IO VAOKey, IO ())] (V3 VInt))
-> (B3 Int16 -> B Int16)
-> B3 Int16
-> State [Int -> (IO VAOKey, IO ())] (V3 VInt)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. B3 Int16 -> B Int16
forall a. B3 a -> B a
unB3)
instance VertexInput (B3 Int8) where
type VertexFormat (B3 Int8) = V3 VInt
toVertex :: ToVertex (B3 Int8) (VertexFormat (B3 Int8))
toVertex = Kleisli (StateT (Ptr ()) IO) (B3 Int8) (V3 VInt)
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B3 Int8)
(V3 VInt)
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) (B3 Int8) (V3 VInt)
-> ToVertex (B3 Int8) (V3 VInt)
forall a b.
Kleisli (StateT (Ptr ()) IO) a b
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text))) a b
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) a b
-> ToVertex a b
ToVertex Kleisli (StateT (Ptr ()) IO) (B3 Int8) (V3 VInt)
forall b b. Kleisli (StateT (Ptr ()) IO) b b
noWriter ((B3 Int8
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) (V3 VInt))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B3 Int8)
(V3 VInt)
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((B3 Int8
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) (V3 VInt))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B3 Int8)
(V3 VInt))
-> (B3 Int8
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) (V3 VInt))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B3 Int8)
(V3 VInt)
forall a b. (a -> b) -> a -> b
$ Integer
-> (SType -> ExprM Text -> V3 VInt)
-> SType
-> B Int8
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) (V3 VInt)
forall (m :: * -> *) p b p b c.
Monad m =>
p
-> (SType -> ExprM Text -> b)
-> SType
-> p
-> StateT (Int, b, c) m b
makeVertexI Integer
3 SType -> ExprM Text -> V3 VInt
forall c a. SType -> ExprM Text -> V3 (S c a)
vec3S (Int -> SType
STypeIVec Int
3) (B Int8
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) (V3 VInt))
-> (B3 Int8 -> B Int8)
-> B3 Int8
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) (V3 VInt)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. B3 Int8 -> B Int8
forall a. B3 a -> B a
unB3) ((B3 Int8 -> State [Int -> (IO VAOKey, IO ())] (V3 VInt))
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) (B3 Int8) (V3 VInt)
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((B3 Int8 -> State [Int -> (IO VAOKey, IO ())] (V3 VInt))
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) (B3 Int8) (V3 VInt))
-> (B3 Int8 -> State [Int -> (IO VAOKey, IO ())] (V3 VInt))
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) (B3 Int8) (V3 VInt)
forall a b. (a -> b) -> a -> b
$ GLint
-> GLuint -> B Int8 -> State [Int -> (IO VAOKey, IO ())] (V3 VInt)
forall (m :: * -> *) a a b.
(Monad m, Integral a) =>
GLint -> GLuint -> B a -> StateT [a -> (IO VAOKey, IO ())] m b
makeBindVertexI GLint
3 GLuint
forall a. (Eq a, Num a) => a
GL_BYTE (B Int8 -> State [Int -> (IO VAOKey, IO ())] (V3 VInt))
-> (B3 Int8 -> B Int8)
-> B3 Int8
-> State [Int -> (IO VAOKey, IO ())] (V3 VInt)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. B3 Int8 -> B Int8
forall a. B3 a -> B a
unB3)
instance VertexInput (B3 Word32) where
type VertexFormat (B3 Word32) = V3 VWord
toVertex :: ToVertex (B3 GLuint) (VertexFormat (B3 GLuint))
toVertex = Kleisli (StateT (Ptr ()) IO) (B3 GLuint) (V3 (S V Word))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B3 GLuint)
(V3 (S V Word))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())]) (B3 GLuint) (V3 (S V Word))
-> ToVertex (B3 GLuint) (V3 (S V Word))
forall a b.
Kleisli (StateT (Ptr ()) IO) a b
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text))) a b
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) a b
-> ToVertex a b
ToVertex Kleisli (StateT (Ptr ()) IO) (B3 GLuint) (V3 (S V Word))
forall b b. Kleisli (StateT (Ptr ()) IO) b b
noWriter ((B3 GLuint
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V3 (S V Word)))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B3 GLuint)
(V3 (S V Word))
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((B3 GLuint
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V3 (S V Word)))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B3 GLuint)
(V3 (S V Word)))
-> (B3 GLuint
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V3 (S V Word)))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B3 GLuint)
(V3 (S V Word))
forall a b. (a -> b) -> a -> b
$ Integer
-> (SType -> ExprM Text -> V3 (S V Word))
-> SType
-> B GLuint
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V3 (S V Word))
forall (m :: * -> *) p b p b c.
Monad m =>
p
-> (SType -> ExprM Text -> b)
-> SType
-> p
-> StateT (Int, b, c) m b
makeVertexI Integer
3 SType -> ExprM Text -> V3 (S V Word)
forall c a. SType -> ExprM Text -> V3 (S c a)
vec3S (Int -> SType
STypeUVec Int
3) (B GLuint
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V3 (S V Word)))
-> (B3 GLuint -> B GLuint)
-> B3 GLuint
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V3 (S V Word))
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. B3 GLuint -> B GLuint
forall a. B3 a -> B a
unB3) ((B3 GLuint -> State [Int -> (IO VAOKey, IO ())] (V3 (S V Word)))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())]) (B3 GLuint) (V3 (S V Word))
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((B3 GLuint -> State [Int -> (IO VAOKey, IO ())] (V3 (S V Word)))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())]) (B3 GLuint) (V3 (S V Word)))
-> (B3 GLuint -> State [Int -> (IO VAOKey, IO ())] (V3 (S V Word)))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())]) (B3 GLuint) (V3 (S V Word))
forall a b. (a -> b) -> a -> b
$ GLint
-> GLuint
-> B GLuint
-> State [Int -> (IO VAOKey, IO ())] (V3 (S V Word))
forall (m :: * -> *) a a b.
(Monad m, Integral a) =>
GLint -> GLuint -> B a -> StateT [a -> (IO VAOKey, IO ())] m b
makeBindVertexI GLint
3 GLuint
forall a. (Eq a, Num a) => a
GL_UNSIGNED_INT (B GLuint -> State [Int -> (IO VAOKey, IO ())] (V3 (S V Word)))
-> (B3 GLuint -> B GLuint)
-> B3 GLuint
-> State [Int -> (IO VAOKey, IO ())] (V3 (S V Word))
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. B3 GLuint -> B GLuint
forall a. B3 a -> B a
unB3)
instance VertexInput (B3 Word16) where
type VertexFormat (B3 Word16) = V3 VWord
toVertex :: ToVertex (B3 Word16) (VertexFormat (B3 Word16))
toVertex = Kleisli (StateT (Ptr ()) IO) (B3 Word16) (V3 (S V Word))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B3 Word16)
(V3 (S V Word))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())]) (B3 Word16) (V3 (S V Word))
-> ToVertex (B3 Word16) (V3 (S V Word))
forall a b.
Kleisli (StateT (Ptr ()) IO) a b
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text))) a b
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) a b
-> ToVertex a b
ToVertex Kleisli (StateT (Ptr ()) IO) (B3 Word16) (V3 (S V Word))
forall b b. Kleisli (StateT (Ptr ()) IO) b b
noWriter ((B3 Word16
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V3 (S V Word)))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B3 Word16)
(V3 (S V Word))
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((B3 Word16
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V3 (S V Word)))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B3 Word16)
(V3 (S V Word)))
-> (B3 Word16
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V3 (S V Word)))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B3 Word16)
(V3 (S V Word))
forall a b. (a -> b) -> a -> b
$ Integer
-> (SType -> ExprM Text -> V3 (S V Word))
-> SType
-> B Word16
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V3 (S V Word))
forall (m :: * -> *) p b p b c.
Monad m =>
p
-> (SType -> ExprM Text -> b)
-> SType
-> p
-> StateT (Int, b, c) m b
makeVertexI Integer
3 SType -> ExprM Text -> V3 (S V Word)
forall c a. SType -> ExprM Text -> V3 (S c a)
vec3S (Int -> SType
STypeUVec Int
3) (B Word16
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V3 (S V Word)))
-> (B3 Word16 -> B Word16)
-> B3 Word16
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V3 (S V Word))
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. B3 Word16 -> B Word16
forall a. B3 a -> B a
unB3) ((B3 Word16 -> State [Int -> (IO VAOKey, IO ())] (V3 (S V Word)))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())]) (B3 Word16) (V3 (S V Word))
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((B3 Word16 -> State [Int -> (IO VAOKey, IO ())] (V3 (S V Word)))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())]) (B3 Word16) (V3 (S V Word)))
-> (B3 Word16 -> State [Int -> (IO VAOKey, IO ())] (V3 (S V Word)))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())]) (B3 Word16) (V3 (S V Word))
forall a b. (a -> b) -> a -> b
$ GLint
-> GLuint
-> B Word16
-> State [Int -> (IO VAOKey, IO ())] (V3 (S V Word))
forall (m :: * -> *) a a b.
(Monad m, Integral a) =>
GLint -> GLuint -> B a -> StateT [a -> (IO VAOKey, IO ())] m b
makeBindVertexI GLint
3 GLuint
forall a. (Eq a, Num a) => a
GL_UNSIGNED_SHORT (B Word16 -> State [Int -> (IO VAOKey, IO ())] (V3 (S V Word)))
-> (B3 Word16 -> B Word16)
-> B3 Word16
-> State [Int -> (IO VAOKey, IO ())] (V3 (S V Word))
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. B3 Word16 -> B Word16
forall a. B3 a -> B a
unB3)
instance VertexInput (B3 Word8) where
type VertexFormat (B3 Word8) = V3 VWord
toVertex :: ToVertex (B3 GLboolean) (VertexFormat (B3 GLboolean))
toVertex = Kleisli (StateT (Ptr ()) IO) (B3 GLboolean) (V3 (S V Word))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B3 GLboolean)
(V3 (S V Word))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())]) (B3 GLboolean) (V3 (S V Word))
-> ToVertex (B3 GLboolean) (V3 (S V Word))
forall a b.
Kleisli (StateT (Ptr ()) IO) a b
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text))) a b
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) a b
-> ToVertex a b
ToVertex Kleisli (StateT (Ptr ()) IO) (B3 GLboolean) (V3 (S V Word))
forall b b. Kleisli (StateT (Ptr ()) IO) b b
noWriter ((B3 GLboolean
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V3 (S V Word)))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B3 GLboolean)
(V3 (S V Word))
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((B3 GLboolean
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V3 (S V Word)))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B3 GLboolean)
(V3 (S V Word)))
-> (B3 GLboolean
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V3 (S V Word)))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B3 GLboolean)
(V3 (S V Word))
forall a b. (a -> b) -> a -> b
$ Integer
-> (SType -> ExprM Text -> V3 (S V Word))
-> SType
-> B GLboolean
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V3 (S V Word))
forall (m :: * -> *) p b p b c.
Monad m =>
p
-> (SType -> ExprM Text -> b)
-> SType
-> p
-> StateT (Int, b, c) m b
makeVertexI Integer
3 SType -> ExprM Text -> V3 (S V Word)
forall c a. SType -> ExprM Text -> V3 (S c a)
vec3S (Int -> SType
STypeUVec Int
3) (B GLboolean
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V3 (S V Word)))
-> (B3 GLboolean -> B GLboolean)
-> B3 GLboolean
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V3 (S V Word))
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. B3 GLboolean -> B GLboolean
forall a. B3 a -> B a
unB3) ((B3 GLboolean -> State [Int -> (IO VAOKey, IO ())] (V3 (S V Word)))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())]) (B3 GLboolean) (V3 (S V Word))
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((B3 GLboolean
-> State [Int -> (IO VAOKey, IO ())] (V3 (S V Word)))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())]) (B3 GLboolean) (V3 (S V Word)))
-> (B3 GLboolean
-> State [Int -> (IO VAOKey, IO ())] (V3 (S V Word)))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())]) (B3 GLboolean) (V3 (S V Word))
forall a b. (a -> b) -> a -> b
$ GLint
-> GLuint
-> B GLboolean
-> State [Int -> (IO VAOKey, IO ())] (V3 (S V Word))
forall (m :: * -> *) a a b.
(Monad m, Integral a) =>
GLint -> GLuint -> B a -> StateT [a -> (IO VAOKey, IO ())] m b
makeBindVertexI GLint
3 GLuint
forall a. (Eq a, Num a) => a
GL_UNSIGNED_BYTE (B GLboolean -> State [Int -> (IO VAOKey, IO ())] (V3 (S V Word)))
-> (B3 GLboolean -> B GLboolean)
-> B3 GLboolean
-> State [Int -> (IO VAOKey, IO ())] (V3 (S V Word))
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. B3 GLboolean -> B GLboolean
forall a. B3 a -> B a
unB3)
instance VertexInput (B4 Float) where
type VertexFormat (B4 Float) = V4 VFloat
toVertex :: ToVertex (B4 Float) (VertexFormat (B4 Float))
toVertex = Kleisli (StateT (Ptr ()) IO) (B4 Float) (V4 PointSize)
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B4 Float)
(V4 PointSize)
-> Kleisli
(State [Int -> (IO VAOKey, IO ())]) (B4 Float) (V4 PointSize)
-> ToVertex (B4 Float) (V4 PointSize)
forall a b.
Kleisli (StateT (Ptr ()) IO) a b
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text))) a b
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) a b
-> ToVertex a b
ToVertex Kleisli (StateT (Ptr ()) IO) (B4 Float) (V4 PointSize)
forall b b. Kleisli (StateT (Ptr ()) IO) b b
noWriter ((B4 Float
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V4 PointSize))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B4 Float)
(V4 PointSize)
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((B4 Float
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V4 PointSize))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B4 Float)
(V4 PointSize))
-> (B4 Float
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V4 PointSize))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B4 Float)
(V4 PointSize)
forall a b. (a -> b) -> a -> b
$ Integer
-> (SType -> ExprM Text -> V4 PointSize)
-> SType
-> B Float
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V4 PointSize)
forall (m :: * -> *) p b p b c.
Monad m =>
p
-> (SType -> ExprM Text -> b)
-> SType
-> p
-> StateT (Int, b, c) m b
makeVertexF Integer
4 SType -> ExprM Text -> V4 PointSize
forall c a. SType -> ExprM Text -> V4 (S c a)
vec4S (Int -> SType
STypeVec Int
4) (B Float
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V4 PointSize))
-> (B4 Float -> B Float)
-> B4 Float
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V4 PointSize)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. B4 Float -> B Float
forall a. B4 a -> B a
unB4) ((B4 Float -> State [Int -> (IO VAOKey, IO ())] (V4 PointSize))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())]) (B4 Float) (V4 PointSize)
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((B4 Float -> State [Int -> (IO VAOKey, IO ())] (V4 PointSize))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())]) (B4 Float) (V4 PointSize))
-> (B4 Float -> State [Int -> (IO VAOKey, IO ())] (V4 PointSize))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())]) (B4 Float) (V4 PointSize)
forall a b. (a -> b) -> a -> b
$ GLint
-> GLuint
-> B Float
-> State [Int -> (IO VAOKey, IO ())] (V4 PointSize)
forall a b.
GLint
-> GLuint -> B a -> StateT [Int -> (IO VAOKey, IO ())] Identity b
makeBindVertexF GLint
4 GLuint
forall a. (Eq a, Num a) => a
GL_FLOAT (B Float -> State [Int -> (IO VAOKey, IO ())] (V4 PointSize))
-> (B4 Float -> B Float)
-> B4 Float
-> State [Int -> (IO VAOKey, IO ())] (V4 PointSize)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. B4 Float -> B Float
forall a. B4 a -> B a
unB4)
instance VertexInput (Normalized (B4 Int32)) where
type VertexFormat (Normalized (B4 Int32)) = V4 VFloat
toVertex :: ToVertex
(Normalized (B4 GLint)) (VertexFormat (Normalized (B4 GLint)))
toVertex = Kleisli (StateT (Ptr ()) IO) (Normalized (B4 GLint)) (V4 PointSize)
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B4 GLint))
(V4 PointSize)
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B4 GLint))
(V4 PointSize)
-> ToVertex (Normalized (B4 GLint)) (V4 PointSize)
forall a b.
Kleisli (StateT (Ptr ()) IO) a b
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text))) a b
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) a b
-> ToVertex a b
ToVertex Kleisli (StateT (Ptr ()) IO) (Normalized (B4 GLint)) (V4 PointSize)
forall b b. Kleisli (StateT (Ptr ()) IO) b b
noWriter ((Normalized (B4 GLint)
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V4 PointSize))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B4 GLint))
(V4 PointSize)
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((Normalized (B4 GLint)
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V4 PointSize))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B4 GLint))
(V4 PointSize))
-> (Normalized (B4 GLint)
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V4 PointSize))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B4 GLint))
(V4 PointSize)
forall a b. (a -> b) -> a -> b
$ Integer
-> (SType -> ExprM Text -> V4 PointSize)
-> SType
-> B GLint
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V4 PointSize)
forall (m :: * -> *) p b p b c.
Monad m =>
p
-> (SType -> ExprM Text -> b)
-> SType
-> p
-> StateT (Int, b, c) m b
makeVertexF Integer
4 SType -> ExprM Text -> V4 PointSize
forall c a. SType -> ExprM Text -> V4 (S c a)
vec4S (Int -> SType
STypeVec Int
4) (B GLint
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V4 PointSize))
-> (Normalized (B4 GLint) -> B GLint)
-> Normalized (B4 GLint)
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V4 PointSize)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. B4 GLint -> B GLint
forall a. B4 a -> B a
unB4 (B4 GLint -> B GLint)
-> (Normalized (B4 GLint) -> B4 GLint)
-> Normalized (B4 GLint)
-> B GLint
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Normalized (B4 GLint) -> B4 GLint
forall t. Normalized t -> t
unBnorm) ((Normalized (B4 GLint)
-> State [Int -> (IO VAOKey, IO ())] (V4 PointSize))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B4 GLint))
(V4 PointSize)
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((Normalized (B4 GLint)
-> State [Int -> (IO VAOKey, IO ())] (V4 PointSize))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B4 GLint))
(V4 PointSize))
-> (Normalized (B4 GLint)
-> State [Int -> (IO VAOKey, IO ())] (V4 PointSize))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B4 GLint))
(V4 PointSize)
forall a b. (a -> b) -> a -> b
$ GLint
-> GLuint
-> B GLint
-> State [Int -> (IO VAOKey, IO ())] (V4 PointSize)
forall a b.
GLint
-> GLuint -> B a -> StateT [Int -> (IO VAOKey, IO ())] Identity b
makeBindVertexFnorm GLint
4 GLuint
forall a. (Eq a, Num a) => a
GL_INT (B GLint -> State [Int -> (IO VAOKey, IO ())] (V4 PointSize))
-> (Normalized (B4 GLint) -> B GLint)
-> Normalized (B4 GLint)
-> State [Int -> (IO VAOKey, IO ())] (V4 PointSize)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. B4 GLint -> B GLint
forall a. B4 a -> B a
unB4 (B4 GLint -> B GLint)
-> (Normalized (B4 GLint) -> B4 GLint)
-> Normalized (B4 GLint)
-> B GLint
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Normalized (B4 GLint) -> B4 GLint
forall t. Normalized t -> t
unBnorm)
instance VertexInput (Normalized (B4 Int16)) where
type VertexFormat (Normalized (B4 Int16)) = V4 VFloat
toVertex :: ToVertex
(Normalized (B4 Int16)) (VertexFormat (Normalized (B4 Int16)))
toVertex = Kleisli (StateT (Ptr ()) IO) (Normalized (B4 Int16)) (V4 PointSize)
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B4 Int16))
(V4 PointSize)
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B4 Int16))
(V4 PointSize)
-> ToVertex (Normalized (B4 Int16)) (V4 PointSize)
forall a b.
Kleisli (StateT (Ptr ()) IO) a b
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text))) a b
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) a b
-> ToVertex a b
ToVertex Kleisli (StateT (Ptr ()) IO) (Normalized (B4 Int16)) (V4 PointSize)
forall b b. Kleisli (StateT (Ptr ()) IO) b b
noWriter ((Normalized (B4 Int16)
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V4 PointSize))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B4 Int16))
(V4 PointSize)
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((Normalized (B4 Int16)
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V4 PointSize))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B4 Int16))
(V4 PointSize))
-> (Normalized (B4 Int16)
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V4 PointSize))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B4 Int16))
(V4 PointSize)
forall a b. (a -> b) -> a -> b
$ Integer
-> (SType -> ExprM Text -> V4 PointSize)
-> SType
-> B Int16
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V4 PointSize)
forall (m :: * -> *) p b p b c.
Monad m =>
p
-> (SType -> ExprM Text -> b)
-> SType
-> p
-> StateT (Int, b, c) m b
makeVertexF Integer
4 SType -> ExprM Text -> V4 PointSize
forall c a. SType -> ExprM Text -> V4 (S c a)
vec4S (Int -> SType
STypeVec Int
4) (B Int16
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V4 PointSize))
-> (Normalized (B4 Int16) -> B Int16)
-> Normalized (B4 Int16)
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V4 PointSize)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. B4 Int16 -> B Int16
forall a. B4 a -> B a
unB4 (B4 Int16 -> B Int16)
-> (Normalized (B4 Int16) -> B4 Int16)
-> Normalized (B4 Int16)
-> B Int16
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Normalized (B4 Int16) -> B4 Int16
forall t. Normalized t -> t
unBnorm) ((Normalized (B4 Int16)
-> State [Int -> (IO VAOKey, IO ())] (V4 PointSize))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B4 Int16))
(V4 PointSize)
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((Normalized (B4 Int16)
-> State [Int -> (IO VAOKey, IO ())] (V4 PointSize))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B4 Int16))
(V4 PointSize))
-> (Normalized (B4 Int16)
-> State [Int -> (IO VAOKey, IO ())] (V4 PointSize))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B4 Int16))
(V4 PointSize)
forall a b. (a -> b) -> a -> b
$ GLint
-> GLuint
-> B Int16
-> State [Int -> (IO VAOKey, IO ())] (V4 PointSize)
forall a b.
GLint
-> GLuint -> B a -> StateT [Int -> (IO VAOKey, IO ())] Identity b
makeBindVertexFnorm GLint
4 GLuint
forall a. (Eq a, Num a) => a
GL_SHORT (B Int16 -> State [Int -> (IO VAOKey, IO ())] (V4 PointSize))
-> (Normalized (B4 Int16) -> B Int16)
-> Normalized (B4 Int16)
-> State [Int -> (IO VAOKey, IO ())] (V4 PointSize)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. B4 Int16 -> B Int16
forall a. B4 a -> B a
unB4 (B4 Int16 -> B Int16)
-> (Normalized (B4 Int16) -> B4 Int16)
-> Normalized (B4 Int16)
-> B Int16
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Normalized (B4 Int16) -> B4 Int16
forall t. Normalized t -> t
unBnorm)
instance VertexInput (Normalized (B4 Int8)) where
type VertexFormat (Normalized (B4 Int8)) = V4 VFloat
toVertex :: ToVertex
(Normalized (B4 Int8)) (VertexFormat (Normalized (B4 Int8)))
toVertex = Kleisli (StateT (Ptr ()) IO) (Normalized (B4 Int8)) (V4 PointSize)
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B4 Int8))
(V4 PointSize)
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B4 Int8))
(V4 PointSize)
-> ToVertex (Normalized (B4 Int8)) (V4 PointSize)
forall a b.
Kleisli (StateT (Ptr ()) IO) a b
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text))) a b
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) a b
-> ToVertex a b
ToVertex Kleisli (StateT (Ptr ()) IO) (Normalized (B4 Int8)) (V4 PointSize)
forall b b. Kleisli (StateT (Ptr ()) IO) b b
noWriter ((Normalized (B4 Int8)
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V4 PointSize))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B4 Int8))
(V4 PointSize)
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((Normalized (B4 Int8)
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V4 PointSize))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B4 Int8))
(V4 PointSize))
-> (Normalized (B4 Int8)
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V4 PointSize))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B4 Int8))
(V4 PointSize)
forall a b. (a -> b) -> a -> b
$ Integer
-> (SType -> ExprM Text -> V4 PointSize)
-> SType
-> B Int8
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V4 PointSize)
forall (m :: * -> *) p b p b c.
Monad m =>
p
-> (SType -> ExprM Text -> b)
-> SType
-> p
-> StateT (Int, b, c) m b
makeVertexF Integer
4 SType -> ExprM Text -> V4 PointSize
forall c a. SType -> ExprM Text -> V4 (S c a)
vec4S (Int -> SType
STypeVec Int
4) (B Int8
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V4 PointSize))
-> (Normalized (B4 Int8) -> B Int8)
-> Normalized (B4 Int8)
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V4 PointSize)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. B4 Int8 -> B Int8
forall a. B4 a -> B a
unB4 (B4 Int8 -> B Int8)
-> (Normalized (B4 Int8) -> B4 Int8)
-> Normalized (B4 Int8)
-> B Int8
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Normalized (B4 Int8) -> B4 Int8
forall t. Normalized t -> t
unBnorm) ((Normalized (B4 Int8)
-> State [Int -> (IO VAOKey, IO ())] (V4 PointSize))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B4 Int8))
(V4 PointSize)
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((Normalized (B4 Int8)
-> State [Int -> (IO VAOKey, IO ())] (V4 PointSize))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B4 Int8))
(V4 PointSize))
-> (Normalized (B4 Int8)
-> State [Int -> (IO VAOKey, IO ())] (V4 PointSize))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B4 Int8))
(V4 PointSize)
forall a b. (a -> b) -> a -> b
$ GLint
-> GLuint
-> B Int8
-> State [Int -> (IO VAOKey, IO ())] (V4 PointSize)
forall a b.
GLint
-> GLuint -> B a -> StateT [Int -> (IO VAOKey, IO ())] Identity b
makeBindVertexFnorm GLint
4 GLuint
forall a. (Eq a, Num a) => a
GL_BYTE (B Int8 -> State [Int -> (IO VAOKey, IO ())] (V4 PointSize))
-> (Normalized (B4 Int8) -> B Int8)
-> Normalized (B4 Int8)
-> State [Int -> (IO VAOKey, IO ())] (V4 PointSize)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. B4 Int8 -> B Int8
forall a. B4 a -> B a
unB4 (B4 Int8 -> B Int8)
-> (Normalized (B4 Int8) -> B4 Int8)
-> Normalized (B4 Int8)
-> B Int8
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Normalized (B4 Int8) -> B4 Int8
forall t. Normalized t -> t
unBnorm)
instance VertexInput (Normalized (B4 Word32)) where
type VertexFormat (Normalized (B4 Word32)) = V4 VFloat
toVertex :: ToVertex
(Normalized (B4 GLuint)) (VertexFormat (Normalized (B4 GLuint)))
toVertex = Kleisli
(StateT (Ptr ()) IO) (Normalized (B4 GLuint)) (V4 PointSize)
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B4 GLuint))
(V4 PointSize)
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B4 GLuint))
(V4 PointSize)
-> ToVertex (Normalized (B4 GLuint)) (V4 PointSize)
forall a b.
Kleisli (StateT (Ptr ()) IO) a b
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text))) a b
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) a b
-> ToVertex a b
ToVertex Kleisli
(StateT (Ptr ()) IO) (Normalized (B4 GLuint)) (V4 PointSize)
forall b b. Kleisli (StateT (Ptr ()) IO) b b
noWriter ((Normalized (B4 GLuint)
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V4 PointSize))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B4 GLuint))
(V4 PointSize)
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((Normalized (B4 GLuint)
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V4 PointSize))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B4 GLuint))
(V4 PointSize))
-> (Normalized (B4 GLuint)
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V4 PointSize))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B4 GLuint))
(V4 PointSize)
forall a b. (a -> b) -> a -> b
$ Integer
-> (SType -> ExprM Text -> V4 PointSize)
-> SType
-> B GLuint
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V4 PointSize)
forall (m :: * -> *) p b p b c.
Monad m =>
p
-> (SType -> ExprM Text -> b)
-> SType
-> p
-> StateT (Int, b, c) m b
makeVertexF Integer
4 SType -> ExprM Text -> V4 PointSize
forall c a. SType -> ExprM Text -> V4 (S c a)
vec4S (Int -> SType
STypeVec Int
4) (B GLuint
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V4 PointSize))
-> (Normalized (B4 GLuint) -> B GLuint)
-> Normalized (B4 GLuint)
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V4 PointSize)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. B4 GLuint -> B GLuint
forall a. B4 a -> B a
unB4 (B4 GLuint -> B GLuint)
-> (Normalized (B4 GLuint) -> B4 GLuint)
-> Normalized (B4 GLuint)
-> B GLuint
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Normalized (B4 GLuint) -> B4 GLuint
forall t. Normalized t -> t
unBnorm) ((Normalized (B4 GLuint)
-> State [Int -> (IO VAOKey, IO ())] (V4 PointSize))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B4 GLuint))
(V4 PointSize)
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((Normalized (B4 GLuint)
-> State [Int -> (IO VAOKey, IO ())] (V4 PointSize))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B4 GLuint))
(V4 PointSize))
-> (Normalized (B4 GLuint)
-> State [Int -> (IO VAOKey, IO ())] (V4 PointSize))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B4 GLuint))
(V4 PointSize)
forall a b. (a -> b) -> a -> b
$ GLint
-> GLuint
-> B GLuint
-> State [Int -> (IO VAOKey, IO ())] (V4 PointSize)
forall a b.
GLint
-> GLuint -> B a -> StateT [Int -> (IO VAOKey, IO ())] Identity b
makeBindVertexFnorm GLint
4 GLuint
forall a. (Eq a, Num a) => a
GL_UNSIGNED_INT (B GLuint -> State [Int -> (IO VAOKey, IO ())] (V4 PointSize))
-> (Normalized (B4 GLuint) -> B GLuint)
-> Normalized (B4 GLuint)
-> State [Int -> (IO VAOKey, IO ())] (V4 PointSize)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. B4 GLuint -> B GLuint
forall a. B4 a -> B a
unB4 (B4 GLuint -> B GLuint)
-> (Normalized (B4 GLuint) -> B4 GLuint)
-> Normalized (B4 GLuint)
-> B GLuint
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Normalized (B4 GLuint) -> B4 GLuint
forall t. Normalized t -> t
unBnorm)
instance VertexInput (Normalized (B4 Word16)) where
type VertexFormat (Normalized (B4 Word16)) = V4 VFloat
toVertex :: ToVertex
(Normalized (B4 Word16)) (VertexFormat (Normalized (B4 Word16)))
toVertex = Kleisli
(StateT (Ptr ()) IO) (Normalized (B4 Word16)) (V4 PointSize)
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B4 Word16))
(V4 PointSize)
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B4 Word16))
(V4 PointSize)
-> ToVertex (Normalized (B4 Word16)) (V4 PointSize)
forall a b.
Kleisli (StateT (Ptr ()) IO) a b
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text))) a b
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) a b
-> ToVertex a b
ToVertex Kleisli
(StateT (Ptr ()) IO) (Normalized (B4 Word16)) (V4 PointSize)
forall b b. Kleisli (StateT (Ptr ()) IO) b b
noWriter ((Normalized (B4 Word16)
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V4 PointSize))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B4 Word16))
(V4 PointSize)
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((Normalized (B4 Word16)
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V4 PointSize))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B4 Word16))
(V4 PointSize))
-> (Normalized (B4 Word16)
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V4 PointSize))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B4 Word16))
(V4 PointSize)
forall a b. (a -> b) -> a -> b
$ Integer
-> (SType -> ExprM Text -> V4 PointSize)
-> SType
-> B Word16
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V4 PointSize)
forall (m :: * -> *) p b p b c.
Monad m =>
p
-> (SType -> ExprM Text -> b)
-> SType
-> p
-> StateT (Int, b, c) m b
makeVertexF Integer
4 SType -> ExprM Text -> V4 PointSize
forall c a. SType -> ExprM Text -> V4 (S c a)
vec4S (Int -> SType
STypeVec Int
4) (B Word16
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V4 PointSize))
-> (Normalized (B4 Word16) -> B Word16)
-> Normalized (B4 Word16)
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V4 PointSize)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. B4 Word16 -> B Word16
forall a. B4 a -> B a
unB4 (B4 Word16 -> B Word16)
-> (Normalized (B4 Word16) -> B4 Word16)
-> Normalized (B4 Word16)
-> B Word16
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Normalized (B4 Word16) -> B4 Word16
forall t. Normalized t -> t
unBnorm) ((Normalized (B4 Word16)
-> State [Int -> (IO VAOKey, IO ())] (V4 PointSize))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B4 Word16))
(V4 PointSize)
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((Normalized (B4 Word16)
-> State [Int -> (IO VAOKey, IO ())] (V4 PointSize))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B4 Word16))
(V4 PointSize))
-> (Normalized (B4 Word16)
-> State [Int -> (IO VAOKey, IO ())] (V4 PointSize))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B4 Word16))
(V4 PointSize)
forall a b. (a -> b) -> a -> b
$ GLint
-> GLuint
-> B Word16
-> State [Int -> (IO VAOKey, IO ())] (V4 PointSize)
forall a b.
GLint
-> GLuint -> B a -> StateT [Int -> (IO VAOKey, IO ())] Identity b
makeBindVertexFnorm GLint
4 GLuint
forall a. (Eq a, Num a) => a
GL_UNSIGNED_SHORT (B Word16 -> State [Int -> (IO VAOKey, IO ())] (V4 PointSize))
-> (Normalized (B4 Word16) -> B Word16)
-> Normalized (B4 Word16)
-> State [Int -> (IO VAOKey, IO ())] (V4 PointSize)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. B4 Word16 -> B Word16
forall a. B4 a -> B a
unB4 (B4 Word16 -> B Word16)
-> (Normalized (B4 Word16) -> B4 Word16)
-> Normalized (B4 Word16)
-> B Word16
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Normalized (B4 Word16) -> B4 Word16
forall t. Normalized t -> t
unBnorm)
instance VertexInput (Normalized (B4 Word8)) where
type VertexFormat (Normalized (B4 Word8)) = V4 VFloat
toVertex :: ToVertex
(Normalized (B4 GLboolean))
(VertexFormat (Normalized (B4 GLboolean)))
toVertex = Kleisli
(StateT (Ptr ()) IO) (Normalized (B4 GLboolean)) (V4 PointSize)
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B4 GLboolean))
(V4 PointSize)
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B4 GLboolean))
(V4 PointSize)
-> ToVertex (Normalized (B4 GLboolean)) (V4 PointSize)
forall a b.
Kleisli (StateT (Ptr ()) IO) a b
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text))) a b
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) a b
-> ToVertex a b
ToVertex Kleisli
(StateT (Ptr ()) IO) (Normalized (B4 GLboolean)) (V4 PointSize)
forall b b. Kleisli (StateT (Ptr ()) IO) b b
noWriter ((Normalized (B4 GLboolean)
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V4 PointSize))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B4 GLboolean))
(V4 PointSize)
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((Normalized (B4 GLboolean)
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V4 PointSize))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B4 GLboolean))
(V4 PointSize))
-> (Normalized (B4 GLboolean)
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V4 PointSize))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(Normalized (B4 GLboolean))
(V4 PointSize)
forall a b. (a -> b) -> a -> b
$ Integer
-> (SType -> ExprM Text -> V4 PointSize)
-> SType
-> B GLboolean
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V4 PointSize)
forall (m :: * -> *) p b p b c.
Monad m =>
p
-> (SType -> ExprM Text -> b)
-> SType
-> p
-> StateT (Int, b, c) m b
makeVertexF Integer
4 SType -> ExprM Text -> V4 PointSize
forall c a. SType -> ExprM Text -> V4 (S c a)
vec4S (Int -> SType
STypeVec Int
4) (B GLboolean
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V4 PointSize))
-> (Normalized (B4 GLboolean) -> B GLboolean)
-> Normalized (B4 GLboolean)
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V4 PointSize)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. B4 GLboolean -> B GLboolean
forall a. B4 a -> B a
unB4 (B4 GLboolean -> B GLboolean)
-> (Normalized (B4 GLboolean) -> B4 GLboolean)
-> Normalized (B4 GLboolean)
-> B GLboolean
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Normalized (B4 GLboolean) -> B4 GLboolean
forall t. Normalized t -> t
unBnorm) ((Normalized (B4 GLboolean)
-> State [Int -> (IO VAOKey, IO ())] (V4 PointSize))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B4 GLboolean))
(V4 PointSize)
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((Normalized (B4 GLboolean)
-> State [Int -> (IO VAOKey, IO ())] (V4 PointSize))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B4 GLboolean))
(V4 PointSize))
-> (Normalized (B4 GLboolean)
-> State [Int -> (IO VAOKey, IO ())] (V4 PointSize))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())])
(Normalized (B4 GLboolean))
(V4 PointSize)
forall a b. (a -> b) -> a -> b
$ GLint
-> GLuint
-> B GLboolean
-> State [Int -> (IO VAOKey, IO ())] (V4 PointSize)
forall a b.
GLint
-> GLuint -> B a -> StateT [Int -> (IO VAOKey, IO ())] Identity b
makeBindVertexFnorm GLint
4 GLuint
forall a. (Eq a, Num a) => a
GL_UNSIGNED_BYTE (B GLboolean -> State [Int -> (IO VAOKey, IO ())] (V4 PointSize))
-> (Normalized (B4 GLboolean) -> B GLboolean)
-> Normalized (B4 GLboolean)
-> State [Int -> (IO VAOKey, IO ())] (V4 PointSize)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. B4 GLboolean -> B GLboolean
forall a. B4 a -> B a
unB4 (B4 GLboolean -> B GLboolean)
-> (Normalized (B4 GLboolean) -> B4 GLboolean)
-> Normalized (B4 GLboolean)
-> B GLboolean
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Normalized (B4 GLboolean) -> B4 GLboolean
forall t. Normalized t -> t
unBnorm)
instance VertexInput (B4 Int32) where
type VertexFormat (B4 Int32) = V4 VInt
toVertex :: ToVertex (B4 GLint) (VertexFormat (B4 GLint))
toVertex = Kleisli (StateT (Ptr ()) IO) (B4 GLint) (V4 VInt)
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B4 GLint)
(V4 VInt)
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) (B4 GLint) (V4 VInt)
-> ToVertex (B4 GLint) (V4 VInt)
forall a b.
Kleisli (StateT (Ptr ()) IO) a b
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text))) a b
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) a b
-> ToVertex a b
ToVertex Kleisli (StateT (Ptr ()) IO) (B4 GLint) (V4 VInt)
forall b b. Kleisli (StateT (Ptr ()) IO) b b
noWriter ((B4 GLint
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) (V4 VInt))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B4 GLint)
(V4 VInt)
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((B4 GLint
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) (V4 VInt))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B4 GLint)
(V4 VInt))
-> (B4 GLint
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) (V4 VInt))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B4 GLint)
(V4 VInt)
forall a b. (a -> b) -> a -> b
$ Integer
-> (SType -> ExprM Text -> V4 VInt)
-> SType
-> B GLint
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) (V4 VInt)
forall (m :: * -> *) p b p b c.
Monad m =>
p
-> (SType -> ExprM Text -> b)
-> SType
-> p
-> StateT (Int, b, c) m b
makeVertexI Integer
4 SType -> ExprM Text -> V4 VInt
forall c a. SType -> ExprM Text -> V4 (S c a)
vec4S (Int -> SType
STypeIVec Int
4) (B GLint
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) (V4 VInt))
-> (B4 GLint -> B GLint)
-> B4 GLint
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) (V4 VInt)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. B4 GLint -> B GLint
forall a. B4 a -> B a
unB4) ((B4 GLint -> State [Int -> (IO VAOKey, IO ())] (V4 VInt))
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) (B4 GLint) (V4 VInt)
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((B4 GLint -> State [Int -> (IO VAOKey, IO ())] (V4 VInt))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())]) (B4 GLint) (V4 VInt))
-> (B4 GLint -> State [Int -> (IO VAOKey, IO ())] (V4 VInt))
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) (B4 GLint) (V4 VInt)
forall a b. (a -> b) -> a -> b
$ GLint
-> GLuint -> B GLint -> State [Int -> (IO VAOKey, IO ())] (V4 VInt)
forall (m :: * -> *) a a b.
(Monad m, Integral a) =>
GLint -> GLuint -> B a -> StateT [a -> (IO VAOKey, IO ())] m b
makeBindVertexI GLint
4 GLuint
forall a. (Eq a, Num a) => a
GL_INT (B GLint -> State [Int -> (IO VAOKey, IO ())] (V4 VInt))
-> (B4 GLint -> B GLint)
-> B4 GLint
-> State [Int -> (IO VAOKey, IO ())] (V4 VInt)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. B4 GLint -> B GLint
forall a. B4 a -> B a
unB4)
instance VertexInput (B4 Int16) where
type VertexFormat (B4 Int16) = V4 VInt
toVertex :: ToVertex (B4 Int16) (VertexFormat (B4 Int16))
toVertex = Kleisli (StateT (Ptr ()) IO) (B4 Int16) (V4 VInt)
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B4 Int16)
(V4 VInt)
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) (B4 Int16) (V4 VInt)
-> ToVertex (B4 Int16) (V4 VInt)
forall a b.
Kleisli (StateT (Ptr ()) IO) a b
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text))) a b
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) a b
-> ToVertex a b
ToVertex Kleisli (StateT (Ptr ()) IO) (B4 Int16) (V4 VInt)
forall b b. Kleisli (StateT (Ptr ()) IO) b b
noWriter ((B4 Int16
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) (V4 VInt))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B4 Int16)
(V4 VInt)
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((B4 Int16
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) (V4 VInt))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B4 Int16)
(V4 VInt))
-> (B4 Int16
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) (V4 VInt))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B4 Int16)
(V4 VInt)
forall a b. (a -> b) -> a -> b
$ Integer
-> (SType -> ExprM Text -> V4 VInt)
-> SType
-> B Int16
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) (V4 VInt)
forall (m :: * -> *) p b p b c.
Monad m =>
p
-> (SType -> ExprM Text -> b)
-> SType
-> p
-> StateT (Int, b, c) m b
makeVertexI Integer
4 SType -> ExprM Text -> V4 VInt
forall c a. SType -> ExprM Text -> V4 (S c a)
vec4S (Int -> SType
STypeIVec Int
4) (B Int16
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) (V4 VInt))
-> (B4 Int16 -> B Int16)
-> B4 Int16
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) (V4 VInt)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. B4 Int16 -> B Int16
forall a. B4 a -> B a
unB4) ((B4 Int16 -> State [Int -> (IO VAOKey, IO ())] (V4 VInt))
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) (B4 Int16) (V4 VInt)
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((B4 Int16 -> State [Int -> (IO VAOKey, IO ())] (V4 VInt))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())]) (B4 Int16) (V4 VInt))
-> (B4 Int16 -> State [Int -> (IO VAOKey, IO ())] (V4 VInt))
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) (B4 Int16) (V4 VInt)
forall a b. (a -> b) -> a -> b
$ GLint
-> GLuint -> B Int16 -> State [Int -> (IO VAOKey, IO ())] (V4 VInt)
forall (m :: * -> *) a a b.
(Monad m, Integral a) =>
GLint -> GLuint -> B a -> StateT [a -> (IO VAOKey, IO ())] m b
makeBindVertexI GLint
4 GLuint
forall a. (Eq a, Num a) => a
GL_SHORT (B Int16 -> State [Int -> (IO VAOKey, IO ())] (V4 VInt))
-> (B4 Int16 -> B Int16)
-> B4 Int16
-> State [Int -> (IO VAOKey, IO ())] (V4 VInt)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. B4 Int16 -> B Int16
forall a. B4 a -> B a
unB4)
instance VertexInput (B4 Int8) where
type VertexFormat (B4 Int8) = V4 VInt
toVertex :: ToVertex (B4 Int8) (VertexFormat (B4 Int8))
toVertex = Kleisli (StateT (Ptr ()) IO) (B4 Int8) (V4 VInt)
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B4 Int8)
(V4 VInt)
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) (B4 Int8) (V4 VInt)
-> ToVertex (B4 Int8) (V4 VInt)
forall a b.
Kleisli (StateT (Ptr ()) IO) a b
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text))) a b
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) a b
-> ToVertex a b
ToVertex Kleisli (StateT (Ptr ()) IO) (B4 Int8) (V4 VInt)
forall b b. Kleisli (StateT (Ptr ()) IO) b b
noWriter ((B4 Int8
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) (V4 VInt))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B4 Int8)
(V4 VInt)
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((B4 Int8
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) (V4 VInt))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B4 Int8)
(V4 VInt))
-> (B4 Int8
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) (V4 VInt))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B4 Int8)
(V4 VInt)
forall a b. (a -> b) -> a -> b
$ Integer
-> (SType -> ExprM Text -> V4 VInt)
-> SType
-> B Int8
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) (V4 VInt)
forall (m :: * -> *) p b p b c.
Monad m =>
p
-> (SType -> ExprM Text -> b)
-> SType
-> p
-> StateT (Int, b, c) m b
makeVertexI Integer
4 SType -> ExprM Text -> V4 VInt
forall c a. SType -> ExprM Text -> V4 (S c a)
vec4S (Int -> SType
STypeIVec Int
4) (B Int8
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) (V4 VInt))
-> (B4 Int8 -> B Int8)
-> B4 Int8
-> StateT
(Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)) (V4 VInt)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. B4 Int8 -> B Int8
forall a. B4 a -> B a
unB4) ((B4 Int8 -> State [Int -> (IO VAOKey, IO ())] (V4 VInt))
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) (B4 Int8) (V4 VInt)
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((B4 Int8 -> State [Int -> (IO VAOKey, IO ())] (V4 VInt))
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) (B4 Int8) (V4 VInt))
-> (B4 Int8 -> State [Int -> (IO VAOKey, IO ())] (V4 VInt))
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) (B4 Int8) (V4 VInt)
forall a b. (a -> b) -> a -> b
$ GLint
-> GLuint -> B Int8 -> State [Int -> (IO VAOKey, IO ())] (V4 VInt)
forall (m :: * -> *) a a b.
(Monad m, Integral a) =>
GLint -> GLuint -> B a -> StateT [a -> (IO VAOKey, IO ())] m b
makeBindVertexI GLint
4 GLuint
forall a. (Eq a, Num a) => a
GL_BYTE (B Int8 -> State [Int -> (IO VAOKey, IO ())] (V4 VInt))
-> (B4 Int8 -> B Int8)
-> B4 Int8
-> State [Int -> (IO VAOKey, IO ())] (V4 VInt)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. B4 Int8 -> B Int8
forall a. B4 a -> B a
unB4)
instance VertexInput (B4 Word32) where
type VertexFormat (B4 Word32) = V4 VWord
toVertex :: ToVertex (B4 GLuint) (VertexFormat (B4 GLuint))
toVertex = Kleisli (StateT (Ptr ()) IO) (B4 GLuint) (V4 (S V Word))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B4 GLuint)
(V4 (S V Word))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())]) (B4 GLuint) (V4 (S V Word))
-> ToVertex (B4 GLuint) (V4 (S V Word))
forall a b.
Kleisli (StateT (Ptr ()) IO) a b
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text))) a b
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) a b
-> ToVertex a b
ToVertex Kleisli (StateT (Ptr ()) IO) (B4 GLuint) (V4 (S V Word))
forall b b. Kleisli (StateT (Ptr ()) IO) b b
noWriter ((B4 GLuint
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V4 (S V Word)))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B4 GLuint)
(V4 (S V Word))
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((B4 GLuint
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V4 (S V Word)))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B4 GLuint)
(V4 (S V Word)))
-> (B4 GLuint
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V4 (S V Word)))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B4 GLuint)
(V4 (S V Word))
forall a b. (a -> b) -> a -> b
$ Integer
-> (SType -> ExprM Text -> V4 (S V Word))
-> SType
-> B GLuint
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V4 (S V Word))
forall (m :: * -> *) p b p b c.
Monad m =>
p
-> (SType -> ExprM Text -> b)
-> SType
-> p
-> StateT (Int, b, c) m b
makeVertexI Integer
4 SType -> ExprM Text -> V4 (S V Word)
forall c a. SType -> ExprM Text -> V4 (S c a)
vec4S (Int -> SType
STypeUVec Int
4) (B GLuint
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V4 (S V Word)))
-> (B4 GLuint -> B GLuint)
-> B4 GLuint
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V4 (S V Word))
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. B4 GLuint -> B GLuint
forall a. B4 a -> B a
unB4) ((B4 GLuint -> State [Int -> (IO VAOKey, IO ())] (V4 (S V Word)))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())]) (B4 GLuint) (V4 (S V Word))
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((B4 GLuint -> State [Int -> (IO VAOKey, IO ())] (V4 (S V Word)))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())]) (B4 GLuint) (V4 (S V Word)))
-> (B4 GLuint -> State [Int -> (IO VAOKey, IO ())] (V4 (S V Word)))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())]) (B4 GLuint) (V4 (S V Word))
forall a b. (a -> b) -> a -> b
$ GLint
-> GLuint
-> B GLuint
-> State [Int -> (IO VAOKey, IO ())] (V4 (S V Word))
forall (m :: * -> *) a a b.
(Monad m, Integral a) =>
GLint -> GLuint -> B a -> StateT [a -> (IO VAOKey, IO ())] m b
makeBindVertexI GLint
4 GLuint
forall a. (Eq a, Num a) => a
GL_UNSIGNED_INT (B GLuint -> State [Int -> (IO VAOKey, IO ())] (V4 (S V Word)))
-> (B4 GLuint -> B GLuint)
-> B4 GLuint
-> State [Int -> (IO VAOKey, IO ())] (V4 (S V Word))
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. B4 GLuint -> B GLuint
forall a. B4 a -> B a
unB4)
instance VertexInput (B4 Word16) where
type VertexFormat (B4 Word16) = V4 VWord
toVertex :: ToVertex (B4 Word16) (VertexFormat (B4 Word16))
toVertex = Kleisli (StateT (Ptr ()) IO) (B4 Word16) (V4 (S V Word))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B4 Word16)
(V4 (S V Word))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())]) (B4 Word16) (V4 (S V Word))
-> ToVertex (B4 Word16) (V4 (S V Word))
forall a b.
Kleisli (StateT (Ptr ()) IO) a b
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text))) a b
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) a b
-> ToVertex a b
ToVertex Kleisli (StateT (Ptr ()) IO) (B4 Word16) (V4 (S V Word))
forall b b. Kleisli (StateT (Ptr ()) IO) b b
noWriter ((B4 Word16
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V4 (S V Word)))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B4 Word16)
(V4 (S V Word))
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((B4 Word16
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V4 (S V Word)))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B4 Word16)
(V4 (S V Word)))
-> (B4 Word16
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V4 (S V Word)))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B4 Word16)
(V4 (S V Word))
forall a b. (a -> b) -> a -> b
$ Integer
-> (SType -> ExprM Text -> V4 (S V Word))
-> SType
-> B Word16
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V4 (S V Word))
forall (m :: * -> *) p b p b c.
Monad m =>
p
-> (SType -> ExprM Text -> b)
-> SType
-> p
-> StateT (Int, b, c) m b
makeVertexI Integer
4 SType -> ExprM Text -> V4 (S V Word)
forall c a. SType -> ExprM Text -> V4 (S c a)
vec4S (Int -> SType
STypeUVec Int
4) (B Word16
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V4 (S V Word)))
-> (B4 Word16 -> B Word16)
-> B4 Word16
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V4 (S V Word))
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. B4 Word16 -> B Word16
forall a. B4 a -> B a
unB4) ((B4 Word16 -> State [Int -> (IO VAOKey, IO ())] (V4 (S V Word)))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())]) (B4 Word16) (V4 (S V Word))
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((B4 Word16 -> State [Int -> (IO VAOKey, IO ())] (V4 (S V Word)))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())]) (B4 Word16) (V4 (S V Word)))
-> (B4 Word16 -> State [Int -> (IO VAOKey, IO ())] (V4 (S V Word)))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())]) (B4 Word16) (V4 (S V Word))
forall a b. (a -> b) -> a -> b
$ GLint
-> GLuint
-> B Word16
-> State [Int -> (IO VAOKey, IO ())] (V4 (S V Word))
forall (m :: * -> *) a a b.
(Monad m, Integral a) =>
GLint -> GLuint -> B a -> StateT [a -> (IO VAOKey, IO ())] m b
makeBindVertexI GLint
4 GLuint
forall a. (Eq a, Num a) => a
GL_UNSIGNED_SHORT (B Word16 -> State [Int -> (IO VAOKey, IO ())] (V4 (S V Word)))
-> (B4 Word16 -> B Word16)
-> B4 Word16
-> State [Int -> (IO VAOKey, IO ())] (V4 (S V Word))
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. B4 Word16 -> B Word16
forall a. B4 a -> B a
unB4)
instance VertexInput (B4 Word8) where
type VertexFormat (B4 Word8) = V4 VWord
toVertex :: ToVertex (B4 GLboolean) (VertexFormat (B4 GLboolean))
toVertex = Kleisli (StateT (Ptr ()) IO) (B4 GLboolean) (V4 (S V Word))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B4 GLboolean)
(V4 (S V Word))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())]) (B4 GLboolean) (V4 (S V Word))
-> ToVertex (B4 GLboolean) (V4 (S V Word))
forall a b.
Kleisli (StateT (Ptr ()) IO) a b
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text))) a b
-> Kleisli (State [Int -> (IO VAOKey, IO ())]) a b
-> ToVertex a b
ToVertex Kleisli (StateT (Ptr ()) IO) (B4 GLboolean) (V4 (S V Word))
forall b b. Kleisli (StateT (Ptr ()) IO) b b
noWriter ((B4 GLboolean
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V4 (S V Word)))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B4 GLboolean)
(V4 (S V Word))
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((B4 GLboolean
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V4 (S V Word)))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B4 GLboolean)
(V4 (S V Word)))
-> (B4 GLboolean
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V4 (S V Word)))
-> Kleisli
(StateT (Int, Int, OffsetToSType) (Reader (Int -> ExprM Text)))
(B4 GLboolean)
(V4 (S V Word))
forall a b. (a -> b) -> a -> b
$ Integer
-> (SType -> ExprM Text -> V4 (S V Word))
-> SType
-> B GLboolean
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V4 (S V Word))
forall (m :: * -> *) p b p b c.
Monad m =>
p
-> (SType -> ExprM Text -> b)
-> SType
-> p
-> StateT (Int, b, c) m b
makeVertexI Integer
4 SType -> ExprM Text -> V4 (S V Word)
forall c a. SType -> ExprM Text -> V4 (S c a)
vec4S (Int -> SType
STypeUVec Int
4) (B GLboolean
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V4 (S V Word)))
-> (B4 GLboolean -> B GLboolean)
-> B4 GLboolean
-> StateT
(Int, Int, OffsetToSType)
(Reader (Int -> ExprM Text))
(V4 (S V Word))
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. B4 GLboolean -> B GLboolean
forall a. B4 a -> B a
unB4) ((B4 GLboolean -> State [Int -> (IO VAOKey, IO ())] (V4 (S V Word)))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())]) (B4 GLboolean) (V4 (S V Word))
forall (m :: * -> *) a b. (a -> m b) -> Kleisli m a b
Kleisli ((B4 GLboolean
-> State [Int -> (IO VAOKey, IO ())] (V4 (S V Word)))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())]) (B4 GLboolean) (V4 (S V Word)))
-> (B4 GLboolean
-> State [Int -> (IO VAOKey, IO ())] (V4 (S V Word)))
-> Kleisli
(State [Int -> (IO VAOKey, IO ())]) (B4 GLboolean) (V4 (S V Word))
forall a b. (a -> b) -> a -> b
$ GLint
-> GLuint
-> B GLboolean
-> State [Int -> (IO VAOKey, IO ())] (V4 (S V Word))
forall (m :: * -> *) a a b.
(Monad m, Integral a) =>
GLint -> GLuint -> B a -> StateT [a -> (IO VAOKey, IO ())] m b
makeBindVertexI GLint
4 GLuint
forall a. (Eq a, Num a) => a
GL_UNSIGNED_BYTE (B GLboolean -> State [Int -> (IO VAOKey, IO ())] (V4 (S V Word)))
-> (B4 GLboolean -> B GLboolean)
-> B4 GLboolean
-> State [Int -> (IO VAOKey, IO ())] (V4 (S V Word))
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. B4 GLboolean -> B GLboolean
forall a. B4 a -> B a
unB4)
instance VertexInput () where
type VertexFormat () = ()
toVertex :: ToVertex () (VertexFormat ())
toVertex = (() -> ()) -> ToVertex () ()
forall (a :: * -> * -> *) b c. Arrow a => (b -> c) -> a b c
arr (() -> () -> ()
forall a b. a -> b -> a
const ())
instance (VertexInput a, VertexInput b) => VertexInput (a,b) where
type VertexFormat (a,b) = (VertexFormat a, VertexFormat b)
toVertex :: ToVertex (a, b) (VertexFormat (a, b))
toVertex = proc ~(a
a,b
b) -> do VertexFormat a
a' <- ToVertex a (VertexFormat a)
forall a. VertexInput a => ToVertex a (VertexFormat a)
toVertex -< a
a
VertexFormat b
b' <- ToVertex b (VertexFormat b)
forall a. VertexInput a => ToVertex a (VertexFormat a)
toVertex -< b
b
ToVertex (VertexFormat a, VertexFormat b) (VertexFormat (a, b))
forall (a :: * -> * -> *) b. Arrow a => a b b
returnA -< (VertexFormat a
a', VertexFormat b
b')
instance (VertexInput a, VertexInput b, VertexInput c) => VertexInput (a,b,c) where
type VertexFormat (a,b,c) = (VertexFormat a, VertexFormat b, VertexFormat c)
toVertex :: ToVertex (a, b, c) (VertexFormat (a, b, c))
toVertex = proc ~(a
a,b
b,c
c) -> do VertexFormat a
a' <- ToVertex a (VertexFormat a)
forall a. VertexInput a => ToVertex a (VertexFormat a)
toVertex -< a
a
VertexFormat b
b' <- ToVertex b (VertexFormat b)
forall a. VertexInput a => ToVertex a (VertexFormat a)
toVertex -< b
b
VertexFormat c
c' <- ToVertex c (VertexFormat c)
forall a. VertexInput a => ToVertex a (VertexFormat a)
toVertex -< c
c
ToVertex
(VertexFormat a, VertexFormat b, VertexFormat c)
(VertexFormat (a, b, c))
forall (a :: * -> * -> *) b. Arrow a => a b b
returnA -< (VertexFormat a
a', VertexFormat b
b', VertexFormat c
c')
instance (VertexInput a, VertexInput b, VertexInput c, VertexInput d) => VertexInput (a,b,c,d) where
type VertexFormat (a,b,c,d) = (VertexFormat a, VertexFormat b, VertexFormat c, VertexFormat d)
toVertex :: ToVertex (a, b, c, d) (VertexFormat (a, b, c, d))
toVertex = proc ~(a
a,b
b,c
c,d
d) -> do VertexFormat a
a' <- ToVertex a (VertexFormat a)
forall a. VertexInput a => ToVertex a (VertexFormat a)
toVertex -< a
a
VertexFormat b
b' <- ToVertex b (VertexFormat b)
forall a. VertexInput a => ToVertex a (VertexFormat a)
toVertex -< b
b
VertexFormat c
c' <- ToVertex c (VertexFormat c)
forall a. VertexInput a => ToVertex a (VertexFormat a)
toVertex -< c
c
VertexFormat d
d' <- ToVertex d (VertexFormat d)
forall a. VertexInput a => ToVertex a (VertexFormat a)
toVertex -< d
d
ToVertex
(VertexFormat a, VertexFormat b, VertexFormat c, VertexFormat d)
(VertexFormat (a, b, c, d))
forall (a :: * -> * -> *) b. Arrow a => a b b
returnA -< (VertexFormat a
a', VertexFormat b
b', VertexFormat c
c', VertexFormat d
d')
instance (VertexInput a, VertexInput b, VertexInput c, VertexInput d, VertexInput e) => VertexInput (a,b,c,d,e) where
type VertexFormat (a,b,c,d,e) = (VertexFormat a, VertexFormat b, VertexFormat c, VertexFormat d, VertexFormat e)
toVertex :: ToVertex (a, b, c, d, e) (VertexFormat (a, b, c, d, e))
toVertex = proc ~(a
a,b
b,c
c,d
d,e
e) -> do VertexFormat a
a' <- ToVertex a (VertexFormat a)
forall a. VertexInput a => ToVertex a (VertexFormat a)
toVertex -< a
a
VertexFormat b
b' <- ToVertex b (VertexFormat b)
forall a. VertexInput a => ToVertex a (VertexFormat a)
toVertex -< b
b
VertexFormat c
c' <- ToVertex c (VertexFormat c)
forall a. VertexInput a => ToVertex a (VertexFormat a)
toVertex -< c
c
VertexFormat d
d' <- ToVertex d (VertexFormat d)
forall a. VertexInput a => ToVertex a (VertexFormat a)
toVertex -< d
d
VertexFormat e
e' <- ToVertex e (VertexFormat e)
forall a. VertexInput a => ToVertex a (VertexFormat a)
toVertex -< e
e
ToVertex
(VertexFormat a, VertexFormat b, VertexFormat c, VertexFormat d,
VertexFormat e)
(VertexFormat (a, b, c, d, e))
forall (a :: * -> * -> *) b. Arrow a => a b b
returnA -< (VertexFormat a
a', VertexFormat b
b', VertexFormat c
c', VertexFormat d
d', VertexFormat e
e')
instance (VertexInput a, VertexInput b, VertexInput c, VertexInput d, VertexInput e, VertexInput f) => VertexInput (a,b,c,d,e,f) where
type VertexFormat (a,b,c,d,e,f) = (VertexFormat a, VertexFormat b, VertexFormat c, VertexFormat d, VertexFormat e, VertexFormat f)
toVertex :: ToVertex (a, b, c, d, e, f) (VertexFormat (a, b, c, d, e, f))
toVertex = proc ~(a
a,b
b,c
c,d
d,e
e,f
f) -> do VertexFormat a
a' <- ToVertex a (VertexFormat a)
forall a. VertexInput a => ToVertex a (VertexFormat a)
toVertex -< a
a
VertexFormat b
b' <- ToVertex b (VertexFormat b)
forall a. VertexInput a => ToVertex a (VertexFormat a)
toVertex -< b
b
VertexFormat c
c' <- ToVertex c (VertexFormat c)
forall a. VertexInput a => ToVertex a (VertexFormat a)
toVertex -< c
c
VertexFormat d
d' <- ToVertex d (VertexFormat d)
forall a. VertexInput a => ToVertex a (VertexFormat a)
toVertex -< d
d
VertexFormat e
e' <- ToVertex e (VertexFormat e)
forall a. VertexInput a => ToVertex a (VertexFormat a)
toVertex -< e
e
VertexFormat f
f' <- ToVertex f (VertexFormat f)
forall a. VertexInput a => ToVertex a (VertexFormat a)
toVertex -< f
f
ToVertex
(VertexFormat a, VertexFormat b, VertexFormat c, VertexFormat d,
VertexFormat e, VertexFormat f)
(VertexFormat (a, b, c, d, e, f))
forall (a :: * -> * -> *) b. Arrow a => a b b
returnA -< (VertexFormat a
a', VertexFormat b
b', VertexFormat c
c', VertexFormat d
d', VertexFormat e
e', VertexFormat f
f')
instance (VertexInput a, VertexInput b, VertexInput c, VertexInput d, VertexInput e, VertexInput f, VertexInput g) => VertexInput (a,b,c,d,e,f,g) where
type VertexFormat (a,b,c,d,e,f,g) = (VertexFormat a, VertexFormat b, VertexFormat c, VertexFormat d, VertexFormat e, VertexFormat f, VertexFormat g)
toVertex :: ToVertex (a, b, c, d, e, f, g) (VertexFormat (a, b, c, d, e, f, g))
toVertex = proc ~(a
a,b
b,c
c,d
d,e
e,f
f,g
g) -> do VertexFormat a
a' <- ToVertex a (VertexFormat a)
forall a. VertexInput a => ToVertex a (VertexFormat a)
toVertex -< a
a
VertexFormat b
b' <- ToVertex b (VertexFormat b)
forall a. VertexInput a => ToVertex a (VertexFormat a)
toVertex -< b
b
VertexFormat c
c' <- ToVertex c (VertexFormat c)
forall a. VertexInput a => ToVertex a (VertexFormat a)
toVertex -< c
c
VertexFormat d
d' <- ToVertex d (VertexFormat d)
forall a. VertexInput a => ToVertex a (VertexFormat a)
toVertex -< d
d
VertexFormat e
e' <- ToVertex e (VertexFormat e)
forall a. VertexInput a => ToVertex a (VertexFormat a)
toVertex -< e
e
VertexFormat f
f' <- ToVertex f (VertexFormat f)
forall a. VertexInput a => ToVertex a (VertexFormat a)
toVertex -< f
f
VertexFormat g
g' <- ToVertex g (VertexFormat g)
forall a. VertexInput a => ToVertex a (VertexFormat a)
toVertex -< g
g
ToVertex
(VertexFormat a, VertexFormat b, VertexFormat c, VertexFormat d,
VertexFormat e, VertexFormat f, VertexFormat g)
(VertexFormat (a, b, c, d, e, f, g))
forall (a :: * -> * -> *) b. Arrow a => a b b
returnA -< (VertexFormat a
a', VertexFormat b
b', VertexFormat c
c', VertexFormat d
d', VertexFormat e
e', VertexFormat f
f', VertexFormat g
g')
instance VertexInput a => VertexInput (V0 a) where
type VertexFormat (V0 a) = V0 (VertexFormat a)
toVertex :: ToVertex (V0 a) (VertexFormat (V0 a))
toVertex = (V0 a -> V0 (VertexFormat a))
-> ToVertex (V0 a) (V0 (VertexFormat a))
forall (a :: * -> * -> *) b c. Arrow a => (b -> c) -> a b c
arr (V0 (VertexFormat a) -> V0 a -> V0 (VertexFormat a)
forall a b. a -> b -> a
const V0 (VertexFormat a)
forall a. V0 a
V0)
instance VertexInput a => VertexInput (V1 a) where
type VertexFormat (V1 a) = V1 (VertexFormat a)
toVertex :: ToVertex (V1 a) (VertexFormat (V1 a))
toVertex = proc ~(V1 a
a) -> do VertexFormat a
a' <- ToVertex a (VertexFormat a)
forall a. VertexInput a => ToVertex a (VertexFormat a)
toVertex -< a
a
ToVertex (V1 (VertexFormat a)) (VertexFormat (V1 a))
forall (a :: * -> * -> *) b. Arrow a => a b b
returnA -< VertexFormat a -> V1 (VertexFormat a)
forall a. a -> V1 a
V1 VertexFormat a
a'
instance VertexInput a => VertexInput (V2 a) where
type VertexFormat (V2 a) = V2 (VertexFormat a)
toVertex :: ToVertex (V2 a) (VertexFormat (V2 a))
toVertex = proc ~(V2 a
a a
b) -> do VertexFormat a
a' <- ToVertex a (VertexFormat a)
forall a. VertexInput a => ToVertex a (VertexFormat a)
toVertex -< a
a
VertexFormat a
b' <- ToVertex a (VertexFormat a)
forall a. VertexInput a => ToVertex a (VertexFormat a)
toVertex -< a
b
ToVertex (V2 (VertexFormat a)) (VertexFormat (V2 a))
forall (a :: * -> * -> *) b. Arrow a => a b b
returnA -< VertexFormat a -> VertexFormat a -> V2 (VertexFormat a)
forall a. a -> a -> V2 a
V2 VertexFormat a
a' VertexFormat a
b'
instance VertexInput a => VertexInput (V3 a) where
type VertexFormat (V3 a) = V3 (VertexFormat a)
toVertex :: ToVertex (V3 a) (VertexFormat (V3 a))
toVertex = proc ~(V3 a
a a
b a
c) -> do VertexFormat a
a' <- ToVertex a (VertexFormat a)
forall a. VertexInput a => ToVertex a (VertexFormat a)
toVertex -< a
a
VertexFormat a
b' <- ToVertex a (VertexFormat a)
forall a. VertexInput a => ToVertex a (VertexFormat a)
toVertex -< a
b
VertexFormat a
c' <- ToVertex a (VertexFormat a)
forall a. VertexInput a => ToVertex a (VertexFormat a)
toVertex -< a
c
ToVertex (V3 (VertexFormat a)) (VertexFormat (V3 a))
forall (a :: * -> * -> *) b. Arrow a => a b b
returnA -< VertexFormat a
-> VertexFormat a -> VertexFormat a -> V3 (VertexFormat a)
forall a. a -> a -> a -> V3 a
V3 VertexFormat a
a' VertexFormat a
b' VertexFormat a
c'
instance VertexInput a => VertexInput (V4 a) where
type VertexFormat (V4 a) = V4 (VertexFormat a)
toVertex :: ToVertex (V4 a) (VertexFormat (V4 a))
toVertex = proc ~(V4 a
a a
b a
c a
d) -> do VertexFormat a
a' <- ToVertex a (VertexFormat a)
forall a. VertexInput a => ToVertex a (VertexFormat a)
toVertex -< a
a
VertexFormat a
b' <- ToVertex a (VertexFormat a)
forall a. VertexInput a => ToVertex a (VertexFormat a)
toVertex -< a
b
VertexFormat a
c' <- ToVertex a (VertexFormat a)
forall a. VertexInput a => ToVertex a (VertexFormat a)
toVertex -< a
c
VertexFormat a
d' <- ToVertex a (VertexFormat a)
forall a. VertexInput a => ToVertex a (VertexFormat a)
toVertex -< a
d
ToVertex (V4 (VertexFormat a)) (VertexFormat (V4 a))
forall (a :: * -> * -> *) b. Arrow a => a b b
returnA -< VertexFormat a
-> VertexFormat a
-> VertexFormat a
-> VertexFormat a
-> V4 (VertexFormat a)
forall a. a -> a -> a -> a -> V4 a
V4 VertexFormat a
a' VertexFormat a
b' VertexFormat a
c' VertexFormat a
d'
instance VertexInput a => VertexInput (Quaternion a) where
type VertexFormat (Quaternion a) = Quaternion (VertexFormat a)
toVertex :: ToVertex (Quaternion a) (VertexFormat (Quaternion a))
toVertex = proc ~(Quaternion a
a V3 a
v) -> do
VertexFormat a
a' <- ToVertex a (VertexFormat a)
forall a. VertexInput a => ToVertex a (VertexFormat a)
toVertex -< a
a
V3 (VertexFormat a)
v' <- ToVertex (V3 a) (V3 (VertexFormat a))
forall a. VertexInput a => ToVertex a (VertexFormat a)
toVertex -< V3 a
v
ToVertex
(Quaternion (VertexFormat a)) (VertexFormat (Quaternion a))
forall (a :: * -> * -> *) b. Arrow a => a b b
returnA -< VertexFormat a
-> V3 (VertexFormat a) -> Quaternion (VertexFormat a)
forall a. a -> V3 a -> Quaternion a
Quaternion VertexFormat a
a' V3 (VertexFormat a)
v'
instance (VertexInput (f a), VertexInput a, HostFormat (f a) ~ f (HostFormat a), VertexFormat (f a) ~ f (VertexFormat a)) => VertexInput (Point f a) where
type VertexFormat (Point f a) = Point f (VertexFormat a)
toVertex :: ToVertex (Point f a) (VertexFormat (Point f a))
toVertex = proc ~(P f a
a) -> do
f (VertexFormat a)
a' <- ToVertex (f a) (f (VertexFormat a))
forall a. VertexInput a => ToVertex a (VertexFormat a)
toVertex -< f a
a
ToVertex (Point f (VertexFormat a)) (VertexFormat (Point f a))
forall (a :: * -> * -> *) b. Arrow a => a b b
returnA -< f (VertexFormat a) -> Point f (VertexFormat a)
forall (f :: * -> *) a. f a -> Point f a
P f (VertexFormat a)
a'
instance VertexInput a => VertexInput (Plucker a) where
type VertexFormat (Plucker a) = Plucker (VertexFormat a)
toVertex :: ToVertex (Plucker a) (VertexFormat (Plucker a))
toVertex = proc ~(Plucker a
a a
b a
c a
d a
e a
f) -> do
VertexFormat a
a' <- ToVertex a (VertexFormat a)
forall a. VertexInput a => ToVertex a (VertexFormat a)
toVertex -< a
a
VertexFormat a
b' <- ToVertex a (VertexFormat a)
forall a. VertexInput a => ToVertex a (VertexFormat a)
toVertex -< a
b
VertexFormat a
c' <- ToVertex a (VertexFormat a)
forall a. VertexInput a => ToVertex a (VertexFormat a)
toVertex -< a
c
VertexFormat a
d' <- ToVertex a (VertexFormat a)
forall a. VertexInput a => ToVertex a (VertexFormat a)
toVertex -< a
d
VertexFormat a
e' <- ToVertex a (VertexFormat a)
forall a. VertexInput a => ToVertex a (VertexFormat a)
toVertex -< a
e
VertexFormat a
f' <- ToVertex a (VertexFormat a)
forall a. VertexInput a => ToVertex a (VertexFormat a)
toVertex -< a
f
ToVertex (Plucker (VertexFormat a)) (VertexFormat (Plucker a))
forall (a :: * -> * -> *) b. Arrow a => a b b
returnA -< VertexFormat a
-> VertexFormat a
-> VertexFormat a
-> VertexFormat a
-> VertexFormat a
-> VertexFormat a
-> Plucker (VertexFormat a)
forall a. a -> a -> a -> a -> a -> a -> Plucker a
Plucker VertexFormat a
a' VertexFormat a
b' VertexFormat a
c' VertexFormat a
d' VertexFormat a
e' VertexFormat a
f'