| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Geomancy
Synopsis
- data Vec2
- vec2 :: Float -> Float -> Vec2
- withVec2 :: Vec2 -> (Float -> Float -> r) -> r
- pattern WithVec2 :: Float -> Float -> Vec2
- type Point2 = Point Vec2
- data Vec3
- vec3 :: Float -> Float -> Float -> Vec3
- withVec3 :: Vec3 -> (Float -> Float -> Float -> r) -> r
- pattern WithVec3 :: Float -> Float -> Float -> Vec3
- type Point3 = Point Vec3
- type Point3P = Point Packed
- data Vec4
- vec4 :: Float -> Float -> Float -> Float -> Vec4
- withVec4 :: Vec4 -> (Float -> Float -> Float -> Float -> r) -> r
- pattern WithVec4 :: Float -> Float -> Float -> Float -> Vec4
- type Point4 = Point Vec4
- data IVec2
- ivec2 :: Int32 -> Int32 -> IVec2
- withIVec2 :: IVec2 -> (Int32 -> Int32 -> r) -> r
- pattern WithIVec2 :: Int32 -> Int32 -> IVec2
- data IVec3
- ivec3 :: Int32 -> Int32 -> Int32 -> IVec3
- withIVec3 :: IVec3 -> (Int32 -> Int32 -> Int32 -> r) -> r
- pattern WithIVec3 :: Int32 -> Int32 -> Int32 -> IVec3
- data IVec4
- ivec4 :: Int32 -> Int32 -> Int32 -> Int32 -> IVec4
- withIVec4 :: IVec4 -> (Int32 -> Int32 -> Int32 -> Int32 -> r) -> r
- pattern WithIVec4 :: Int32 -> Int32 -> Int32 -> Int32 -> IVec4
- data UVec2
- uvec2 :: Word32 -> Word32 -> UVec2
- withUVec2 :: UVec2 -> (Word32 -> Word32 -> r) -> r
- pattern WithUVec2 :: Word32 -> Word32 -> UVec2
- data UVec3
- uvec3 :: Word32 -> Word32 -> Word32 -> UVec3
- withUVec3 :: UVec3 -> (Word32 -> Word32 -> Word32 -> r) -> r
- pattern WithUVec3 :: Word32 -> Word32 -> Word32 -> UVec3
- data UVec4
- uvec4 :: Word32 -> Word32 -> Word32 -> Word32 -> UVec4
- withUVec4 :: UVec4 -> (Word32 -> Word32 -> Word32 -> Word32 -> r) -> r
- pattern WithUVec4 :: Word32 -> Word32 -> Word32 -> Word32 -> UVec4
- class Elementwise a where
- epoint :: Element a -> a
- emap :: (Element a -> Element a) -> a -> a
- emap2 :: (Element a -> Element a -> Element a) -> a -> a -> a
- emap3 :: (Element a -> Element a -> Element a -> Element a) -> a -> a -> a -> a
- emap4 :: (Element a -> Element a -> Element a -> Element a -> Element a) -> a -> a -> a -> a -> a
- emap5 :: (Element a -> Element a -> Element a -> Element a -> Element a -> Element a) -> a -> a -> a -> a -> a -> a
- data Mat4
- newtype Transform = Transform {
- unTransform :: Mat4
- data Quaternion
- quaternion :: Float -> Float -> Float -> Float -> Quaternion
- withQuaternion :: Quaternion -> (Float -> Float -> Float -> Float -> r) -> r
- newtype Point v = Point v
- class (Floating a, VectorSpace v a) => AffineSpace p v a | p -> v, v -> a where
- class VectorSpace v a | v -> a where
- zeroVector :: v
- (*^) :: a -> v -> v
- (^/) :: v -> a -> v
- (^+^) :: v -> v -> v
- (^-^) :: v -> v -> v
- negateVector :: v -> v
- dot :: v -> v -> a
- norm :: v -> a
- normalize :: v -> v
- (^*) :: VectorSpace v a => v -> a -> v
- lerp :: (VectorSpace v a, Num a) => v -> v -> a -> v
- quadrance :: VectorSpace v a => v -> a
Vectors
Single-precision / float32s
Instances
Instances
Instances
Signed / int32s
Instances
Instances
Instances
Unsigned / word32s
Instances
Instances
Instances
Generic maps
class Elementwise a where Source #
Methods
epoint :: Element a -> a Source #
default epoint :: MonoPointed a => Element a -> a Source #
emap :: (Element a -> Element a) -> a -> a Source #
emap2 :: (Element a -> Element a -> Element a) -> a -> a -> a Source #
emap3 :: (Element a -> Element a -> Element a -> Element a) -> a -> a -> a -> a Source #
emap4 :: (Element a -> Element a -> Element a -> Element a -> Element a) -> a -> a -> a -> a -> a Source #
emap5 :: (Element a -> Element a -> Element a -> Element a -> Element a -> Element a) -> a -> a -> a -> a -> a -> a Source #
Instances
Matrices
Instances
| Storable Mat4 Source # | |
Defined in Geomancy.Mat4 | |
| Monoid Mat4 Source # | |
| Semigroup Mat4 Source # | |
| Show Mat4 Source # | |
| NFData Mat4 Source # | |
Defined in Geomancy.Mat4 | |
| Block Mat4 Source # | |
Defined in Geomancy.Mat4 Methods alignment140 :: proxy Mat4 -> Int Source # sizeOf140 :: proxy Mat4 -> Int Source # isStruct :: proxy Mat4 -> Bool Source # read140 :: MonadIO m => Ptr a -> Diff a Mat4 -> m Mat4 Source # write140 :: MonadIO m => Ptr a -> Diff a Mat4 -> Mat4 -> m () Source # alignment430 :: proxy Mat4 -> Int Source # sizeOf430 :: proxy Mat4 -> Int Source # read430 :: MonadIO m => Ptr a -> Diff a Mat4 -> m Mat4 Source # write430 :: MonadIO m => Ptr a -> Diff a Mat4 -> Mat4 -> m () Source # sizeOfPacked :: proxy Mat4 -> Int Source # readPacked :: MonadIO m => Ptr a -> Diff a Mat4 -> m Mat4 Source # writePacked :: MonadIO m => Ptr a -> Diff a Mat4 -> Mat4 -> m () Source # | |
Constructors
| Transform | |
Fields
| |
Instances
| Storable Transform Source # | |
Defined in Geomancy.Transform | |
| Monoid Transform Source # | |
| Semigroup Transform Source # | |
| Show Transform Source # | |
| Block Transform Source # | |
Defined in Geomancy.Transform Methods alignment140 :: proxy Transform -> Int Source # sizeOf140 :: proxy Transform -> Int Source # isStruct :: proxy Transform -> Bool Source # read140 :: MonadIO m => Ptr a -> Diff a Transform -> m Transform Source # write140 :: MonadIO m => Ptr a -> Diff a Transform -> Transform -> m () Source # alignment430 :: proxy Transform -> Int Source # sizeOf430 :: proxy Transform -> Int Source # read430 :: MonadIO m => Ptr a -> Diff a Transform -> m Transform Source # write430 :: MonadIO m => Ptr a -> Diff a Transform -> Transform -> m () Source # sizeOfPacked :: proxy Transform -> Int Source # readPacked :: MonadIO m => Ptr a -> Diff a Transform -> m Transform Source # writePacked :: MonadIO m => Ptr a -> Diff a Transform -> Transform -> m () Source # | |
Other beasts
data Quaternion Source #
Instances
quaternion :: Float -> Float -> Float -> Float -> Quaternion Source #
withQuaternion :: Quaternion -> (Float -> Float -> Float -> Float -> r) -> r Source #
Spaces
Constructors
| Point v |
Instances
class (Floating a, VectorSpace v a) => AffineSpace p v a | p -> v, v -> a where #
Affine Space type relation.
An affine space is a set (type) p, and an associated vector space v over
a field a.
class VectorSpace v a | v -> a where #
Vector space type relation.
A vector space is a set (type) closed under addition and multiplication by
a scalar. The type of the scalar is the field of the vector space, and
it is said that v is a vector space over a.
The encoding uses a type class |VectorSpace| v a, where v represents
the type of the vectors and a represents the types of the scalars.
Minimal complete definition
zeroVector, (*^), (^+^), dot
Methods
zeroVector :: v #
Vector with no magnitude (unit for addition).
(*^) :: a -> v -> v infixr 9 #
Multiplication by a scalar.
(^/) :: v -> a -> v infixl 9 #
Division by a scalar.
(^+^) :: v -> v -> v infixl 6 #
Vector addition
(^-^) :: v -> v -> v infixl 6 #
Vector subtraction
negateVector :: v -> v #
Vector negation. Addition with a negated vector should be same as subtraction.
Dot product (also known as scalar or inner product).
For two vectors, mathematically represented as a = a1,a2,...,an and b
= b1,b2,...,bn, the dot product is a . b = a1*b1 + a2*b2 + ... +
an*bn.
Some properties are derived from this. The dot product of a vector with
itself is the square of its magnitude (norm), and the dot product of
two orthogonal vectors is zero.
Vector's norm (also known as magnitude).
For a vector represented mathematically as a = a1,a2,...,an, the norm
is the square root of a1^2 + a2^2 + ... + an^2.
Return a vector with the same origin and orientation (angle), but such that the norm is one (the unit for multiplication by a scalar).
Instances
| VectorSpace Vec2 Float Source # | |
| VectorSpace Packed Float Source # | |
Defined in Geomancy.Vec3 | |
| VectorSpace Vec3 Float Source # | |
| VectorSpace Vec4 Float Source # | |
| VectorSpace Double Double | |
| VectorSpace Float Float | |
Defined in Data.VectorSpace | |
| (Eq a, Floating a) => VectorSpace (a, a) a | Vector space instance for pairs of |
Defined in Data.VectorSpace | |
| (Eq a, Floating a) => VectorSpace (a, a, a) a | Vector space instance for triplets of |
Defined in Data.VectorSpace | |
| (Eq a, Floating a) => VectorSpace (a, a, a, a) a | Vector space instance for tuples with four |
Defined in Data.VectorSpace Methods zeroVector :: (a, a, a, a) # (*^) :: a -> (a, a, a, a) -> (a, a, a, a) # (^/) :: (a, a, a, a) -> a -> (a, a, a, a) # (^+^) :: (a, a, a, a) -> (a, a, a, a) -> (a, a, a, a) # (^-^) :: (a, a, a, a) -> (a, a, a, a) -> (a, a, a, a) # negateVector :: (a, a, a, a) -> (a, a, a, a) # | |
| (Eq a, Floating a) => VectorSpace (a, a, a, a, a) a | Vector space instance for tuples with five |
Defined in Data.VectorSpace Methods zeroVector :: (a, a, a, a, a) # (*^) :: a -> (a, a, a, a, a) -> (a, a, a, a, a) # (^/) :: (a, a, a, a, a) -> a -> (a, a, a, a, a) # (^+^) :: (a, a, a, a, a) -> (a, a, a, a, a) -> (a, a, a, a, a) # (^-^) :: (a, a, a, a, a) -> (a, a, a, a, a) -> (a, a, a, a, a) # negateVector :: (a, a, a, a, a) -> (a, a, a, a, a) # dot :: (a, a, a, a, a) -> (a, a, a, a, a) -> a # | |
(^*) :: VectorSpace v a => v -> a -> v Source #
lerp :: (VectorSpace v a, Num a) => v -> v -> a -> v Source #
quadrance :: VectorSpace v a => v -> a Source #