nonlinear-0.1.0: Low-dimensional vectors
Safe HaskellNone
LanguageHaskell2010

Nonlinear.V4

Description

Adapted from Linear.V4

Documentation

data V4 a Source #

Constructors

V4 

Fields

Instances

Instances details
Monad V4 Source # 
Instance details

Defined in Nonlinear.V4

Methods

(>>=) :: V4 a -> (a -> V4 b) -> V4 b #

(>>) :: V4 a -> V4 b -> V4 b #

return :: a -> V4 a #

Functor V4 Source # 
Instance details

Defined in Nonlinear.V4

Methods

fmap :: (a -> b) -> V4 a -> V4 b #

(<$) :: a -> V4 b -> V4 a #

Applicative V4 Source # 
Instance details

Defined in Nonlinear.V4

Methods

pure :: a -> V4 a #

(<*>) :: V4 (a -> b) -> V4 a -> V4 b #

liftA2 :: (a -> b -> c) -> V4 a -> V4 b -> V4 c #

(*>) :: V4 a -> V4 b -> V4 b #

(<*) :: V4 a -> V4 b -> V4 a #

Foldable V4 Source # 
Instance details

Defined in Nonlinear.V4

Methods

fold :: Monoid m => V4 m -> m #

foldMap :: Monoid m => (a -> m) -> V4 a -> m #

foldMap' :: Monoid m => (a -> m) -> V4 a -> m #

foldr :: (a -> b -> b) -> b -> V4 a -> b #

foldr' :: (a -> b -> b) -> b -> V4 a -> b #

foldl :: (b -> a -> b) -> b -> V4 a -> b #

foldl' :: (b -> a -> b) -> b -> V4 a -> b #

foldr1 :: (a -> a -> a) -> V4 a -> a #

foldl1 :: (a -> a -> a) -> V4 a -> a #

toList :: V4 a -> [a] #

null :: V4 a -> Bool #

length :: V4 a -> Int #

elem :: Eq a => a -> V4 a -> Bool #

maximum :: Ord a => V4 a -> a #

minimum :: Ord a => V4 a -> a #

sum :: Num a => V4 a -> a #

product :: Num a => V4 a -> a #

Traversable V4 Source # 
Instance details

Defined in Nonlinear.V4

Methods

traverse :: Applicative f => (a -> f b) -> V4 a -> f (V4 b) #

sequenceA :: Applicative f => V4 (f a) -> f (V4 a) #

mapM :: Monad m => (a -> m b) -> V4 a -> m (V4 b) #

sequence :: Monad m => V4 (m a) -> m (V4 a) #

Eq1 V4 Source # 
Instance details

Defined in Nonlinear.V4

Methods

liftEq :: (a -> b -> Bool) -> V4 a -> V4 b -> Bool #

Ord1 V4 Source # 
Instance details

Defined in Nonlinear.V4

Methods

liftCompare :: (a -> b -> Ordering) -> V4 a -> V4 b -> Ordering #

Read1 V4 Source # 
Instance details

Defined in Nonlinear.V4

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (V4 a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [V4 a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (V4 a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [V4 a] #

Show1 V4 Source # 
Instance details

Defined in Nonlinear.V4

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> V4 a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [V4 a] -> ShowS #

Vec V4 Source # 
Instance details

Defined in Nonlinear.V4

Methods

construct :: ((forall b. Lens' (V4 b) b) -> a) -> V4 a Source #

R1 V4 Source # 
Instance details

Defined in Nonlinear.V4

Methods

_x :: Lens' (V4 a) a Source #

R2 V4 Source # 
Instance details

Defined in Nonlinear.V4

Methods

_y :: Lens' (V4 a) a Source #

_xy :: Lens' (V4 a) (V2 a) Source #

R3 V4 Source # 
Instance details

Defined in Nonlinear.V4

Methods

_z :: Lens' (V4 a) a Source #

_xyz :: Lens' (V4 a) (V3 a) Source #

R4 V4 Source # 
Instance details

Defined in Nonlinear.V4

Methods

_w :: Lens' (V4 a) a Source #

_xyzw :: Lens' (V4 a) (V4 a) Source #

Bounded a => Bounded (V4 a) Source # 
Instance details

Defined in Nonlinear.V4

Methods

minBound :: V4 a #

maxBound :: V4 a #

Eq a => Eq (V4 a) Source # 
Instance details

Defined in Nonlinear.V4

Methods

(==) :: V4 a -> V4 a -> Bool #

(/=) :: V4 a -> V4 a -> Bool #

Floating a => Floating (V4 a) Source # 
Instance details

Defined in Nonlinear.V4

Methods

pi :: V4 a #

exp :: V4 a -> V4 a #

log :: V4 a -> V4 a #

sqrt :: V4 a -> V4 a #

(**) :: V4 a -> V4 a -> V4 a #

logBase :: V4 a -> V4 a -> V4 a #

sin :: V4 a -> V4 a #

cos :: V4 a -> V4 a #

tan :: V4 a -> V4 a #

asin :: V4 a -> V4 a #

acos :: V4 a -> V4 a #

atan :: V4 a -> V4 a #

sinh :: V4 a -> V4 a #

cosh :: V4 a -> V4 a #

tanh :: V4 a -> V4 a #

asinh :: V4 a -> V4 a #

acosh :: V4 a -> V4 a #

atanh :: V4 a -> V4 a #

log1p :: V4 a -> V4 a #

expm1 :: V4 a -> V4 a #

log1pexp :: V4 a -> V4 a #

log1mexp :: V4 a -> V4 a #

Fractional a => Fractional (V4 a) Source # 
Instance details

Defined in Nonlinear.V4

Methods

(/) :: V4 a -> V4 a -> V4 a #

recip :: V4 a -> V4 a #

fromRational :: Rational -> V4 a #

Data a => Data (V4 a) Source # 
Instance details

Defined in Nonlinear.V4

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> V4 a -> c (V4 a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (V4 a) #

toConstr :: V4 a -> Constr #

dataTypeOf :: V4 a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (V4 a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (V4 a)) #

gmapT :: (forall b. Data b => b -> b) -> V4 a -> V4 a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> V4 a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> V4 a -> r #

gmapQ :: (forall d. Data d => d -> u) -> V4 a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> V4 a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> V4 a -> m (V4 a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> V4 a -> m (V4 a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> V4 a -> m (V4 a) #

Num a => Num (V4 a) Source # 
Instance details

Defined in Nonlinear.V4

Methods

(+) :: V4 a -> V4 a -> V4 a #

(-) :: V4 a -> V4 a -> V4 a #

(*) :: V4 a -> V4 a -> V4 a #

negate :: V4 a -> V4 a #

abs :: V4 a -> V4 a #

signum :: V4 a -> V4 a #

fromInteger :: Integer -> V4 a #

Ord a => Ord (V4 a) Source # 
Instance details

Defined in Nonlinear.V4

Methods

compare :: V4 a -> V4 a -> Ordering #

(<) :: V4 a -> V4 a -> Bool #

(<=) :: V4 a -> V4 a -> Bool #

(>) :: V4 a -> V4 a -> Bool #

(>=) :: V4 a -> V4 a -> Bool #

max :: V4 a -> V4 a -> V4 a #

min :: V4 a -> V4 a -> V4 a #

Read a => Read (V4 a) Source # 
Instance details

Defined in Nonlinear.V4

Show a => Show (V4 a) Source # 
Instance details

Defined in Nonlinear.V4

Methods

showsPrec :: Int -> V4 a -> ShowS #

show :: V4 a -> String #

showList :: [V4 a] -> ShowS #

Ix a => Ix (V4 a) Source # 
Instance details

Defined in Nonlinear.V4

Methods

range :: (V4 a, V4 a) -> [V4 a] #

index :: (V4 a, V4 a) -> V4 a -> Int #

unsafeIndex :: (V4 a, V4 a) -> V4 a -> Int #

inRange :: (V4 a, V4 a) -> V4 a -> Bool #

rangeSize :: (V4 a, V4 a) -> Int #

unsafeRangeSize :: (V4 a, V4 a) -> Int #

Generic (V4 a) Source # 
Instance details

Defined in Nonlinear.V4

Associated Types

type Rep (V4 a) :: Type -> Type #

Methods

from :: V4 a -> Rep (V4 a) x #

to :: Rep (V4 a) x -> V4 a #

Semigroup x => Semigroup (V4 x) Source # 
Instance details

Defined in Nonlinear.V4

Methods

(<>) :: V4 x -> V4 x -> V4 x #

sconcat :: NonEmpty (V4 x) -> V4 x #

stimes :: Integral b => b -> V4 x -> V4 x #

Monoid a => Monoid (V4 a) Source # 
Instance details

Defined in Nonlinear.V4

Methods

mempty :: V4 a #

mappend :: V4 a -> V4 a -> V4 a #

mconcat :: [V4 a] -> V4 a #

Storable a => Storable (V4 a) Source # 
Instance details

Defined in Nonlinear.V4

Methods

sizeOf :: V4 a -> Int #

alignment :: V4 a -> Int #

peekElemOff :: Ptr (V4 a) -> Int -> IO (V4 a) #

pokeElemOff :: Ptr (V4 a) -> Int -> V4 a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (V4 a) #

pokeByteOff :: Ptr b -> Int -> V4 a -> IO () #

peek :: Ptr (V4 a) -> IO (V4 a) #

poke :: Ptr (V4 a) -> V4 a -> IO () #

Generic1 V4 Source # 
Instance details

Defined in Nonlinear.V4

Associated Types

type Rep1 V4 :: k -> Type #

Methods

from1 :: forall (a :: k). V4 a -> Rep1 V4 a #

to1 :: forall (a :: k). Rep1 V4 a -> V4 a #

type Rep (V4 a) Source # 
Instance details

Defined in Nonlinear.V4

type Rep (V4 a) = D1 ('MetaData "V4" "Nonlinear.V4" "nonlinear-0.1.0-dd7wbAvLl3JZC37BHOks3" 'False) (C1 ('MetaCons "V4" 'PrefixI 'True) ((S1 ('MetaSel ('Just "v4x") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Just "v4y") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a)) :*: (S1 ('MetaSel ('Just "v4z") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Just "v4w") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a))))
type Rep1 V4 Source # 
Instance details

Defined in Nonlinear.V4

class R3 t => R4 t where Source #

Methods

_w :: Lens' (t a) a Source #

_xyzw :: Lens' (t a) (V4 a) Source #

Instances

Instances details
R4 V4 Source # 
Instance details

Defined in Nonlinear.V4

Methods

_w :: Lens' (V4 a) a Source #

_xyzw :: Lens' (V4 a) (V4 a) Source #

R4 Quaternion Source # 
Instance details

Defined in Nonlinear.Quaternion

Methods

_w :: Lens' (Quaternion a) a Source #

_xyzw :: Lens' (Quaternion a) (V4 a) Source #

_xw :: R4 t => Lens' (t a) (V2 a) Source #

_yw :: R4 t => Lens' (t a) (V2 a) Source #

_zw :: R4 t => Lens' (t a) (V2 a) Source #

_wx :: R4 t => Lens' (t a) (V2 a) Source #

_wy :: R4 t => Lens' (t a) (V2 a) Source #

_wz :: R4 t => Lens' (t a) (V2 a) Source #

_xyw :: R4 t => Lens' (t a) (V3 a) Source #

_xzw :: R4 t => Lens' (t a) (V3 a) Source #

_xwy :: R4 t => Lens' (t a) (V3 a) Source #

_xwz :: R4 t => Lens' (t a) (V3 a) Source #

_yxw :: R4 t => Lens' (t a) (V3 a) Source #

_yzw :: R4 t => Lens' (t a) (V3 a) Source #

_ywx :: R4 t => Lens' (t a) (V3 a) Source #

_ywz :: R4 t => Lens' (t a) (V3 a) Source #

_zxw :: R4 t => Lens' (t a) (V3 a) Source #

_zyw :: R4 t => Lens' (t a) (V3 a) Source #

_zwx :: R4 t => Lens' (t a) (V3 a) Source #

_zwy :: R4 t => Lens' (t a) (V3 a) Source #

_wxy :: R4 t => Lens' (t a) (V3 a) Source #

_wxz :: R4 t => Lens' (t a) (V3 a) Source #

_wyx :: R4 t => Lens' (t a) (V3 a) Source #

_wyz :: R4 t => Lens' (t a) (V3 a) Source #

_wzx :: R4 t => Lens' (t a) (V3 a) Source #

_wzy :: R4 t => Lens' (t a) (V3 a) Source #

_xywz :: R4 t => Lens' (t a) (V4 a) Source #

_xzyw :: R4 t => Lens' (t a) (V4 a) Source #

_xzwy :: R4 t => Lens' (t a) (V4 a) Source #

_xwyz :: R4 t => Lens' (t a) (V4 a) Source #

_xwzy :: R4 t => Lens' (t a) (V4 a) Source #

_yxzw :: R4 t => Lens' (t a) (V4 a) Source #

_yxwz :: R4 t => Lens' (t a) (V4 a) Source #

_yzxw :: R4 t => Lens' (t a) (V4 a) Source #

_yzwx :: R4 t => Lens' (t a) (V4 a) Source #

_ywxz :: R4 t => Lens' (t a) (V4 a) Source #

_ywzx :: R4 t => Lens' (t a) (V4 a) Source #

_zxyw :: R4 t => Lens' (t a) (V4 a) Source #

_zxwy :: R4 t => Lens' (t a) (V4 a) Source #

_zyxw :: R4 t => Lens' (t a) (V4 a) Source #

_zywx :: R4 t => Lens' (t a) (V4 a) Source #

_zwxy :: R4 t => Lens' (t a) (V4 a) Source #

_zwyx :: R4 t => Lens' (t a) (V4 a) Source #

_wxyz :: R4 t => Lens' (t a) (V4 a) Source #

_wxzy :: R4 t => Lens' (t a) (V4 a) Source #

_wyxz :: R4 t => Lens' (t a) (V4 a) Source #

_wyzx :: R4 t => Lens' (t a) (V4 a) Source #

_wzxy :: R4 t => Lens' (t a) (V4 a) Source #

_wzyx :: R4 t => Lens' (t a) (V4 a) Source #