geomancy-0.2.6.0: Geometry and matrix manipulation
Safe HaskellSafe-Inferred
LanguageHaskell2010

Geomancy.Vec4

Description

Specialized and inlined V4 Float.

Documentation

data Vec4 Source #

Constructors

Vec4 ByteArray# 

Instances

Instances details
Storable Vec4 Source # 
Instance details

Defined in Geomancy.Vec4

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 () #

Floating Vec4 Source # 
Instance details

Defined in Geomancy.Vec4

Methods

pi :: Vec4 #

exp :: Vec4 -> Vec4 #

log :: Vec4 -> Vec4 #

sqrt :: Vec4 -> Vec4 #

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

logBase :: Vec4 -> Vec4 -> Vec4 #

sin :: Vec4 -> Vec4 #

cos :: Vec4 -> Vec4 #

tan :: Vec4 -> Vec4 #

asin :: Vec4 -> Vec4 #

acos :: Vec4 -> Vec4 #

atan :: Vec4 -> Vec4 #

sinh :: Vec4 -> Vec4 #

cosh :: Vec4 -> Vec4 #

tanh :: Vec4 -> Vec4 #

asinh :: Vec4 -> Vec4 #

acosh :: Vec4 -> Vec4 #

atanh :: Vec4 -> Vec4 #

log1p :: Vec4 -> Vec4 #

expm1 :: Vec4 -> Vec4 #

log1pexp :: Vec4 -> Vec4 #

log1mexp :: Vec4 -> Vec4 #

Num Vec4 Source # 
Instance details

Defined in Geomancy.Vec4

Methods

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

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

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

negate :: Vec4 -> Vec4 #

abs :: Vec4 -> Vec4 #

signum :: Vec4 -> Vec4 #

fromInteger :: Integer -> Vec4 #

Fractional Vec4 Source # 
Instance details

Defined in Geomancy.Vec4

Methods

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

recip :: Vec4 -> Vec4 #

fromRational :: Rational -> Vec4 #

Show Vec4 Source # 
Instance details

Defined in Geomancy.Vec4

Methods

showsPrec :: Int -> Vec4 -> ShowS #

show :: Vec4 -> String #

showList :: [Vec4] -> ShowS #

NFData Vec4 Source # 
Instance details

Defined in Geomancy.Vec4

Methods

rnf :: Vec4 -> () #

Elementwise Vec4 Source # 
Instance details

Defined in Geomancy.Vec4

GlNearest Vec4 Source # 
Instance details

Defined in Geomancy.Vec4

Eq Vec4 Source # 
Instance details

Defined in Geomancy.Vec4

Methods

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

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

Ord Vec4 Source # 
Instance details

Defined in Geomancy.Vec4

Methods

compare :: Vec4 -> Vec4 -> Ordering #

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

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

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

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

max :: Vec4 -> Vec4 -> Vec4 #

min :: Vec4 -> Vec4 -> Vec4 #

Block Vec4 Source # 
Instance details

Defined in Geomancy.Vec4

Associated Types

type PackedSize Vec4 :: Nat #

Methods

alignment140 :: proxy Vec4 -> Int #

sizeOf140 :: proxy Vec4 -> Int #

isStruct :: proxy Vec4 -> Bool #

read140 :: MonadIO m => Ptr a -> Diff a Vec4 -> m Vec4 #

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

alignment430 :: proxy Vec4 -> Int #

sizeOf430 :: proxy Vec4 -> Int #

read430 :: MonadIO m => Ptr a -> Diff a Vec4 -> m Vec4 #

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

sizeOfPacked :: proxy Vec4 -> Int #

readPacked :: MonadIO m => Ptr a -> Diff a Vec4 -> m Vec4 #

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

MonoFunctor Vec4 Source # 
Instance details

Defined in Geomancy.Vec4

Methods

omap :: (Element Vec4 -> Element Vec4) -> Vec4 -> Vec4 #

MonoPointed Vec4 Source # 
Instance details

Defined in Geomancy.Vec4

Methods

opoint :: Element Vec4 -> Vec4 #

GlModf Vec4 Vec4 Source # 
Instance details

Defined in Geomancy.Vec4

Methods

glModf :: Vec4 -> (Vec4, Vec4) Source #

VectorSpace Vec4 Float Source # 
Instance details

Defined in Geomancy.Vec4

type PackedSize Vec4 Source # 
Instance details

Defined in Geomancy.Vec4

type PackedSize Vec4 = 16
type Element Vec4 Source # 
Instance details

Defined in Geomancy.Vec4

withVec4 :: Vec4 -> (Float -> Float -> Float -> Float -> r) -> r Source #

pattern WithVec4 :: Float -> Float -> Float -> Float -> Vec4 Source #

convert :: Coercible v Vec4 => (Float -> a) -> (a -> a -> a -> a -> r) -> v -> r Source #