hylogen-0.1.5.1: GLSL embedded in Haskell

Safe HaskellNone
LanguageHaskell2010

Hylogen.Types.Vec

Synopsis

Documentation

data FloatVec n where Source #

Floating vector singleton type tag

Constructors

FloatVec :: Veccable n => FloatVec n 

Instances

Veccable n => Floating (Vec n) Source # 

Methods

pi :: Vec n #

exp :: Vec n -> Vec n #

log :: Vec n -> Vec n #

sqrt :: Vec n -> Vec n #

(**) :: Vec n -> Vec n -> Vec n #

logBase :: Vec n -> Vec n -> Vec n #

sin :: Vec n -> Vec n #

cos :: Vec n -> Vec n #

tan :: Vec n -> Vec n #

asin :: Vec n -> Vec n #

acos :: Vec n -> Vec n #

atan :: Vec n -> Vec n #

sinh :: Vec n -> Vec n #

cosh :: Vec n -> Vec n #

tanh :: Vec n -> Vec n #

asinh :: Vec n -> Vec n #

acosh :: Vec n -> Vec n #

atanh :: Vec n -> Vec n #

log1p :: Vec n -> Vec n #

expm1 :: Vec n -> Vec n #

log1pexp :: Vec n -> Vec n #

log1mexp :: Vec n -> Vec n #

Veccable n => Fractional (Vec n) Source # 

Methods

(/) :: Vec n -> Vec n -> Vec n #

recip :: Vec n -> Vec n #

fromRational :: Rational -> Vec n #

Veccable n => Num (Vec n) Source # 

Methods

(+) :: Vec n -> Vec n -> Vec n #

(-) :: Vec n -> Vec n -> Vec n #

(*) :: Vec n -> Vec n -> Vec n #

negate :: Vec n -> Vec n #

abs :: Vec n -> Vec n #

signum :: Vec n -> Vec n #

fromInteger :: Integer -> Vec n #

ToGLSLType (FloatVec 1) Source # 
ToGLSLType (FloatVec 2) Source # 
ToGLSLType (FloatVec 3) Source # 
ToGLSLType (FloatVec 4) Source # 
Veccable n => VectorSpace (Vec n) Source # 

Associated Types

type Scalar (Vec n) :: *

Methods

(*^) :: Scalar (Vec n) -> Vec n -> Vec n

Veccable n => InnerSpace (Vec n) Source # 

Methods

(<.>) :: Vec n -> Vec n -> Scalar (Vec n)

Veccable n => AdditiveGroup (Vec n) Source # 

Methods

zeroV :: Vec n

(^+^) :: Vec n -> Vec n -> Vec n

negateV :: Vec n -> Vec n

(^-^) :: Vec n -> Vec n -> Vec n

((~) * a Vec1, (~) * b Vec1) => ToVec4 (a, b, Vec2) Source # 

Methods

vec4 :: (a, b, Vec2) -> Vec4 Source #

((~) * a Vec1, (~) * c Vec1) => ToVec4 (a, Vec2, c) Source # 

Methods

vec4 :: (a, Vec2, c) -> Vec4 Source #

((~) * b Vec1, (~) * c Vec1) => ToVec4 (Vec2, b, c) Source # 

Methods

vec4 :: (Vec2, b, c) -> Vec4 Source #

type Scalar (Vec n) Source # 
type Scalar (Vec n) = Vec 1

type Vec n = Expr (FloatVec n) Source #

Hylogen floating-point Vector type

type Vec1 = Vec 1 Source #

type Vec2 = Vec 2 Source #

type Vec3 = Vec 3 Source #

type Vec4 = Vec 4 Source #

class (ToGLSLType (FloatVec n), KnownNat n) => Veccable n where Source #

A Nat is veccable if it can be the dimension of a GLSL vector

Minimal complete definition

copy, toList

Methods

copy :: Vec1 -> Vec n Source #

Creates a Vec n from a Vec1

toList :: Vec n -> [Vec1] Source #

Transforms a Vec n into a list of Vec1's

Instances

Veccable 1 Source # 

Methods

copy :: Vec1 -> Vec 1 Source #

toList :: Vec 1 -> [Vec1] Source #

Veccable 2 Source # 

Methods

copy :: Vec1 -> Vec 2 Source #

toList :: Vec 2 -> [Vec1] Source #

Veccable 3 Source # 

Methods

copy :: Vec1 -> Vec 3 Source #

toList :: Vec 3 -> [Vec1] Source #

Veccable 4 Source # 

Methods

copy :: Vec1 -> Vec 4 Source #

toList :: Vec 4 -> [Vec1] Source #

vec2 :: (Vec1, Vec1) -> Vec2 Source #

Exposed constructor for making vec2's

class ToVec3 tuple where Source #

Minimal complete definition

vec3

Methods

vec3 :: tuple -> Vec3 Source #

Exposed constructor for making vec3's

Instances

((~) * a (Vec m), (~) * b (Vec ((-) 3 m))) => ToVec3 (a, b) Source # 

Methods

vec3 :: (a, b) -> Vec3 Source #

((~) * a Vec1, (~) * b Vec1, (~) * c Vec1) => ToVec3 (a, b, c) Source # 

Methods

vec3 :: (a, b, c) -> Vec3 Source #

class ToVec4 tuple where Source #

Minimal complete definition

vec4

Methods

vec4 :: tuple -> Vec4 Source #

Exposed constructor for making vec4's

Instances

((~) * a (Vec m), (~) * b (Vec ((-) 4 m))) => ToVec4 (a, b) Source # 

Methods

vec4 :: (a, b) -> Vec4 Source #

((~) * a Vec1, (~) * b Vec1) => ToVec4 (a, b, Vec2) Source # 

Methods

vec4 :: (a, b, Vec2) -> Vec4 Source #

((~) * a Vec1, (~) * c Vec1) => ToVec4 (a, Vec2, c) Source # 

Methods

vec4 :: (a, Vec2, c) -> Vec4 Source #

((~) * b Vec1, (~) * c Vec1) => ToVec4 (Vec2, b, c) Source # 

Methods

vec4 :: (Vec2, b, c) -> Vec4 Source #

((~) * a Vec1, (~) * b Vec1, (~) * c Vec1, (~) * d Vec1) => ToVec4 (a, b, c, d) Source # 

Methods

vec4 :: (a, b, c, d) -> Vec4 Source #

type (>=) x y = ((x + 1) <=? y) ~ False Source #

mkSwizz :: forall n m. (Veccable n, Veccable m) => String -> Vec n -> Vec m Source #

Makes swizzle functions. Uses GenSwizz.hs to generate the following 340 swizzle expressions.

xxxx_ :: forall n. (Veccable n, n >= 2) => Vec n -> Vec 4 Source #

yxxx_ :: forall n. (Veccable n, n >= 2) => Vec n -> Vec 4 Source #

zxxx_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 4 Source #

wxxx_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

xxx_ :: forall n. (Veccable n, n >= 2) => Vec n -> Vec 3 Source #

xyxx_ :: forall n. (Veccable n, n >= 2) => Vec n -> Vec 4 Source #

yyxx_ :: forall n. (Veccable n, n >= 2) => Vec n -> Vec 4 Source #

zyxx_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 4 Source #

wyxx_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

yxx_ :: forall n. (Veccable n, n >= 2) => Vec n -> Vec 3 Source #

xzxx_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 4 Source #

yzxx_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 4 Source #

zzxx_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 4 Source #

wzxx_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

zxx_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 3 Source #

xwxx_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

ywxx_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

zwxx_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

wwxx_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

wxx_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 3 Source #

xx_ :: forall n. (Veccable n, n >= 2) => Vec n -> Vec 2 Source #

xxyx_ :: forall n. (Veccable n, n >= 2) => Vec n -> Vec 4 Source #

yxyx_ :: forall n. (Veccable n, n >= 2) => Vec n -> Vec 4 Source #

zxyx_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 4 Source #

wxyx_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

xyx_ :: forall n. (Veccable n, n >= 2) => Vec n -> Vec 3 Source #

xyyx_ :: forall n. (Veccable n, n >= 2) => Vec n -> Vec 4 Source #

yyyx_ :: forall n. (Veccable n, n >= 2) => Vec n -> Vec 4 Source #

zyyx_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 4 Source #

wyyx_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

yyx_ :: forall n. (Veccable n, n >= 2) => Vec n -> Vec 3 Source #

xzyx_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 4 Source #

yzyx_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 4 Source #

zzyx_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 4 Source #

wzyx_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

zyx_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 3 Source #

xwyx_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

ywyx_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

zwyx_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

wwyx_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

wyx_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 3 Source #

yx_ :: forall n. (Veccable n, n >= 2) => Vec n -> Vec 2 Source #

xxzx_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 4 Source #

yxzx_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 4 Source #

zxzx_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 4 Source #

wxzx_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

xzx_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 3 Source #

xyzx_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 4 Source #

yyzx_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 4 Source #

zyzx_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 4 Source #

wyzx_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

yzx_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 3 Source #

xzzx_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 4 Source #

yzzx_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 4 Source #

zzzx_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 4 Source #

wzzx_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

zzx_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 3 Source #

xwzx_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

ywzx_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

zwzx_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

wwzx_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

wzx_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 3 Source #

zx_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 2 Source #

xxwx_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

yxwx_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

zxwx_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

wxwx_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

xwx_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 3 Source #

xywx_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

yywx_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

zywx_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

wywx_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

ywx_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 3 Source #

xzwx_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

yzwx_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

zzwx_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

wzwx_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

zwx_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 3 Source #

xwwx_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

ywwx_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

zwwx_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

wwwx_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

wwx_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 3 Source #

wx_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 2 Source #

x_ :: forall n. (Veccable n, n >= 2) => Vec n -> Vec 1 Source #

xxxy_ :: forall n. (Veccable n, n >= 2) => Vec n -> Vec 4 Source #

yxxy_ :: forall n. (Veccable n, n >= 2) => Vec n -> Vec 4 Source #

zxxy_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 4 Source #

wxxy_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

xxy_ :: forall n. (Veccable n, n >= 2) => Vec n -> Vec 3 Source #

xyxy_ :: forall n. (Veccable n, n >= 2) => Vec n -> Vec 4 Source #

yyxy_ :: forall n. (Veccable n, n >= 2) => Vec n -> Vec 4 Source #

zyxy_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 4 Source #

wyxy_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

yxy_ :: forall n. (Veccable n, n >= 2) => Vec n -> Vec 3 Source #

xzxy_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 4 Source #

yzxy_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 4 Source #

zzxy_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 4 Source #

wzxy_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

zxy_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 3 Source #

xwxy_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

ywxy_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

zwxy_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

wwxy_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

wxy_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 3 Source #

xy_ :: forall n. (Veccable n, n >= 2) => Vec n -> Vec 2 Source #

xxyy_ :: forall n. (Veccable n, n >= 2) => Vec n -> Vec 4 Source #

yxyy_ :: forall n. (Veccable n, n >= 2) => Vec n -> Vec 4 Source #

zxyy_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 4 Source #

wxyy_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

xyy_ :: forall n. (Veccable n, n >= 2) => Vec n -> Vec 3 Source #

xyyy_ :: forall n. (Veccable n, n >= 2) => Vec n -> Vec 4 Source #

yyyy_ :: forall n. (Veccable n, n >= 2) => Vec n -> Vec 4 Source #

zyyy_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 4 Source #

wyyy_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

yyy_ :: forall n. (Veccable n, n >= 2) => Vec n -> Vec 3 Source #

xzyy_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 4 Source #

yzyy_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 4 Source #

zzyy_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 4 Source #

wzyy_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

zyy_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 3 Source #

xwyy_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

ywyy_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

zwyy_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

wwyy_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

wyy_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 3 Source #

yy_ :: forall n. (Veccable n, n >= 2) => Vec n -> Vec 2 Source #

xxzy_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 4 Source #

yxzy_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 4 Source #

zxzy_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 4 Source #

wxzy_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

xzy_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 3 Source #

xyzy_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 4 Source #

yyzy_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 4 Source #

zyzy_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 4 Source #

wyzy_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

yzy_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 3 Source #

xzzy_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 4 Source #

yzzy_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 4 Source #

zzzy_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 4 Source #

wzzy_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

zzy_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 3 Source #

xwzy_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

ywzy_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

zwzy_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

wwzy_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

wzy_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 3 Source #

zy_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 2 Source #

xxwy_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

yxwy_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

zxwy_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

wxwy_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

xwy_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 3 Source #

xywy_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

yywy_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

zywy_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

wywy_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

ywy_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 3 Source #

xzwy_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

yzwy_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

zzwy_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

wzwy_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

zwy_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 3 Source #

xwwy_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

ywwy_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

zwwy_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

wwwy_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

wwy_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 3 Source #

wy_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 2 Source #

y_ :: forall n. (Veccable n, n >= 2) => Vec n -> Vec 1 Source #

xxxz_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 4 Source #

yxxz_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 4 Source #

zxxz_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 4 Source #

wxxz_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

xxz_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 3 Source #

xyxz_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 4 Source #

yyxz_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 4 Source #

zyxz_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 4 Source #

wyxz_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

yxz_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 3 Source #

xzxz_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 4 Source #

yzxz_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 4 Source #

zzxz_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 4 Source #

wzxz_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

zxz_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 3 Source #

xwxz_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

ywxz_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

zwxz_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

wwxz_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

wxz_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 3 Source #

xz_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 2 Source #

xxyz_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 4 Source #

yxyz_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 4 Source #

zxyz_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 4 Source #

wxyz_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

xyz_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 3 Source #

xyyz_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 4 Source #

yyyz_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 4 Source #

zyyz_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 4 Source #

wyyz_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

yyz_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 3 Source #

xzyz_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 4 Source #

yzyz_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 4 Source #

zzyz_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 4 Source #

wzyz_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

zyz_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 3 Source #

xwyz_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

ywyz_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

zwyz_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

wwyz_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

wyz_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 3 Source #

yz_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 2 Source #

xxzz_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 4 Source #

yxzz_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 4 Source #

zxzz_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 4 Source #

wxzz_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

xzz_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 3 Source #

xyzz_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 4 Source #

yyzz_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 4 Source #

zyzz_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 4 Source #

wyzz_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

yzz_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 3 Source #

xzzz_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 4 Source #

yzzz_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 4 Source #

zzzz_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 4 Source #

wzzz_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

zzz_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 3 Source #

xwzz_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

ywzz_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

zwzz_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

wwzz_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

wzz_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 3 Source #

zz_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 2 Source #

xxwz_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

yxwz_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

zxwz_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

wxwz_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

xwz_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 3 Source #

xywz_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

yywz_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

zywz_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

wywz_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

ywz_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 3 Source #

xzwz_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

yzwz_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

zzwz_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

wzwz_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

zwz_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 3 Source #

xwwz_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

ywwz_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

zwwz_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

wwwz_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

wwz_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 3 Source #

wz_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 2 Source #

z_ :: forall n. (Veccable n, n >= 3) => Vec n -> Vec 1 Source #

xxxw_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

yxxw_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

zxxw_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

wxxw_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

xxw_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 3 Source #

xyxw_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

yyxw_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

zyxw_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

wyxw_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

yxw_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 3 Source #

xzxw_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

yzxw_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

zzxw_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

wzxw_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

zxw_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 3 Source #

xwxw_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

ywxw_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

zwxw_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

wwxw_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

wxw_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 3 Source #

xw_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 2 Source #

xxyw_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

yxyw_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

zxyw_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

wxyw_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

xyw_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 3 Source #

xyyw_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

yyyw_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

zyyw_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

wyyw_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

yyw_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 3 Source #

xzyw_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

yzyw_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

zzyw_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

wzyw_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

zyw_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 3 Source #

xwyw_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

ywyw_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

zwyw_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

wwyw_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

wyw_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 3 Source #

yw_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 2 Source #

xxzw_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

yxzw_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

zxzw_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

wxzw_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

xzw_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 3 Source #

xyzw_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

yyzw_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

zyzw_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

wyzw_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

yzw_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 3 Source #

xzzw_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

yzzw_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

zzzw_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

wzzw_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

zzw_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 3 Source #

xwzw_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

ywzw_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

zwzw_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

wwzw_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

wzw_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 3 Source #

zw_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 2 Source #

xxww_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

yxww_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

zxww_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

wxww_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

xww_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 3 Source #

xyww_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

yyww_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

zyww_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

wyww_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

yww_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 3 Source #

xzww_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

yzww_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

zzww_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

wzww_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

zww_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 3 Source #

xwww_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

ywww_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

zwww_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

wwww_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 4 Source #

www_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 3 Source #

ww_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 2 Source #

w_ :: forall n. (Veccable n, n >= 4) => Vec n -> Vec 1 Source #