ombra-0.3.0.0: Render engine.

Safe HaskellNone
LanguageHaskell2010

Graphics.Rendering.Ombra.Vector

Documentation

module Data.Cross

data Vec2 Source #

Constructors

Vec2 !Float !Float 

Instances

Eq Vec2 Source # 

Methods

(==) :: Vec2 -> Vec2 -> Bool #

(/=) :: Vec2 -> Vec2 -> Bool #

Show Vec2 Source # 

Methods

showsPrec :: Int -> Vec2 -> ShowS #

show :: Vec2 -> String #

showList :: [Vec2] -> ShowS #

Generic Vec2 Source # 

Associated Types

type Rep Vec2 :: * -> * #

Methods

from :: Vec2 -> Rep Vec2 x #

to :: Rep Vec2 x -> Vec2 #

Storable Vec2 Source # 

Methods

sizeOf :: Vec2 -> Int #

alignment :: Vec2 -> Int #

peekElemOff :: Ptr Vec2 -> Int -> IO Vec2 #

pokeElemOff :: Ptr Vec2 -> Int -> Vec2 -> IO () #

peekByteOff :: Ptr b -> Int -> IO Vec2 #

pokeByteOff :: Ptr b -> Int -> Vec2 -> IO () #

peek :: Ptr Vec2 -> IO Vec2 #

poke :: Ptr Vec2 -> Vec2 -> IO () #

Hashable Vec2 Source # 

Methods

hashWithSalt :: Int -> Vec2 -> Int #

hash :: Vec2 -> Int #

VectorSpace Vec2 Source # 

Associated Types

type Scalar Vec2 :: * #

Methods

(*^) :: Scalar Vec2 -> Vec2 -> Vec2 #

InnerSpace Vec2 Source # 

Methods

(<.>) :: Vec2 -> Vec2 -> Scalar Vec2 #

AdditiveGroup Vec2 Source # 

Methods

zeroV :: Vec2 #

(^+^) :: Vec2 -> Vec2 -> Vec2 #

negateV :: Vec2 -> Vec2 #

(^-^) :: Vec2 -> Vec2 -> Vec2 #

Ext Vec2 Source # 

Associated Types

type Extended Vec2 = (w :: *) Source #

type Rep Vec2 Source # 
type Rep Vec2 = D1 (MetaData "Vec2" "Graphics.Rendering.Ombra.Vector" "ombra-0.3.0.0-AelVPs5t89yJbS9QoxoRjc" False) (C1 (MetaCons "Vec2" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 Float)) (S1 (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 Float))))
type Scalar Vec2 Source # 
type Extended Vec2 Source # 

data Vec3 Source #

Constructors

Vec3 !Float !Float !Float 

Instances

Eq Vec3 Source # 

Methods

(==) :: Vec3 -> Vec3 -> Bool #

(/=) :: Vec3 -> Vec3 -> Bool #

Show Vec3 Source # 

Methods

showsPrec :: Int -> Vec3 -> ShowS #

show :: Vec3 -> String #

showList :: [Vec3] -> ShowS #

Generic Vec3 Source # 

Associated Types

type Rep Vec3 :: * -> * #

Methods

from :: Vec3 -> Rep Vec3 x #

to :: Rep Vec3 x -> Vec3 #

Storable Vec3 Source # 

Methods

sizeOf :: Vec3 -> Int #

alignment :: Vec3 -> Int #

peekElemOff :: Ptr Vec3 -> Int -> IO Vec3 #

pokeElemOff :: Ptr Vec3 -> Int -> Vec3 -> IO () #

peekByteOff :: Ptr b -> Int -> IO Vec3 #

pokeByteOff :: Ptr b -> Int -> Vec3 -> IO () #

peek :: Ptr Vec3 -> IO Vec3 #

poke :: Ptr Vec3 -> Vec3 -> IO () #

Hashable Vec3 Source # 

Methods

hashWithSalt :: Int -> Vec3 -> Int #

hash :: Vec3 -> Int #

HasCross3 Vec3 Source # 

Methods

cross3 :: Vec3 -> Vec3 -> Vec3 #

VectorSpace Vec3 Source # 

Associated Types

type Scalar Vec3 :: * #

Methods

(*^) :: Scalar Vec3 -> Vec3 -> Vec3 #

InnerSpace Vec3 Source # 

Methods

(<.>) :: Vec3 -> Vec3 -> Scalar Vec3 #

AdditiveGroup Vec3 Source # 

Methods

zeroV :: Vec3 #

(^+^) :: Vec3 -> Vec3 -> Vec3 #

negateV :: Vec3 -> Vec3 #

(^-^) :: Vec3 -> Vec3 -> Vec3 #

Ext Vec3 Source # 

Associated Types

type Extended Vec3 = (w :: *) Source #

type Rep Vec3 Source # 
type Scalar Vec3 Source # 
type Extended Vec3 Source # 

data Vec4 Source #

Constructors

Vec4 !Float !Float !Float !Float 

Instances

Eq Vec4 Source # 

Methods

(==) :: Vec4 -> Vec4 -> Bool #

(/=) :: Vec4 -> Vec4 -> Bool #

Show Vec4 Source # 

Methods

showsPrec :: Int -> Vec4 -> ShowS #

show :: Vec4 -> String #

showList :: [Vec4] -> ShowS #

Generic Vec4 Source # 

Associated Types

type Rep Vec4 :: * -> * #

Methods

from :: Vec4 -> Rep Vec4 x #

to :: Rep Vec4 x -> Vec4 #

Storable Vec4 Source # 

Methods

sizeOf :: Vec4 -> Int #

alignment :: Vec4 -> Int #

peekElemOff :: Ptr Vec4 -> Int -> IO Vec4 #

pokeElemOff :: Ptr Vec4 -> Int -> Vec4 -> IO () #

peekByteOff :: Ptr b -> Int -> IO Vec4 #

pokeByteOff :: Ptr b -> Int -> Vec4 -> IO () #

peek :: Ptr Vec4 -> IO Vec4 #

poke :: Ptr Vec4 -> Vec4 -> IO () #

Hashable Vec4 Source # 

Methods

hashWithSalt :: Int -> Vec4 -> Int #

hash :: Vec4 -> Int #

VectorSpace Vec4 Source # 

Associated Types

type Scalar Vec4 :: * #

Methods

(*^) :: Scalar Vec4 -> Vec4 -> Vec4 #

InnerSpace Vec4 Source # 

Methods

(<.>) :: Vec4 -> Vec4 -> Scalar Vec4 #

AdditiveGroup Vec4 Source # 

Methods

zeroV :: Vec4 #

(^+^) :: Vec4 -> Vec4 -> Vec4 #

negateV :: Vec4 -> Vec4 #

(^-^) :: Vec4 -> Vec4 -> Vec4 #

type Rep Vec4 Source # 
type Scalar Vec4 Source # 

data Mat2 Source #

Constructors

Mat2 !Vec2 !Vec2 

Instances

Eq Mat2 Source # 

Methods

(==) :: Mat2 -> Mat2 -> Bool #

(/=) :: Mat2 -> Mat2 -> Bool #

Show Mat2 Source # 

Methods

showsPrec :: Int -> Mat2 -> ShowS #

show :: Mat2 -> String #

showList :: [Mat2] -> ShowS #

Generic Mat2 Source # 

Associated Types

type Rep Mat2 :: * -> * #

Methods

from :: Mat2 -> Rep Mat2 x #

to :: Rep Mat2 x -> Mat2 #

Hashable Mat2 Source # 

Methods

hashWithSalt :: Int -> Mat2 -> Int #

hash :: Mat2 -> Int #

VectorSpace Mat2 Source # 

Associated Types

type Scalar Mat2 :: * #

Methods

(*^) :: Scalar Mat2 -> Mat2 -> Mat2 #

AdditiveGroup Mat2 Source # 

Methods

zeroV :: Mat2 #

(^+^) :: Mat2 -> Mat2 -> Mat2 #

negateV :: Mat2 -> Mat2 #

(^-^) :: Mat2 -> Mat2 -> Mat2 #

Matrix Mat2 Source # 

Associated Types

type Row Mat2 = (b :: *) Source #

Ext Mat2 Source # 

Associated Types

type Extended Mat2 = (w :: *) Source #

type Rep Mat2 Source # 
type Rep Mat2 = D1 (MetaData "Mat2" "Graphics.Rendering.Ombra.Vector" "ombra-0.3.0.0-AelVPs5t89yJbS9QoxoRjc" False) (C1 (MetaCons "Mat2" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Vec2)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Vec2))))
type Scalar Mat2 Source # 
type Row Mat2 Source # 
type Row Mat2 = Vec2
type Extended Mat2 Source # 

data Mat3 Source #

Constructors

Mat3 !Vec3 !Vec3 !Vec3 

Instances

Eq Mat3 Source # 

Methods

(==) :: Mat3 -> Mat3 -> Bool #

(/=) :: Mat3 -> Mat3 -> Bool #

Show Mat3 Source # 

Methods

showsPrec :: Int -> Mat3 -> ShowS #

show :: Mat3 -> String #

showList :: [Mat3] -> ShowS #

Generic Mat3 Source # 

Associated Types

type Rep Mat3 :: * -> * #

Methods

from :: Mat3 -> Rep Mat3 x #

to :: Rep Mat3 x -> Mat3 #

Hashable Mat3 Source # 

Methods

hashWithSalt :: Int -> Mat3 -> Int #

hash :: Mat3 -> Int #

VectorSpace Mat3 Source # 

Associated Types

type Scalar Mat3 :: * #

Methods

(*^) :: Scalar Mat3 -> Mat3 -> Mat3 #

AdditiveGroup Mat3 Source # 

Methods

zeroV :: Mat3 #

(^+^) :: Mat3 -> Mat3 -> Mat3 #

negateV :: Mat3 -> Mat3 #

(^-^) :: Mat3 -> Mat3 -> Mat3 #

Matrix Mat3 Source # 

Associated Types

type Row Mat3 = (b :: *) Source #

Ext Mat3 Source # 

Associated Types

type Extended Mat3 = (w :: *) Source #

type Rep Mat3 Source # 
type Scalar Mat3 Source # 
type Row Mat3 Source # 
type Row Mat3 = Vec3
type Extended Mat3 Source # 

data Mat4 Source #

Constructors

Mat4 !Vec4 !Vec4 !Vec4 !Vec4 

Instances

Eq Mat4 Source # 

Methods

(==) :: Mat4 -> Mat4 -> Bool #

(/=) :: Mat4 -> Mat4 -> Bool #

Show Mat4 Source # 

Methods

showsPrec :: Int -> Mat4 -> ShowS #

show :: Mat4 -> String #

showList :: [Mat4] -> ShowS #

Generic Mat4 Source # 

Associated Types

type Rep Mat4 :: * -> * #

Methods

from :: Mat4 -> Rep Mat4 x #

to :: Rep Mat4 x -> Mat4 #

Hashable Mat4 Source # 

Methods

hashWithSalt :: Int -> Mat4 -> Int #

hash :: Mat4 -> Int #

VectorSpace Mat4 Source # 

Associated Types

type Scalar Mat4 :: * #

Methods

(*^) :: Scalar Mat4 -> Mat4 -> Mat4 #

AdditiveGroup Mat4 Source # 

Methods

zeroV :: Mat4 #

(^+^) :: Mat4 -> Mat4 -> Mat4 #

negateV :: Mat4 -> Mat4 #

(^-^) :: Mat4 -> Mat4 -> Mat4 #

Matrix Mat4 Source # 

Associated Types

type Row Mat4 = (b :: *) Source #

type Rep Mat4 Source # 
type Scalar Mat4 Source # 
type Row Mat4 Source # 
type Row Mat4 = Vec4

data IVec2 Source #

Constructors

IVec2 !Int32 !Int32 

Instances

Eq IVec2 Source # 

Methods

(==) :: IVec2 -> IVec2 -> Bool #

(/=) :: IVec2 -> IVec2 -> Bool #

Show IVec2 Source # 

Methods

showsPrec :: Int -> IVec2 -> ShowS #

show :: IVec2 -> String #

showList :: [IVec2] -> ShowS #

Generic IVec2 Source # 

Associated Types

type Rep IVec2 :: * -> * #

Methods

from :: IVec2 -> Rep IVec2 x #

to :: Rep IVec2 x -> IVec2 #

Storable IVec2 Source # 

Methods

sizeOf :: IVec2 -> Int #

alignment :: IVec2 -> Int #

peekElemOff :: Ptr IVec2 -> Int -> IO IVec2 #

pokeElemOff :: Ptr IVec2 -> Int -> IVec2 -> IO () #

peekByteOff :: Ptr b -> Int -> IO IVec2 #

pokeByteOff :: Ptr b -> Int -> IVec2 -> IO () #

peek :: Ptr IVec2 -> IO IVec2 #

poke :: Ptr IVec2 -> IVec2 -> IO () #

Hashable IVec2 Source # 

Methods

hashWithSalt :: Int -> IVec2 -> Int #

hash :: IVec2 -> Int #

type Rep IVec2 Source # 
type Rep IVec2 = D1 (MetaData "IVec2" "Graphics.Rendering.Ombra.Vector" "ombra-0.3.0.0-AelVPs5t89yJbS9QoxoRjc" False) (C1 (MetaCons "IVec2" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 Int32)) (S1 (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 Int32))))

data IVec3 Source #

Constructors

IVec3 !Int32 !Int32 !Int32 

Instances

Eq IVec3 Source # 

Methods

(==) :: IVec3 -> IVec3 -> Bool #

(/=) :: IVec3 -> IVec3 -> Bool #

Show IVec3 Source # 

Methods

showsPrec :: Int -> IVec3 -> ShowS #

show :: IVec3 -> String #

showList :: [IVec3] -> ShowS #

Generic IVec3 Source # 

Associated Types

type Rep IVec3 :: * -> * #

Methods

from :: IVec3 -> Rep IVec3 x #

to :: Rep IVec3 x -> IVec3 #

Storable IVec3 Source # 

Methods

sizeOf :: IVec3 -> Int #

alignment :: IVec3 -> Int #

peekElemOff :: Ptr IVec3 -> Int -> IO IVec3 #

pokeElemOff :: Ptr IVec3 -> Int -> IVec3 -> IO () #

peekByteOff :: Ptr b -> Int -> IO IVec3 #

pokeByteOff :: Ptr b -> Int -> IVec3 -> IO () #

peek :: Ptr IVec3 -> IO IVec3 #

poke :: Ptr IVec3 -> IVec3 -> IO () #

Hashable IVec3 Source # 

Methods

hashWithSalt :: Int -> IVec3 -> Int #

hash :: IVec3 -> Int #

type Rep IVec3 Source # 

data IVec4 Source #

Constructors

IVec4 !Int32 !Int32 !Int32 !Int32 

class Matrix a where Source #

Minimal complete definition

idmtx, transpose, (.*.), (.*)

Associated Types

type Row a = b | b -> a Source #

Methods

idmtx :: a Source #

transpose :: a -> a Source #

(.*.) :: a -> a -> a infixl 7 Source #

(.*) :: a -> Row a -> Row a infixl 7 Source #

(*.) :: Row a -> a -> Row a infixr 7 Source #

Instances

Matrix Mat4 Source # 

Associated Types

type Row Mat4 = (b :: *) Source #

Matrix Mat3 Source # 

Associated Types

type Row Mat3 = (b :: *) Source #

Matrix Mat2 Source # 

Associated Types

type Row Mat2 = (b :: *) Source #

class VectorSpace v => Ext v where Source #

Minimal complete definition

(^|), (^|^), extract

Associated Types

type Extended v = w | w -> v Source #

Methods

(^|) :: v -> Scalar v -> Extended v infixr 5 Source #

Extend the vector with a specified scalar.

(^|^) :: v -> Extended v -> Extended v infixr 5 Source #

Extend the first vector using the components of the second vector.

For instance: Mat2 (Vec2 x y) (Vec2 z w) ^|^ idmtx = Mat3 (Vec3 x y 0) (Vec3 z w 0) (Vec3 0 0 1)

extract :: Extended v -> v Source #

Extract a smaller vector.