easytensor-2.1.1.1: Pure, type-indexed haskell vector, matrix, and tensor library.
Safe HaskellNone
LanguageHaskell2010

Numeric.Quaternion

Description

Quaternion operations implemented for Floats and Doubles.

The types QDouble and QFloat have the same representation as corresponding Vector t 4. This means, you can do a cheap conversion between the types.

However, arithmetic instances, such as Num and Floating are implemented in substentially different ways. For example, fromInteger fills a vector fully but sets only real part to a quaternion:

>>> 1 = vec4 1 1 1 1
>>> 1 = packQ 0 0 0 1

All other numeric operations for vectors are element-wise, but for quaternions I have implemented the actual quaternion math. In most of the cases, you can think of these as being operations on complex numbers, where the role of imaginary i is played by a 3D vector. Some of the operations are ambiguous for quaternions; for example \( \sqrt{-1} = \pm i \), but also \( \sqrt{-1} = \pm j \), and \( \sqrt{-1} = \pm k \), and any other unit quaterion with zero real part. In cases like this, I stick to the i-th axis: \( \sqrt{-1} := i \)

Synopsis

Documentation

class (Floating (Quater t), Floating t, Ord t, PrimBytes t, KnownBackend t '[3], KnownBackend t '[4], KnownBackend t '[3, 3], KnownBackend t '[4, 4]) => Quaternion t where Source #

Quaternion operations

Associated Types

data Quater t Source #

Quaternion data type. The ordering of coordinates is (x,y,z,w), where w is the argument, and x y z are the components of a 3D vector

Methods

packQ :: t -> t -> t -> t -> Quater t Source #

Set the quaternion in format (x,y,z,w)

unpackQ# :: Quater t -> (# t, t, t, t #) Source #

Get the values of the quaternion in format (x,y,z,w)

fromVecNum :: Vector t 3 -> t -> Quater t Source #

Set the quaternion from 3D axis vector and argument

fromVec4 :: Vector t 4 -> Quater t Source #

Set the quaternion from 4D vector in format (x,y,z,w)

toVec4 :: Quater t -> Vector t 4 Source #

Transform the quaternion to 4D vector in format (x,y,z,w)

square :: Quater t -> t Source #

Get scalar square of the quaternion.

>>> realToFrac (square q) == q * conjugate q

im :: Quater t -> Quater t Source #

Imaginary part of the quaternion (orientation vector)

re :: Quater t -> Quater t Source #

Real part of the quaternion

imVec :: Quater t -> Vector t 3 Source #

Imaginary part of the quaternion as a 3D vector

taker :: Quater t -> t Source #

Real part of the quaternion as a scalar

takei :: Quater t -> t Source #

i-th component

takej :: Quater t -> t Source #

j-th component

takek :: Quater t -> t Source #

k-th component

conjugate :: Quater t -> Quater t Source #

Conjugate quaternion (negate imaginary part)

rotScale :: Quater t -> Vector t 3 -> Vector t 3 Source #

Rotates and scales vector in 3D using quaternion. Let \( q = c (\cos \frac{\alpha}{2}, v \sin \frac{\alpha}{2}) \) , \( c > 0 \), \( {|v|}^2 = 1 \); then the rotation angle is \( \alpha \), and the axis of rotation is \(v\). Scaling is proportional to \( c^2 \).

>>> rotScale q x == q * x * (conjugate q)

getRotScale :: Vector t 3 -> Vector t 3 -> Quater t Source #

Creates a quaternion q from two vectors a and b, such that rotScale q a == b.

axisRotation :: Vector t 3 -> t -> Quater t Source #

Creates a rotation versor from an axis vector and an angle in radians. Result is always a unit quaternion (versor). If the argument vector is zero, then result is a real unit quaternion.

qArg :: Quater t -> t Source #

Quaternion rotation angle \( \alpha \) (where \( q = c (\cos \frac{\alpha}{2}, v \sin \frac{\alpha}{2}) \) , \( c > 0 \), \( {|v|}^2 = 1 \)).

>>> q /= 0 ==> axisRotation (imVec q) (qArg q) == signum q

fromMatrix33 :: Matrix t 3 3 -> Quater t Source #

Create a quaternion from a rotation matrix. Note, that rotations of \(q\) and \(-q\) are equivalent, there result of this function may be ambiguious. Assume the sign of the result to be chosen arbitrarily.

fromMatrix44 :: Matrix t 4 4 -> Quater t Source #

Create a quaternion from a homogenious coordinates trasform matrix. Ignores matrix translation transform. Note, that rotations of \(q\) and \(-q\) are equivalent, there result of this function may be ambiguious. Assume the sign of the result to be chosen arbitrarily.

toMatrix33 :: Quater t -> Matrix t 3 3 Source #

Create a rotation matrix from a quaternion. Note, that rotations of \(q\) and \(-q\) are equivalent, so the following property holds:

>>> toMatrix33 q == toMatrix33 (-q)

toMatrix44 :: Quater t -> Matrix t 4 4 Source #

Create a homogenious coordinates trasform matrix from a quaternion. Translation of the output matrix is zero. Note, that rotations of \(q\) and \(-q\) are equivalent, so the following property holds:

>>> toMatrix44 q == toMatrix44 (-q)

Instances

Instances details
Quaternion Double Source # 
Instance details

Defined in Numeric.Quaternion.Internal.QDouble

Associated Types

data Quater Double Source #

Quaternion Float Source # 
Instance details

Defined in Numeric.Quaternion.Internal.QFloat

Associated Types

data Quater Float Source #