luminance-0.11.0.4: Type-safe, type-level and stateless graphics framework

Copyright(C) 2015, 2016 Dimitri Sabadie
LicenseBSD3
MaintainerDimitri Sabadie <dimitri.sabadie@gmail.com>
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Graphics.Luminance.Vertex

Contents

Description

 

Synopsis

Vertex components

data V k n a :: forall k. k -> * -> * #

Instances

FunctorWithIndex Int (V k n) 

Methods

imap :: (Int -> a -> b) -> V k n a -> V k n b #

imapped :: (Indexable Int p, Settable f) => p a (f b) -> V k n a -> f (V k n b) #

FoldableWithIndex Int (V k n) 

Methods

ifoldMap :: Monoid m => (Int -> a -> m) -> V k n a -> m #

ifolded :: (Indexable Int p, Contravariant f, Applicative f) => p a (f a) -> V k n a -> f (V k n a) #

ifoldr :: (Int -> a -> b -> b) -> b -> V k n a -> b #

ifoldl :: (Int -> b -> a -> b) -> b -> V k n a -> b #

ifoldr' :: (Int -> a -> b -> b) -> b -> V k n a -> b #

ifoldl' :: (Int -> b -> a -> b) -> b -> V k n a -> b #

TraversableWithIndex Int (V k n) 

Methods

itraverse :: Applicative f => (Int -> a -> f b) -> V k n a -> f (V k n b) #

itraversed :: (Indexable Int p, Applicative f) => p a (f b) -> V k n a -> f (V k n b) #

(Dim k n, Unbox a) => Vector Vector (V k n a) 

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (V k n a) -> m (Vector (V k n a)) #

basicUnsafeThaw :: PrimMonad m => Vector (V k n a) -> m (Mutable Vector (PrimState m) (V k n a)) #

basicLength :: Vector (V k n a) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (V k n a) -> Vector (V k n a) #

basicUnsafeIndexM :: Monad m => Vector (V k n a) -> Int -> m (V k n a) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (V k n a) -> Vector (V k n a) -> m () #

elemseq :: Vector (V k n a) -> V k n a -> b -> b #

(Dim k n, Unbox a) => MVector MVector (V k n a) 

Methods

basicLength :: MVector s (V k n a) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (V k n a) -> MVector s (V k n a) #

basicOverlaps :: MVector s (V k n a) -> MVector s (V k n a) -> Bool #

basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (V k n a)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (V k n a) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> V k n a -> m (MVector (PrimState m) (V k n a)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (V k n a) -> Int -> m (V k n a) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (V k n a) -> Int -> V k n a -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (V k n a) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (V k n a) -> V k n a -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (V k n a) -> MVector (PrimState m) (V k n a) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (V k n a) -> MVector (PrimState m) (V k n a) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (V k n a) -> Int -> m (MVector (PrimState m) (V k n a)) #

Uniform [V Nat 2 Float] Source # 

Methods

toU :: Monad m => GLuint -> GLint -> UniformInterface m (U [V Nat 2 Float])

Uniform [V Nat 2 Int32] Source # 

Methods

toU :: Monad m => GLuint -> GLint -> UniformInterface m (U [V Nat 2 Int32])

Uniform [V Nat 2 Word32] Source # 

Methods

toU :: Monad m => GLuint -> GLint -> UniformInterface m (U [V Nat 2 Word32])

Uniform [V Nat 3 Float] Source # 

Methods

toU :: Monad m => GLuint -> GLint -> UniformInterface m (U [V Nat 3 Float])

Uniform [V Nat 3 Int32] Source # 

Methods

toU :: Monad m => GLuint -> GLint -> UniformInterface m (U [V Nat 3 Int32])

Uniform [V Nat 3 Word32] Source # 

Methods

toU :: Monad m => GLuint -> GLint -> UniformInterface m (U [V Nat 3 Word32])

Uniform [V Nat 4 Float] Source # 

Methods

toU :: Monad m => GLuint -> GLint -> UniformInterface m (U [V Nat 4 Float])

Uniform [V Nat 4 Int32] Source # 

Methods

toU :: Monad m => GLuint -> GLint -> UniformInterface m (U [V Nat 4 Int32])

Uniform [V Nat 4 Word32] Source # 

Methods

toU :: Monad m => GLuint -> GLint -> UniformInterface m (U [V Nat 4 Word32])

Dim k n => Dim * (V k n a) 

Methods

reflectDim :: p n -> Int #

Dim k n => Monad (V k n) 

Methods

(>>=) :: V k n a -> (a -> V k n b) -> V k n b #

(>>) :: V k n a -> V k n b -> V k n b #

return :: a -> V k n a #

fail :: String -> V k n a #

Functor (V k n) 

Methods

fmap :: (a -> b) -> V k n a -> V k n b #

(<$) :: a -> V k n b -> V k n a #

Dim k n => MonadFix (V k n) 

Methods

mfix :: (a -> V k n a) -> V k n a #

Dim k n => Applicative (V k n) 

Methods

pure :: a -> V k n a #

(<*>) :: V k n (a -> b) -> V k n a -> V k n b #

(*>) :: V k n a -> V k n b -> V k n b #

(<*) :: V k n a -> V k n b -> V k n a #

Foldable (V k n) 

Methods

fold :: Monoid m => V k n m -> m #

foldMap :: Monoid m => (a -> m) -> V k n a -> m #

foldr :: (a -> b -> b) -> b -> V k n a -> b #

foldr' :: (a -> b -> b) -> b -> V k n a -> b #

foldl :: (b -> a -> b) -> b -> V k n a -> b #

foldl' :: (b -> a -> b) -> b -> V k n a -> b #

foldr1 :: (a -> a -> a) -> V k n a -> a #

foldl1 :: (a -> a -> a) -> V k n a -> a #

toList :: V k n a -> [a] #

null :: V k n a -> Bool #

length :: V k n a -> Int #

elem :: Eq a => a -> V k n a -> Bool #

maximum :: Ord a => V k n a -> a #

minimum :: Ord a => V k n a -> a #

sum :: Num a => V k n a -> a #

product :: Num a => V k n a -> a #

Traversable (V k n) 

Methods

traverse :: Applicative f => (a -> f b) -> V k n a -> f (V k n b) #

sequenceA :: Applicative f => V k n (f a) -> f (V k n a) #

mapM :: Monad m => (a -> m b) -> V k n a -> m (V k n b) #

sequence :: Monad m => V k n (m a) -> m (V k n a) #

Generic1 (V k n) 

Associated Types

type Rep1 (V k n :: * -> *) :: * -> * #

Methods

from1 :: V k n a -> Rep1 (V k n) a #

to1 :: Rep1 (V k n) a -> V k n a #

Dim k n => Distributive (V k n) 

Methods

distribute :: Functor f => f (V k n a) -> V k n (f a) #

collect :: Functor f => (a -> V k n b) -> f a -> V k n (f b) #

distributeM :: Monad m => m (V k n a) -> V k n (m a) #

collectM :: Monad m => (a -> V k n b) -> m a -> V k n (m b) #

Dim k n => Representable (V k n) 

Associated Types

type Rep (V k n :: * -> *) :: * #

Methods

tabulate :: (Rep (V k n) -> a) -> V k n a #

index :: V k n a -> Rep (V k n) -> a #

Eq1 (V k n) 

Methods

liftEq :: (a -> b -> Bool) -> V k n a -> V k n b -> Bool #

Ord1 (V k n) 

Methods

liftCompare :: (a -> b -> Ordering) -> V k n a -> V k n b -> Ordering #

Dim k n => Read1 (V k n) 

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (V k n a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [V k n a] #

Show1 (V k n) 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> V k n a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [V k n a] -> ShowS #

Dim k n => MonadZip (V k n) 

Methods

mzip :: V k n a -> V k n b -> V k n (a, b) #

mzipWith :: (a -> b -> c) -> V k n a -> V k n b -> V k n c #

munzip :: V k n (a, b) -> (V k n a, V k n b) #

Dim k n => Serial1 (V k n) 

Methods

serializeWith :: MonadPut m => (a -> m ()) -> V k n a -> m () #

deserializeWith :: MonadGet m => m a -> m (V k n a) #

Dim k n => Metric (V k n) 

Methods

dot :: Num a => V k n a -> V k n a -> a #

quadrance :: Num a => V k n a -> a #

qd :: Num a => V k n a -> V k n a -> a #

distance :: Floating a => V k n a -> V k n a -> a #

norm :: Floating a => V k n a -> a #

signorm :: Floating a => V k n a -> V k n a #

Dim k n => Additive (V k n) 

Methods

zero :: Num a => V k n a #

(^+^) :: Num a => V k n a -> V k n a -> V k n a #

(^-^) :: Num a => V k n a -> V k n a -> V k n a #

lerp :: Num a => a -> V k n a -> V k n a -> V k n a #

liftU2 :: (a -> a -> a) -> V k n a -> V k n a -> V k n a #

liftI2 :: (a -> b -> c) -> V k n a -> V k n b -> V k n c #

Apply (V k n) 

Methods

(<.>) :: V k n (a -> b) -> V k n a -> V k n b #

(.>) :: V k n a -> V k n b -> V k n b #

(<.) :: V k n a -> V k n b -> V k n a #

Bind (V k n) 

Methods

(>>-) :: V k n a -> (a -> V k n b) -> V k n b #

join :: V k n (V k n a) -> V k n a #

(Bounded a, Dim k n) => Bounded (V k n a) 

Methods

minBound :: V k n a #

maxBound :: V k n a #

Eq a => Eq (V k n a) 

Methods

(==) :: V k n a -> V k n a -> Bool #

(/=) :: V k n a -> V k n a -> Bool #

(Dim k n, Floating a) => Floating (V k n a) 

Methods

pi :: V k n a #

exp :: V k n a -> V k n a #

log :: V k n a -> V k n a #

sqrt :: V k n a -> V k n a #

(**) :: V k n a -> V k n a -> V k n a #

logBase :: V k n a -> V k n a -> V k n a #

sin :: V k n a -> V k n a #

cos :: V k n a -> V k n a #

tan :: V k n a -> V k n a #

asin :: V k n a -> V k n a #

acos :: V k n a -> V k n a #

atan :: V k n a -> V k n a #

sinh :: V k n a -> V k n a #

cosh :: V k n a -> V k n a #

tanh :: V k n a -> V k n a #

asinh :: V k n a -> V k n a #

acosh :: V k n a -> V k n a #

atanh :: V k n a -> V k n a #

log1p :: V k n a -> V k n a #

expm1 :: V k n a -> V k n a #

log1pexp :: V k n a -> V k n a #

log1mexp :: V k n a -> V k n a #

(Dim k n, Fractional a) => Fractional (V k n a) 

Methods

(/) :: V k n a -> V k n a -> V k n a #

recip :: V k n a -> V k n a #

fromRational :: Rational -> V k n a #

(Typeable (* -> *) (V k n), Typeable * (V k n a), Dim k n, Data a) => Data (V k n a) 

Methods

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

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

toConstr :: V k n a -> Constr #

dataTypeOf :: V k n a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (V k n a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (V k n a)) #

gmapT :: (forall b. Data b => b -> b) -> V k n a -> V k n a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> V k n a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> V k n a -> r #

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

gmapQi :: Int -> (forall d. Data d => d -> u) -> V k n a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> V k n a -> m (V k n a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> V k n a -> m (V k n a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> V k n a -> m (V k n a) #

(Dim k n, Num a) => Num (V k n a) 

Methods

(+) :: V k n a -> V k n a -> V k n a #

(-) :: V k n a -> V k n a -> V k n a #

(*) :: V k n a -> V k n a -> V k n a #

negate :: V k n a -> V k n a #

abs :: V k n a -> V k n a #

signum :: V k n a -> V k n a #

fromInteger :: Integer -> V k n a #

Ord a => Ord (V k n a) 

Methods

compare :: V k n a -> V k n a -> Ordering #

(<) :: V k n a -> V k n a -> Bool #

(<=) :: V k n a -> V k n a -> Bool #

(>) :: V k n a -> V k n a -> Bool #

(>=) :: V k n a -> V k n a -> Bool #

max :: V k n a -> V k n a -> V k n a #

min :: V k n a -> V k n a -> V k n a #

Read a => Read (V k n a) 

Methods

readsPrec :: Int -> ReadS (V k n a) #

readList :: ReadS [V k n a] #

readPrec :: ReadPrec (V k n a) #

readListPrec :: ReadPrec [V k n a] #

Show a => Show (V k n a) 

Methods

showsPrec :: Int -> V k n a -> ShowS #

show :: V k n a -> String #

showList :: [V k n a] -> ShowS #

Generic (V k n a) 

Associated Types

type Rep (V k n a) :: * -> * #

Methods

from :: V k n a -> Rep (V k n a) x #

to :: Rep (V k n a) x -> V k n a #

(Dim k n, Storable a) => Storable (V k n a) 

Methods

sizeOf :: V k n a -> Int #

alignment :: V k n a -> Int #

peekElemOff :: Ptr (V k n a) -> Int -> IO (V k n a) #

pokeElemOff :: Ptr (V k n a) -> Int -> V k n a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (V k n a) #

pokeByteOff :: Ptr b -> Int -> V k n a -> IO () #

peek :: Ptr (V k n a) -> IO (V k n a) #

poke :: Ptr (V k n a) -> V k n a -> IO () #

(Dim k n, Binary a) => Binary (V k n a) 

Methods

put :: V k n a -> Put #

get :: Get (V k n a) #

putList :: [V k n a] -> Put #

(Dim k n, Serial a) => Serial (V k n a) 

Methods

serialize :: MonadPut m => V k n a -> m () #

deserialize :: MonadGet m => m (V k n a) #

(Dim k n, Serialize a) => Serialize (V k n a) 

Methods

put :: Putter (V k n a) #

get :: Get (V k n a) #

NFData a => NFData (V k n a) 

Methods

rnf :: V k n a -> () #

(Dim k n, Unbox a) => Unbox (V k n a) 
Ixed (V k n a) 

Methods

ix :: Index (V k n a) -> Traversal' (V k n a) (IxValue (V k n a)) #

(Dim k n, Epsilon a) => Epsilon (V k n a) 

Methods

nearZero :: V k n a -> Bool #

Uniform (V Nat 2 Float) Source # 

Methods

toU :: Monad m => GLuint -> GLint -> UniformInterface m (U (V Nat 2 Float))

Uniform (V Nat 2 Int32) Source # 

Methods

toU :: Monad m => GLuint -> GLint -> UniformInterface m (U (V Nat 2 Int32))

Uniform (V Nat 2 Word32) Source # 

Methods

toU :: Monad m => GLuint -> GLint -> UniformInterface m (U (V Nat 2 Word32))

Uniform (V Nat 3 Float) Source # 

Methods

toU :: Monad m => GLuint -> GLint -> UniformInterface m (U (V Nat 3 Float))

Uniform (V Nat 3 Int32) Source # 

Methods

toU :: Monad m => GLuint -> GLint -> UniformInterface m (U (V Nat 3 Int32))

Uniform (V Nat 3 Word32) Source # 

Methods

toU :: Monad m => GLuint -> GLint -> UniformInterface m (U (V Nat 3 Word32))

Uniform (V Nat 4 Float) Source # 

Methods

toU :: Monad m => GLuint -> GLint -> UniformInterface m (U (V Nat 4 Float))

Uniform (V Nat 4 Int32) Source # 

Methods

toU :: Monad m => GLuint -> GLint -> UniformInterface m (U (V Nat 4 Int32))

Uniform (V Nat 4 Word32) Source # 

Methods

toU :: Monad m => GLuint -> GLint -> UniformInterface m (U (V Nat 4 Word32))

(KnownNat n, Storable a, VertexAttribute a) => Vertex (V Nat n a) Source # 

Methods

setFormatV :: MonadIO m => GLuint -> GLuint -> GLuint -> proxy (V Nat n a) -> m (GLuint, GLuint)

Each (V k n a) (V k n b) a b 

Methods

each :: Traversal (V k n a) (V k n b) a b #

data MVector s (V k n a) 
data MVector s (V k n a) = MV_VN ~Int ~(MVector s a)
type Rep1 (V k n) 
type Rep1 (V k n) = D1 (MetaData "V" "Linear.V" "linear-1.20.5-5Tgt1gTsoNi9Wd1re8ARtA" True) (C1 (MetaCons "V" PrefixI True) (S1 (MetaSel (Just Symbol "toVector") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 Vector)))
type Rep (V k n) 
type Rep (V k n) = Int
type Rep (V k n a) 
type Rep (V k n a) = D1 (MetaData "V" "Linear.V" "linear-1.20.5-5Tgt1gTsoNi9Wd1re8ARtA" True) (C1 (MetaCons "V" PrefixI True) (S1 (MetaSel (Just Symbol "toVector") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Vector a))))
data Vector (V k n a) 
data Vector (V k n a) = V_VN ~Int ~(Vector a)
type Index (V k n a) 
type Index (V k n a) = Int
type IxValue (V k n a) 
type IxValue (V k n a) = a

vec2 :: a -> a -> V 2 a Source #

Create a new V 2.

vec3 :: a -> a -> a -> V 3 a Source #

Create a new V 3.

vec4 :: a -> a -> a -> a -> V 4 a Source #

Create a new V 4.

class VertexAttribute a Source #

A vertex might have several attributes. The types of those attributes have to implement the VertexAttribute typeclass in order to be used as vertex attributes.

Minimal complete definition

vertexGLType

Vertex

class Vertex v Source #

A vertex has to implement Vertex in order to be used as-is. That typeclass is closed, so you cannot add anymore instances. However, you shouldn’t need to since you can use the already provided types to build up your vertex type.

Minimal complete definition

setFormatV

Instances

(Vertex a, Vertex b) => Vertex ((:.) a b) Source # 

Methods

setFormatV :: MonadIO m => GLuint -> GLuint -> GLuint -> proxy (a :. b) -> m (GLuint, GLuint)

(KnownNat n, Storable a, VertexAttribute a) => Vertex (V Nat n a) Source # 

Methods

setFormatV :: MonadIO m => GLuint -> GLuint -> GLuint -> proxy (V Nat n a) -> m (GLuint, GLuint)