gl-block-1.0: OpenGL standard memory layouts
Copyright(c) 2023 IC Rainbow
(c) 2014-2019 Edward Kmett
LicenseBSD-2-Clause OR Apache-2.0
MaintainerIC Rainbow <aenor.realm@gmail.com>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Graphics.Gl.Block

Description

OpenGL std140 and std430 support

Synopsis

Documentation

class Block b where Source #

This describes how to load and store primitives through a uniform/shader storage blocks according to OpenGL Std140 and Std430.

There are lots of fiddly little constants around, beware.

Minimal complete definition

Nothing

Associated Types

type PackedSize b :: Nat Source #

Methods

alignment140 :: proxy b -> Int Source #

As per Storable alignment, but matching OpenGL Std140.

default alignment140 :: GBlock (Rep b) => proxy b -> Int Source #

sizeOf140 :: proxy b -> Int Source #

As per Storable sizeOf, but matching OpenGL Std140.

default sizeOf140 :: GBlock (Rep b) => proxy b -> Int Source #

isStruct :: proxy b -> Bool Source #

Structures get smashed up to a minimum of a vec4 alignment in 140 mode

read140 :: MonadIO m => Ptr a -> Diff a b -> m b Source #

default read140 :: (MonadIO m, Generic b, GBlock (Rep b)) => Ptr a -> Diff a b -> m b Source #

write140 :: MonadIO m => Ptr a -> Diff a b -> b -> m () Source #

default write140 :: (MonadIO m, Generic b, GBlock (Rep b)) => Ptr a -> Diff a b -> b -> m () Source #

alignment430 :: proxy b -> Int Source #

As per Storable alignment, but matching OpenGL Std430.

default alignment430 :: GBlock (Rep b) => proxy b -> Int Source #

sizeOf430 :: proxy b -> Int Source #

As per Storable sizeOf, but matching OpenGL Std430.

default sizeOf430 :: GBlock (Rep b) => proxy b -> Int Source #

read430 :: MonadIO m => Ptr a -> Diff a b -> m b Source #

default read430 :: (MonadIO m, Generic b, GBlock (Rep b)) => Ptr a -> Diff a b -> m b Source #

write430 :: MonadIO m => Ptr a -> Diff a b -> b -> m () Source #

default write430 :: (MonadIO m, Generic b, GBlock (Rep b)) => Ptr a -> Diff a b -> b -> m () Source #

sizeOfPacked :: proxy b -> Int Source #

As per Storable sizeOf, but without padding and no alignment

default sizeOfPacked :: KnownNat (PackedSize b) => proxy b -> Int Source #

readPacked :: MonadIO m => Ptr a -> Diff a b -> m b Source #

default readPacked :: (MonadIO m, Generic b, GBlock (Rep b)) => Ptr a -> Diff a b -> m b Source #

writePacked :: MonadIO m => Ptr a -> Diff a b -> b -> m () Source #

default writePacked :: (MonadIO m, Generic b, GBlock (Rep b)) => Ptr a -> Diff a b -> b -> m () Source #

Instances

Instances details
Block Int32 Source # 
Instance details

Defined in Graphics.Gl.Block

Associated Types

type PackedSize Int32 :: Nat Source #

Methods

alignment140 :: proxy Int32 -> Int Source #

sizeOf140 :: proxy Int32 -> Int Source #

isStruct :: proxy Int32 -> Bool Source #

read140 :: MonadIO m => Ptr a -> Diff a Int32 -> m Int32 Source #

write140 :: MonadIO m => Ptr a -> Diff a Int32 -> Int32 -> m () Source #

alignment430 :: proxy Int32 -> Int Source #

sizeOf430 :: proxy Int32 -> Int Source #

read430 :: MonadIO m => Ptr a -> Diff a Int32 -> m Int32 Source #

write430 :: MonadIO m => Ptr a -> Diff a Int32 -> Int32 -> m () Source #

sizeOfPacked :: proxy Int32 -> Int Source #

readPacked :: MonadIO m => Ptr a -> Diff a Int32 -> m Int32 Source #

writePacked :: MonadIO m => Ptr a -> Diff a Int32 -> Int32 -> m () Source #

Block Word32 Source # 
Instance details

Defined in Graphics.Gl.Block

Associated Types

type PackedSize Word32 :: Nat Source #

Methods

alignment140 :: proxy Word32 -> Int Source #

sizeOf140 :: proxy Word32 -> Int Source #

isStruct :: proxy Word32 -> Bool Source #

read140 :: MonadIO m => Ptr a -> Diff a Word32 -> m Word32 Source #

write140 :: MonadIO m => Ptr a -> Diff a Word32 -> Word32 -> m () Source #

alignment430 :: proxy Word32 -> Int Source #

sizeOf430 :: proxy Word32 -> Int Source #

read430 :: MonadIO m => Ptr a -> Diff a Word32 -> m Word32 Source #

write430 :: MonadIO m => Ptr a -> Diff a Word32 -> Word32 -> m () Source #

sizeOfPacked :: proxy Word32 -> Int Source #

readPacked :: MonadIO m => Ptr a -> Diff a Word32 -> m Word32 Source #

writePacked :: MonadIO m => Ptr a -> Diff a Word32 -> Word32 -> m () Source #

Block Bool Source # 
Instance details

Defined in Graphics.Gl.Block

Associated Types

type PackedSize Bool :: Nat Source #

Methods

alignment140 :: proxy Bool -> Int Source #

sizeOf140 :: proxy Bool -> Int Source #

isStruct :: proxy Bool -> Bool Source #

read140 :: MonadIO m => Ptr a -> Diff a Bool -> m Bool Source #

write140 :: MonadIO m => Ptr a -> Diff a Bool -> Bool -> m () Source #

alignment430 :: proxy Bool -> Int Source #

sizeOf430 :: proxy Bool -> Int Source #

read430 :: MonadIO m => Ptr a -> Diff a Bool -> m Bool Source #

write430 :: MonadIO m => Ptr a -> Diff a Bool -> Bool -> m () Source #

sizeOfPacked :: proxy Bool -> Int Source #

readPacked :: MonadIO m => Ptr a -> Diff a Bool -> m Bool Source #

writePacked :: MonadIO m => Ptr a -> Diff a Bool -> Bool -> m () Source #

Block Double Source # 
Instance details

Defined in Graphics.Gl.Block

Associated Types

type PackedSize Double :: Nat Source #

Methods

alignment140 :: proxy Double -> Int Source #

sizeOf140 :: proxy Double -> Int Source #

isStruct :: proxy Double -> Bool Source #

read140 :: MonadIO m => Ptr a -> Diff a Double -> m Double Source #

write140 :: MonadIO m => Ptr a -> Diff a Double -> Double -> m () Source #

alignment430 :: proxy Double -> Int Source #

sizeOf430 :: proxy Double -> Int Source #

read430 :: MonadIO m => Ptr a -> Diff a Double -> m Double Source #

write430 :: MonadIO m => Ptr a -> Diff a Double -> Double -> m () Source #

sizeOfPacked :: proxy Double -> Int Source #

readPacked :: MonadIO m => Ptr a -> Diff a Double -> m Double Source #

writePacked :: MonadIO m => Ptr a -> Diff a Double -> Double -> m () Source #

Block Float Source # 
Instance details

Defined in Graphics.Gl.Block

Associated Types

type PackedSize Float :: Nat Source #

Methods

alignment140 :: proxy Float -> Int Source #

sizeOf140 :: proxy Float -> Int Source #

isStruct :: proxy Float -> Bool Source #

read140 :: MonadIO m => Ptr a -> Diff a Float -> m Float Source #

write140 :: MonadIO m => Ptr a -> Diff a Float -> Float -> m () Source #

alignment430 :: proxy Float -> Int Source #

sizeOf430 :: proxy Float -> Int Source #

read430 :: MonadIO m => Ptr a -> Diff a Float -> m Float Source #

write430 :: MonadIO m => Ptr a -> Diff a Float -> Float -> m () Source #

sizeOfPacked :: proxy Float -> Int Source #

readPacked :: MonadIO m => Ptr a -> Diff a Float -> m Float Source #

writePacked :: MonadIO m => Ptr a -> Diff a Float -> Float -> m () Source #

(Block a, Block b, KnownNat (PackedSize a + PackedSize b)) => Block (a, b) Source # 
Instance details

Defined in Graphics.Gl.Block

Associated Types

type PackedSize (a, b) :: Nat Source #

Methods

alignment140 :: proxy (a, b) -> Int Source #

sizeOf140 :: proxy (a, b) -> Int Source #

isStruct :: proxy (a, b) -> Bool Source #

read140 :: MonadIO m => Ptr a0 -> Diff a0 (a, b) -> m (a, b) Source #

write140 :: MonadIO m => Ptr a0 -> Diff a0 (a, b) -> (a, b) -> m () Source #

alignment430 :: proxy (a, b) -> Int Source #

sizeOf430 :: proxy (a, b) -> Int Source #

read430 :: MonadIO m => Ptr a0 -> Diff a0 (a, b) -> m (a, b) Source #

write430 :: MonadIO m => Ptr a0 -> Diff a0 (a, b) -> (a, b) -> m () Source #

sizeOfPacked :: proxy (a, b) -> Int Source #

readPacked :: MonadIO m => Ptr a0 -> Diff a0 (a, b) -> m (a, b) Source #

writePacked :: MonadIO m => Ptr a0 -> Diff a0 (a, b) -> (a, b) -> m () Source #

(Block a, Block b, Block c, KnownNat (PackedSize a + (PackedSize b + PackedSize c))) => Block (a, b, c) Source # 
Instance details

Defined in Graphics.Gl.Block

Associated Types

type PackedSize (a, b, c) :: Nat Source #

Methods

alignment140 :: proxy (a, b, c) -> Int Source #

sizeOf140 :: proxy (a, b, c) -> Int Source #

isStruct :: proxy (a, b, c) -> Bool Source #

read140 :: MonadIO m => Ptr a0 -> Diff a0 (a, b, c) -> m (a, b, c) Source #

write140 :: MonadIO m => Ptr a0 -> Diff a0 (a, b, c) -> (a, b, c) -> m () Source #

alignment430 :: proxy (a, b, c) -> Int Source #

sizeOf430 :: proxy (a, b, c) -> Int Source #

read430 :: MonadIO m => Ptr a0 -> Diff a0 (a, b, c) -> m (a, b, c) Source #

write430 :: MonadIO m => Ptr a0 -> Diff a0 (a, b, c) -> (a, b, c) -> m () Source #

sizeOfPacked :: proxy (a, b, c) -> Int Source #

readPacked :: MonadIO m => Ptr a0 -> Diff a0 (a, b, c) -> m (a, b, c) Source #

writePacked :: MonadIO m => Ptr a0 -> Diff a0 (a, b, c) -> (a, b, c) -> m () Source #

class GBlock f where Source #

Automatically derive Std140 and Std430 alignment using GHC Generics

Associated Types

type GPackedSize f :: Nat Source #

Methods

galignment140 :: p f -> Int Source #

galignment430 :: p f -> Int Source #

gsizeOf140 :: p f -> Int Source #

gsizeOf430 :: p f -> Int Source #

gsizeOfPacked :: p f -> Int Source #

gread140 :: Ptr a -> Int -> IO (f b) Source #

gread430 :: Ptr a -> Int -> IO (f b) Source #

greadPacked :: Ptr a -> Int -> IO (f b) Source #

gwrite140 :: Ptr a -> Int -> f b -> IO () Source #

gwrite430 :: Ptr a -> Int -> f b -> IO () Source #

gwritePacked :: Ptr a -> Int -> f b -> IO () Source #

Instances

Instances details
GBlock (U1 :: k -> Type) Source # 
Instance details

Defined in Graphics.Gl.Block

Associated Types

type GPackedSize U1 :: Nat Source #

Methods

galignment140 :: p U1 -> Int Source #

galignment430 :: p U1 -> Int Source #

gsizeOf140 :: p U1 -> Int Source #

gsizeOf430 :: p U1 -> Int Source #

gsizeOfPacked :: p U1 -> Int Source #

gread140 :: forall a (b :: k0). Ptr a -> Int -> IO (U1 b) Source #

gread430 :: forall a (b :: k0). Ptr a -> Int -> IO (U1 b) Source #

greadPacked :: forall a (b :: k0). Ptr a -> Int -> IO (U1 b) Source #

gwrite140 :: forall a (b :: k0). Ptr a -> Int -> U1 b -> IO () Source #

gwrite430 :: forall a (b :: k0). Ptr a -> Int -> U1 b -> IO () Source #

gwritePacked :: forall a (b :: k0). Ptr a -> Int -> U1 b -> IO () Source #

(GBlock f, GBlock g) => GBlock (f :*: g :: k -> Type) Source # 
Instance details

Defined in Graphics.Gl.Block

Associated Types

type GPackedSize (f :*: g) :: Nat Source #

Methods

galignment140 :: p (f :*: g) -> Int Source #

galignment430 :: p (f :*: g) -> Int Source #

gsizeOf140 :: p (f :*: g) -> Int Source #

gsizeOf430 :: p (f :*: g) -> Int Source #

gsizeOfPacked :: p (f :*: g) -> Int Source #

gread140 :: forall a (b :: k0). Ptr a -> Int -> IO ((f :*: g) b) Source #

gread430 :: forall a (b :: k0). Ptr a -> Int -> IO ((f :*: g) b) Source #

greadPacked :: forall a (b :: k0). Ptr a -> Int -> IO ((f :*: g) b) Source #

gwrite140 :: forall a (b :: k0). Ptr a -> Int -> (f :*: g) b -> IO () Source #

gwrite430 :: forall a (b :: k0). Ptr a -> Int -> (f :*: g) b -> IO () Source #

gwritePacked :: forall a (b :: k0). Ptr a -> Int -> (f :*: g) b -> IO () Source #

Block c => GBlock (K1 i c :: k -> Type) Source # 
Instance details

Defined in Graphics.Gl.Block

Associated Types

type GPackedSize (K1 i c) :: Nat Source #

Methods

galignment140 :: p (K1 i c) -> Int Source #

galignment430 :: p (K1 i c) -> Int Source #

gsizeOf140 :: p (K1 i c) -> Int Source #

gsizeOf430 :: p (K1 i c) -> Int Source #

gsizeOfPacked :: p (K1 i c) -> Int Source #

gread140 :: forall a (b :: k0). Ptr a -> Int -> IO (K1 i c b) Source #

gread430 :: forall a (b :: k0). Ptr a -> Int -> IO (K1 i c b) Source #

greadPacked :: forall a (b :: k0). Ptr a -> Int -> IO (K1 i c b) Source #

gwrite140 :: forall a (b :: k0). Ptr a -> Int -> K1 i c b -> IO () Source #

gwrite430 :: forall a (b :: k0). Ptr a -> Int -> K1 i c b -> IO () Source #

gwritePacked :: forall a (b :: k0). Ptr a -> Int -> K1 i c b -> IO () Source #

GBlock f => GBlock (M1 C c f :: k -> Type) Source # 
Instance details

Defined in Graphics.Gl.Block

Associated Types

type GPackedSize (M1 C c f) :: Nat Source #

Methods

galignment140 :: p (M1 C c f) -> Int Source #

galignment430 :: p (M1 C c f) -> Int Source #

gsizeOf140 :: p (M1 C c f) -> Int Source #

gsizeOf430 :: p (M1 C c f) -> Int Source #

gsizeOfPacked :: p (M1 C c f) -> Int Source #

gread140 :: forall a (b :: k0). Ptr a -> Int -> IO (M1 C c f b) Source #

gread430 :: forall a (b :: k0). Ptr a -> Int -> IO (M1 C c f b) Source #

greadPacked :: forall a (b :: k0). Ptr a -> Int -> IO (M1 C c f b) Source #

gwrite140 :: forall a (b :: k0). Ptr a -> Int -> M1 C c f b -> IO () Source #

gwrite430 :: forall a (b :: k0). Ptr a -> Int -> M1 C c f b -> IO () Source #

gwritePacked :: forall a (b :: k0). Ptr a -> Int -> M1 C c f b -> IO () Source #

GBlock f => GBlock (M1 D c f :: k -> Type) Source # 
Instance details

Defined in Graphics.Gl.Block

Associated Types

type GPackedSize (M1 D c f) :: Nat Source #

Methods

galignment140 :: p (M1 D c f) -> Int Source #

galignment430 :: p (M1 D c f) -> Int Source #

gsizeOf140 :: p (M1 D c f) -> Int Source #

gsizeOf430 :: p (M1 D c f) -> Int Source #

gsizeOfPacked :: p (M1 D c f) -> Int Source #

gread140 :: forall a (b :: k0). Ptr a -> Int -> IO (M1 D c f b) Source #

gread430 :: forall a (b :: k0). Ptr a -> Int -> IO (M1 D c f b) Source #

greadPacked :: forall a (b :: k0). Ptr a -> Int -> IO (M1 D c f b) Source #

gwrite140 :: forall a (b :: k0). Ptr a -> Int -> M1 D c f b -> IO () Source #

gwrite430 :: forall a (b :: k0). Ptr a -> Int -> M1 D c f b -> IO () Source #

gwritePacked :: forall a (b :: k0). Ptr a -> Int -> M1 D c f b -> IO () Source #

GBlock f => GBlock (M1 S c f :: k -> Type) Source # 
Instance details

Defined in Graphics.Gl.Block

Associated Types

type GPackedSize (M1 S c f) :: Nat Source #

Methods

galignment140 :: p (M1 S c f) -> Int Source #

galignment430 :: p (M1 S c f) -> Int Source #

gsizeOf140 :: p (M1 S c f) -> Int Source #

gsizeOf430 :: p (M1 S c f) -> Int Source #

gsizeOfPacked :: p (M1 S c f) -> Int Source #

gread140 :: forall a (b :: k0). Ptr a -> Int -> IO (M1 S c f b) Source #

gread430 :: forall a (b :: k0). Ptr a -> Int -> IO (M1 S c f b) Source #

greadPacked :: forall a (b :: k0). Ptr a -> Int -> IO (M1 S c f b) Source #

gwrite140 :: forall a (b :: k0). Ptr a -> Int -> M1 S c f b -> IO () Source #

gwrite430 :: forall a (b :: k0). Ptr a -> Int -> M1 S c f b -> IO () Source #

gwritePacked :: forall a (b :: k0). Ptr a -> Int -> M1 S c f b -> IO () Source #

newtype Packed a Source #

Constructors

Packed 

Fields

Instances

Instances details
Foldable Packed Source # 
Instance details

Defined in Graphics.Gl.Block

Methods

fold :: Monoid m => Packed m -> m #

foldMap :: Monoid m => (a -> m) -> Packed a -> m #

foldMap' :: Monoid m => (a -> m) -> Packed a -> m #

foldr :: (a -> b -> b) -> b -> Packed a -> b #

foldr' :: (a -> b -> b) -> b -> Packed a -> b #

foldl :: (b -> a -> b) -> b -> Packed a -> b #

foldl' :: (b -> a -> b) -> b -> Packed a -> b #

foldr1 :: (a -> a -> a) -> Packed a -> a #

foldl1 :: (a -> a -> a) -> Packed a -> a #

toList :: Packed a -> [a] #

null :: Packed a -> Bool #

length :: Packed a -> Int #

elem :: Eq a => a -> Packed a -> Bool #

maximum :: Ord a => Packed a -> a #

minimum :: Ord a => Packed a -> a #

sum :: Num a => Packed a -> a #

product :: Num a => Packed a -> a #

Traversable Packed Source # 
Instance details

Defined in Graphics.Gl.Block

Methods

traverse :: Applicative f => (a -> f b) -> Packed a -> f (Packed b) #

sequenceA :: Applicative f => Packed (f a) -> f (Packed a) #

mapM :: Monad m => (a -> m b) -> Packed a -> m (Packed b) #

sequence :: Monad m => Packed (m a) -> m (Packed a) #

Functor Packed Source # 
Instance details

Defined in Graphics.Gl.Block

Methods

fmap :: (a -> b) -> Packed a -> Packed b #

(<$) :: a -> Packed b -> Packed a #

Data a => Data (Packed a) Source # 
Instance details

Defined in Graphics.Gl.Block

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Packed a -> c (Packed a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Packed a) #

toConstr :: Packed a -> Constr #

dataTypeOf :: Packed a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Packed a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Packed a)) #

gmapT :: (forall b. Data b => b -> b) -> Packed a -> Packed a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Packed a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Packed a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Packed a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Packed a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Packed a -> m (Packed a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Packed a -> m (Packed a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Packed a -> m (Packed a) #

Block a => Storable (Packed a) Source # 
Instance details

Defined in Graphics.Gl.Block

Methods

sizeOf :: Packed a -> Int #

alignment :: Packed a -> Int #

peekElemOff :: Ptr (Packed a) -> Int -> IO (Packed a) #

pokeElemOff :: Ptr (Packed a) -> Int -> Packed a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Packed a) #

pokeByteOff :: Ptr b -> Int -> Packed a -> IO () #

peek :: Ptr (Packed a) -> IO (Packed a) #

poke :: Ptr (Packed a) -> Packed a -> IO () #

Generic (Packed a) Source # 
Instance details

Defined in Graphics.Gl.Block

Associated Types

type Rep (Packed a) :: Type -> Type #

Methods

from :: Packed a -> Rep (Packed a) x #

to :: Rep (Packed a) x -> Packed a #

Read a => Read (Packed a) Source # 
Instance details

Defined in Graphics.Gl.Block

Show a => Show (Packed a) Source # 
Instance details

Defined in Graphics.Gl.Block

Methods

showsPrec :: Int -> Packed a -> ShowS #

show :: Packed a -> String #

showList :: [Packed a] -> ShowS #

Eq a => Eq (Packed a) Source # 
Instance details

Defined in Graphics.Gl.Block

Methods

(==) :: Packed a -> Packed a -> Bool #

(/=) :: Packed a -> Packed a -> Bool #

Ord a => Ord (Packed a) Source # 
Instance details

Defined in Graphics.Gl.Block

Methods

compare :: Packed a -> Packed a -> Ordering #

(<) :: Packed a -> Packed a -> Bool #

(<=) :: Packed a -> Packed a -> Bool #

(>) :: Packed a -> Packed a -> Bool #

(>=) :: Packed a -> Packed a -> Bool #

max :: Packed a -> Packed a -> Packed a #

min :: Packed a -> Packed a -> Packed a #

type Rep (Packed a) Source # 
Instance details

Defined in Graphics.Gl.Block

type Rep (Packed a) = D1 ('MetaData "Packed" "Graphics.Gl.Block" "gl-block-1.0-9KxWvhJL6MZ4sPMBjpKfRA" 'True) (C1 ('MetaCons "Packed" 'PrefixI 'True) (S1 ('MetaSel ('Just "getPacked") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

newtype Std140 a Source #

Constructors

Std140 

Fields

Instances

Instances details
Foldable Std140 Source # 
Instance details

Defined in Graphics.Gl.Block

Methods

fold :: Monoid m => Std140 m -> m #

foldMap :: Monoid m => (a -> m) -> Std140 a -> m #

foldMap' :: Monoid m => (a -> m) -> Std140 a -> m #

foldr :: (a -> b -> b) -> b -> Std140 a -> b #

foldr' :: (a -> b -> b) -> b -> Std140 a -> b #

foldl :: (b -> a -> b) -> b -> Std140 a -> b #

foldl' :: (b -> a -> b) -> b -> Std140 a -> b #

foldr1 :: (a -> a -> a) -> Std140 a -> a #

foldl1 :: (a -> a -> a) -> Std140 a -> a #

toList :: Std140 a -> [a] #

null :: Std140 a -> Bool #

length :: Std140 a -> Int #

elem :: Eq a => a -> Std140 a -> Bool #

maximum :: Ord a => Std140 a -> a #

minimum :: Ord a => Std140 a -> a #

sum :: Num a => Std140 a -> a #

product :: Num a => Std140 a -> a #

Traversable Std140 Source # 
Instance details

Defined in Graphics.Gl.Block

Methods

traverse :: Applicative f => (a -> f b) -> Std140 a -> f (Std140 b) #

sequenceA :: Applicative f => Std140 (f a) -> f (Std140 a) #

mapM :: Monad m => (a -> m b) -> Std140 a -> m (Std140 b) #

sequence :: Monad m => Std140 (m a) -> m (Std140 a) #

Functor Std140 Source # 
Instance details

Defined in Graphics.Gl.Block

Methods

fmap :: (a -> b) -> Std140 a -> Std140 b #

(<$) :: a -> Std140 b -> Std140 a #

Data a => Data (Std140 a) Source # 
Instance details

Defined in Graphics.Gl.Block

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Std140 a -> c (Std140 a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Std140 a) #

toConstr :: Std140 a -> Constr #

dataTypeOf :: Std140 a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Std140 a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Std140 a)) #

gmapT :: (forall b. Data b => b -> b) -> Std140 a -> Std140 a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Std140 a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Std140 a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Std140 a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Std140 a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Std140 a -> m (Std140 a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Std140 a -> m (Std140 a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Std140 a -> m (Std140 a) #

Block a => Storable (Std140 a) Source # 
Instance details

Defined in Graphics.Gl.Block

Methods

sizeOf :: Std140 a -> Int #

alignment :: Std140 a -> Int #

peekElemOff :: Ptr (Std140 a) -> Int -> IO (Std140 a) #

pokeElemOff :: Ptr (Std140 a) -> Int -> Std140 a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Std140 a) #

pokeByteOff :: Ptr b -> Int -> Std140 a -> IO () #

peek :: Ptr (Std140 a) -> IO (Std140 a) #

poke :: Ptr (Std140 a) -> Std140 a -> IO () #

Generic (Std140 a) Source # 
Instance details

Defined in Graphics.Gl.Block

Associated Types

type Rep (Std140 a) :: Type -> Type #

Methods

from :: Std140 a -> Rep (Std140 a) x #

to :: Rep (Std140 a) x -> Std140 a #

Read a => Read (Std140 a) Source # 
Instance details

Defined in Graphics.Gl.Block

Show a => Show (Std140 a) Source # 
Instance details

Defined in Graphics.Gl.Block

Methods

showsPrec :: Int -> Std140 a -> ShowS #

show :: Std140 a -> String #

showList :: [Std140 a] -> ShowS #

Eq a => Eq (Std140 a) Source # 
Instance details

Defined in Graphics.Gl.Block

Methods

(==) :: Std140 a -> Std140 a -> Bool #

(/=) :: Std140 a -> Std140 a -> Bool #

Ord a => Ord (Std140 a) Source # 
Instance details

Defined in Graphics.Gl.Block

Methods

compare :: Std140 a -> Std140 a -> Ordering #

(<) :: Std140 a -> Std140 a -> Bool #

(<=) :: Std140 a -> Std140 a -> Bool #

(>) :: Std140 a -> Std140 a -> Bool #

(>=) :: Std140 a -> Std140 a -> Bool #

max :: Std140 a -> Std140 a -> Std140 a #

min :: Std140 a -> Std140 a -> Std140 a #

type Rep (Std140 a) Source # 
Instance details

Defined in Graphics.Gl.Block

type Rep (Std140 a) = D1 ('MetaData "Std140" "Graphics.Gl.Block" "gl-block-1.0-9KxWvhJL6MZ4sPMBjpKfRA" 'True) (C1 ('MetaCons "Std140" 'PrefixI 'True) (S1 ('MetaSel ('Just "getStd140") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

newtype Std430 a Source #

Constructors

Std430 

Fields

Instances

Instances details
Foldable Std430 Source # 
Instance details

Defined in Graphics.Gl.Block

Methods

fold :: Monoid m => Std430 m -> m #

foldMap :: Monoid m => (a -> m) -> Std430 a -> m #

foldMap' :: Monoid m => (a -> m) -> Std430 a -> m #

foldr :: (a -> b -> b) -> b -> Std430 a -> b #

foldr' :: (a -> b -> b) -> b -> Std430 a -> b #

foldl :: (b -> a -> b) -> b -> Std430 a -> b #

foldl' :: (b -> a -> b) -> b -> Std430 a -> b #

foldr1 :: (a -> a -> a) -> Std430 a -> a #

foldl1 :: (a -> a -> a) -> Std430 a -> a #

toList :: Std430 a -> [a] #

null :: Std430 a -> Bool #

length :: Std430 a -> Int #

elem :: Eq a => a -> Std430 a -> Bool #

maximum :: Ord a => Std430 a -> a #

minimum :: Ord a => Std430 a -> a #

sum :: Num a => Std430 a -> a #

product :: Num a => Std430 a -> a #

Traversable Std430 Source # 
Instance details

Defined in Graphics.Gl.Block

Methods

traverse :: Applicative f => (a -> f b) -> Std430 a -> f (Std430 b) #

sequenceA :: Applicative f => Std430 (f a) -> f (Std430 a) #

mapM :: Monad m => (a -> m b) -> Std430 a -> m (Std430 b) #

sequence :: Monad m => Std430 (m a) -> m (Std430 a) #

Functor Std430 Source # 
Instance details

Defined in Graphics.Gl.Block

Methods

fmap :: (a -> b) -> Std430 a -> Std430 b #

(<$) :: a -> Std430 b -> Std430 a #

Data a => Data (Std430 a) Source # 
Instance details

Defined in Graphics.Gl.Block

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Std430 a -> c (Std430 a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Std430 a) #

toConstr :: Std430 a -> Constr #

dataTypeOf :: Std430 a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Std430 a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Std430 a)) #

gmapT :: (forall b. Data b => b -> b) -> Std430 a -> Std430 a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Std430 a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Std430 a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Std430 a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Std430 a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Std430 a -> m (Std430 a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Std430 a -> m (Std430 a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Std430 a -> m (Std430 a) #

Block a => Storable (Std430 a) Source # 
Instance details

Defined in Graphics.Gl.Block

Methods

sizeOf :: Std430 a -> Int #

alignment :: Std430 a -> Int #

peekElemOff :: Ptr (Std430 a) -> Int -> IO (Std430 a) #

pokeElemOff :: Ptr (Std430 a) -> Int -> Std430 a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Std430 a) #

pokeByteOff :: Ptr b -> Int -> Std430 a -> IO () #

peek :: Ptr (Std430 a) -> IO (Std430 a) #

poke :: Ptr (Std430 a) -> Std430 a -> IO () #

Generic (Std430 a) Source # 
Instance details

Defined in Graphics.Gl.Block

Associated Types

type Rep (Std430 a) :: Type -> Type #

Methods

from :: Std430 a -> Rep (Std430 a) x #

to :: Rep (Std430 a) x -> Std430 a #

Read a => Read (Std430 a) Source # 
Instance details

Defined in Graphics.Gl.Block

Show a => Show (Std430 a) Source # 
Instance details

Defined in Graphics.Gl.Block

Methods

showsPrec :: Int -> Std430 a -> ShowS #

show :: Std430 a -> String #

showList :: [Std430 a] -> ShowS #

Eq a => Eq (Std430 a) Source # 
Instance details

Defined in Graphics.Gl.Block

Methods

(==) :: Std430 a -> Std430 a -> Bool #

(/=) :: Std430 a -> Std430 a -> Bool #

Ord a => Ord (Std430 a) Source # 
Instance details

Defined in Graphics.Gl.Block

Methods

compare :: Std430 a -> Std430 a -> Ordering #

(<) :: Std430 a -> Std430 a -> Bool #

(<=) :: Std430 a -> Std430 a -> Bool #

(>) :: Std430 a -> Std430 a -> Bool #

(>=) :: Std430 a -> Std430 a -> Bool #

max :: Std430 a -> Std430 a -> Std430 a #

min :: Std430 a -> Std430 a -> Std430 a #

type Rep (Std430 a) Source # 
Instance details

Defined in Graphics.Gl.Block

type Rep (Std430 a) = D1 ('MetaData "Std430" "Graphics.Gl.Block" "gl-block-1.0-9KxWvhJL6MZ4sPMBjpKfRA" 'True) (C1 ('MetaCons "Std430" 'PrefixI 'True) (S1 ('MetaSel ('Just "getStd430") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

roundUp :: Int -> Int -> Int Source #

roundUp k n rounds up k up to an integral multiple of n