linear-1.22: Linear Algebra
Copyright(C) 2012-2015 Edward Kmett
LicenseBSD-style (see the file LICENSE)
MaintainerEdward Kmett <ekmett@gmail.com>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellTrustworthy
LanguageHaskell2010

Linear.V2

Description

2-D Vectors

Synopsis

Documentation

data V2 a Source #

A 2-dimensional vector

>>> pure 1 :: V2 Int
V2 1 1
>>> V2 1 2 + V2 3 4
V2 4 6
>>> V2 1 2 * V2 3 4
V2 3 8
>>> sum (V2 1 2)
3

Constructors

V2 !a !a 

Instances

Instances details
Representable V2 Source # 
Instance details

Defined in Linear.V2

Associated Types

type Rep V2 Source #

Methods

tabulate :: (Rep V2 -> a) -> V2 a Source #

index :: V2 a -> Rep V2 -> a Source #

MonadFix V2 Source # 
Instance details

Defined in Linear.V2

Methods

mfix :: (a -> V2 a) -> V2 a Source #

MonadZip V2 Source # 
Instance details

Defined in Linear.V2

Methods

mzip :: V2 a -> V2 b -> V2 (a, b) Source #

mzipWith :: (a -> b -> c) -> V2 a -> V2 b -> V2 c Source #

munzip :: V2 (a, b) -> (V2 a, V2 b) Source #

Foldable V2 Source # 
Instance details

Defined in Linear.V2

Methods

fold :: Monoid m => V2 m -> m Source #

foldMap :: Monoid m => (a -> m) -> V2 a -> m Source #

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

foldr :: (a -> b -> b) -> b -> V2 a -> b Source #

foldr' :: (a -> b -> b) -> b -> V2 a -> b Source #

foldl :: (b -> a -> b) -> b -> V2 a -> b Source #

foldl' :: (b -> a -> b) -> b -> V2 a -> b Source #

foldr1 :: (a -> a -> a) -> V2 a -> a Source #

foldl1 :: (a -> a -> a) -> V2 a -> a Source #

toList :: V2 a -> [a] Source #

null :: V2 a -> Bool Source #

length :: V2 a -> Int Source #

elem :: Eq a => a -> V2 a -> Bool Source #

maximum :: Ord a => V2 a -> a Source #

minimum :: Ord a => V2 a -> a Source #

sum :: Num a => V2 a -> a Source #

product :: Num a => V2 a -> a Source #

Eq1 V2 Source # 
Instance details

Defined in Linear.V2

Methods

liftEq :: (a -> b -> Bool) -> V2 a -> V2 b -> Bool Source #

Ord1 V2 Source # 
Instance details

Defined in Linear.V2

Methods

liftCompare :: (a -> b -> Ordering) -> V2 a -> V2 b -> Ordering Source #

Read1 V2 Source # 
Instance details

Defined in Linear.V2

Methods

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

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

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (V2 a) Source #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [V2 a] Source #

Show1 V2 Source # 
Instance details

Defined in Linear.V2

Methods

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

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

Traversable V2 Source # 
Instance details

Defined in Linear.V2

Methods

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

sequenceA :: Applicative f => V2 (f a) -> f (V2 a) Source #

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

sequence :: Monad m => V2 (m a) -> m (V2 a) Source #

Applicative V2 Source # 
Instance details

Defined in Linear.V2

Methods

pure :: a -> V2 a Source #

(<*>) :: V2 (a -> b) -> V2 a -> V2 b Source #

liftA2 :: (a -> b -> c) -> V2 a -> V2 b -> V2 c Source #

(*>) :: V2 a -> V2 b -> V2 b Source #

(<*) :: V2 a -> V2 b -> V2 a Source #

Functor V2 Source # 
Instance details

Defined in Linear.V2

Methods

fmap :: (a -> b) -> V2 a -> V2 b Source #

(<$) :: a -> V2 b -> V2 a Source #

Monad V2 Source # 
Instance details

Defined in Linear.V2

Methods

(>>=) :: V2 a -> (a -> V2 b) -> V2 b Source #

(>>) :: V2 a -> V2 b -> V2 b Source #

return :: a -> V2 a Source #

Serial1 V2 Source # 
Instance details

Defined in Linear.V2

Methods

serializeWith :: MonadPut m => (a -> m ()) -> V2 a -> m () Source #

deserializeWith :: MonadGet m => m a -> m (V2 a) Source #

Distributive V2 Source # 
Instance details

Defined in Linear.V2

Methods

distribute :: Functor f => f (V2 a) -> V2 (f a) Source #

collect :: Functor f => (a -> V2 b) -> f a -> V2 (f b) Source #

distributeM :: Monad m => m (V2 a) -> V2 (m a) Source #

collectM :: Monad m => (a -> V2 b) -> m a -> V2 (m b) Source #

Hashable1 V2 Source # 
Instance details

Defined in Linear.V2

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> V2 a -> Int Source #

Affine V2 Source # 
Instance details

Defined in Linear.Affine

Associated Types

type Diff V2 :: Type -> Type Source #

Methods

(.-.) :: Num a => V2 a -> V2 a -> Diff V2 a Source #

(.+^) :: Num a => V2 a -> Diff V2 a -> V2 a Source #

(.-^) :: Num a => V2 a -> Diff V2 a -> V2 a Source #

Metric V2 Source # 
Instance details

Defined in Linear.V2

Methods

dot :: Num a => V2 a -> V2 a -> a Source #

quadrance :: Num a => V2 a -> a Source #

qd :: Num a => V2 a -> V2 a -> a Source #

distance :: Floating a => V2 a -> V2 a -> a Source #

norm :: Floating a => V2 a -> a Source #

signorm :: Floating a => V2 a -> V2 a Source #

Trace V2 Source # 
Instance details

Defined in Linear.Trace

Methods

trace :: Num a => V2 (V2 a) -> a Source #

diagonal :: V2 (V2 a) -> V2 a Source #

Finite V2 Source # 
Instance details

Defined in Linear.V2

Associated Types

type Size V2 :: Nat Source #

Methods

toV :: V2 a -> V (Size V2) a Source #

fromV :: V (Size V2) a -> V2 a Source #

R1 V2 Source # 
Instance details

Defined in Linear.V2

Methods

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

R2 V2 Source # 
Instance details

Defined in Linear.V2

Methods

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

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

Additive V2 Source # 
Instance details

Defined in Linear.V2

Methods

zero :: Num a => V2 a Source #

(^+^) :: Num a => V2 a -> V2 a -> V2 a Source #

(^-^) :: Num a => V2 a -> V2 a -> V2 a Source #

lerp :: Num a => a -> V2 a -> V2 a -> V2 a Source #

liftU2 :: (a -> a -> a) -> V2 a -> V2 a -> V2 a Source #

liftI2 :: (a -> b -> c) -> V2 a -> V2 b -> V2 c Source #

Apply V2 Source # 
Instance details

Defined in Linear.V2

Methods

(<.>) :: V2 (a -> b) -> V2 a -> V2 b Source #

(.>) :: V2 a -> V2 b -> V2 b Source #

(<.) :: V2 a -> V2 b -> V2 a Source #

liftF2 :: (a -> b -> c) -> V2 a -> V2 b -> V2 c Source #

Bind V2 Source # 
Instance details

Defined in Linear.V2

Methods

(>>-) :: V2 a -> (a -> V2 b) -> V2 b Source #

join :: V2 (V2 a) -> V2 a Source #

Foldable1 V2 Source # 
Instance details

Defined in Linear.V2

Methods

fold1 :: Semigroup m => V2 m -> m Source #

foldMap1 :: Semigroup m => (a -> m) -> V2 a -> m Source #

toNonEmpty :: V2 a -> NonEmpty a Source #

Traversable1 V2 Source # 
Instance details

Defined in Linear.V2

Methods

traverse1 :: Apply f => (a -> f b) -> V2 a -> f (V2 b) Source #

sequence1 :: Apply f => V2 (f b) -> f (V2 b) Source #

Generic1 V2 Source # 
Instance details

Defined in Linear.V2

Associated Types

type Rep1 V2 :: k -> Type Source #

Methods

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

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

Num r => Coalgebra r (E V2) Source # 
Instance details

Defined in Linear.Algebra

Methods

comult :: (E V2 -> r) -> E V2 -> E V2 -> r Source #

counital :: (E V2 -> r) -> r Source #

Lift a => Lift (V2 a :: Type) Source # 
Instance details

Defined in Linear.V2

Methods

lift :: Quote m => V2 a -> m Exp Source #

liftTyped :: forall (m :: Type -> Type). Quote m => V2 a -> Code m (V2 a) Source #

Unbox a => Vector Vector (V2 a) Source # 
Instance details

Defined in Linear.V2

Methods

basicUnsafeFreeze :: Mutable Vector s (V2 a) -> ST s (Vector (V2 a)) Source #

basicUnsafeThaw :: Vector (V2 a) -> ST s (Mutable Vector s (V2 a)) Source #

basicLength :: Vector (V2 a) -> Int Source #

basicUnsafeSlice :: Int -> Int -> Vector (V2 a) -> Vector (V2 a) Source #

basicUnsafeIndexM :: Vector (V2 a) -> Int -> Box (V2 a) Source #

basicUnsafeCopy :: Mutable Vector s (V2 a) -> Vector (V2 a) -> ST s () Source #

elemseq :: Vector (V2 a) -> V2 a -> b -> b Source #

Unbox a => MVector MVector (V2 a) Source # 
Instance details

Defined in Linear.V2

Methods

basicLength :: MVector s (V2 a) -> Int Source #

basicUnsafeSlice :: Int -> Int -> MVector s (V2 a) -> MVector s (V2 a) Source #

basicOverlaps :: MVector s (V2 a) -> MVector s (V2 a) -> Bool Source #

basicUnsafeNew :: Int -> ST s (MVector s (V2 a)) Source #

basicInitialize :: MVector s (V2 a) -> ST s () Source #

basicUnsafeReplicate :: Int -> V2 a -> ST s (MVector s (V2 a)) Source #

basicUnsafeRead :: MVector s (V2 a) -> Int -> ST s (V2 a) Source #

basicUnsafeWrite :: MVector s (V2 a) -> Int -> V2 a -> ST s () Source #

basicClear :: MVector s (V2 a) -> ST s () Source #

basicSet :: MVector s (V2 a) -> V2 a -> ST s () Source #

basicUnsafeCopy :: MVector s (V2 a) -> MVector s (V2 a) -> ST s () Source #

basicUnsafeMove :: MVector s (V2 a) -> MVector s (V2 a) -> ST s () Source #

basicUnsafeGrow :: MVector s (V2 a) -> Int -> ST s (MVector s (V2 a)) Source #

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

Defined in Linear.V2

Methods

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

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

toConstr :: V2 a -> Constr Source #

dataTypeOf :: V2 a -> DataType Source #

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

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

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

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

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

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

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

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

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

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

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

Defined in Linear.V2

Methods

sizeOf :: V2 a -> Int Source #

alignment :: V2 a -> Int Source #

peekElemOff :: Ptr (V2 a) -> Int -> IO (V2 a) Source #

pokeElemOff :: Ptr (V2 a) -> Int -> V2 a -> IO () Source #

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

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

peek :: Ptr (V2 a) -> IO (V2 a) Source #

poke :: Ptr (V2 a) -> V2 a -> IO () Source #

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

Defined in Linear.V2

Methods

mempty :: V2 a Source #

mappend :: V2 a -> V2 a -> V2 a Source #

mconcat :: [V2 a] -> V2 a Source #

Semigroup a => Semigroup (V2 a) Source # 
Instance details

Defined in Linear.V2

Methods

(<>) :: V2 a -> V2 a -> V2 a Source #

sconcat :: NonEmpty (V2 a) -> V2 a Source #

stimes :: Integral b => b -> V2 a -> V2 a Source #

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

Defined in Linear.V2

Methods

minBound :: V2 a Source #

maxBound :: V2 a Source #

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

Defined in Linear.V2

Methods

pi :: V2 a Source #

exp :: V2 a -> V2 a Source #

log :: V2 a -> V2 a Source #

sqrt :: V2 a -> V2 a Source #

(**) :: V2 a -> V2 a -> V2 a Source #

logBase :: V2 a -> V2 a -> V2 a Source #

sin :: V2 a -> V2 a Source #

cos :: V2 a -> V2 a Source #

tan :: V2 a -> V2 a Source #

asin :: V2 a -> V2 a Source #

acos :: V2 a -> V2 a Source #

atan :: V2 a -> V2 a Source #

sinh :: V2 a -> V2 a Source #

cosh :: V2 a -> V2 a Source #

tanh :: V2 a -> V2 a Source #

asinh :: V2 a -> V2 a Source #

acosh :: V2 a -> V2 a Source #

atanh :: V2 a -> V2 a Source #

log1p :: V2 a -> V2 a Source #

expm1 :: V2 a -> V2 a Source #

log1pexp :: V2 a -> V2 a Source #

log1mexp :: V2 a -> V2 a Source #

Generic (V2 a) Source # 
Instance details

Defined in Linear.V2

Associated Types

type Rep (V2 a) :: Type -> Type Source #

Methods

from :: V2 a -> Rep (V2 a) x Source #

to :: Rep (V2 a) x -> V2 a Source #

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

Defined in Linear.V2

Methods

range :: (V2 a, V2 a) -> [V2 a] Source #

index :: (V2 a, V2 a) -> V2 a -> Int Source #

unsafeIndex :: (V2 a, V2 a) -> V2 a -> Int Source #

inRange :: (V2 a, V2 a) -> V2 a -> Bool Source #

rangeSize :: (V2 a, V2 a) -> Int Source #

unsafeRangeSize :: (V2 a, V2 a) -> Int Source #

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

Defined in Linear.V2

Methods

(+) :: V2 a -> V2 a -> V2 a Source #

(-) :: V2 a -> V2 a -> V2 a Source #

(*) :: V2 a -> V2 a -> V2 a Source #

negate :: V2 a -> V2 a Source #

abs :: V2 a -> V2 a Source #

signum :: V2 a -> V2 a Source #

fromInteger :: Integer -> V2 a Source #

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

Defined in Linear.V2

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

Defined in Linear.V2

Methods

(/) :: V2 a -> V2 a -> V2 a Source #

recip :: V2 a -> V2 a Source #

fromRational :: Rational -> V2 a Source #

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

Defined in Linear.V2

Methods

showsPrec :: Int -> V2 a -> ShowS Source #

show :: V2 a -> String Source #

showList :: [V2 a] -> ShowS Source #

Binary a => Binary (V2 a) Source # 
Instance details

Defined in Linear.V2

Methods

put :: V2 a -> Put Source #

get :: Get (V2 a) Source #

putList :: [V2 a] -> Put Source #

Serial a => Serial (V2 a) Source # 
Instance details

Defined in Linear.V2

Methods

serialize :: MonadPut m => V2 a -> m () Source #

deserialize :: MonadGet m => m (V2 a) Source #

Serialize a => Serialize (V2 a) Source # 
Instance details

Defined in Linear.V2

Methods

put :: Putter (V2 a) Source #

get :: Get (V2 a) Source #

NFData a => NFData (V2 a) Source # 
Instance details

Defined in Linear.V2

Methods

rnf :: V2 a -> () Source #

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

Defined in Linear.V2

Methods

(==) :: V2 a -> V2 a -> Bool Source #

(/=) :: V2 a -> V2 a -> Bool Source #

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

Defined in Linear.V2

Methods

compare :: V2 a -> V2 a -> Ordering Source #

(<) :: V2 a -> V2 a -> Bool Source #

(<=) :: V2 a -> V2 a -> Bool Source #

(>) :: V2 a -> V2 a -> Bool Source #

(>=) :: V2 a -> V2 a -> Bool Source #

max :: V2 a -> V2 a -> V2 a Source #

min :: V2 a -> V2 a -> V2 a Source #

Hashable a => Hashable (V2 a) Source # 
Instance details

Defined in Linear.V2

Methods

hashWithSalt :: Int -> V2 a -> Int Source #

hash :: V2 a -> Int Source #

Ixed (V2 a) Source # 
Instance details

Defined in Linear.V2

Methods

ix :: Index (V2 a) -> Traversal' (V2 a) (IxValue (V2 a)) Source #

Epsilon a => Epsilon (V2 a) Source # 
Instance details

Defined in Linear.V2

Methods

nearZero :: V2 a -> Bool Source #

Random a => Random (V2 a) Source # 
Instance details

Defined in Linear.V2

Methods

randomR :: RandomGen g => (V2 a, V2 a) -> g -> (V2 a, g) Source #

random :: RandomGen g => g -> (V2 a, g) Source #

randomRs :: RandomGen g => (V2 a, V2 a) -> g -> [V2 a] Source #

randoms :: RandomGen g => g -> [V2 a] Source #

Unbox a => Unbox (V2 a) Source # 
Instance details

Defined in Linear.V2

FoldableWithIndex (E V2) V2 Source # 
Instance details

Defined in Linear.V2

Methods

ifoldMap :: Monoid m => (E V2 -> a -> m) -> V2 a -> m Source #

ifoldMap' :: Monoid m => (E V2 -> a -> m) -> V2 a -> m Source #

ifoldr :: (E V2 -> a -> b -> b) -> b -> V2 a -> b Source #

ifoldl :: (E V2 -> b -> a -> b) -> b -> V2 a -> b Source #

ifoldr' :: (E V2 -> a -> b -> b) -> b -> V2 a -> b Source #

ifoldl' :: (E V2 -> b -> a -> b) -> b -> V2 a -> b Source #

FunctorWithIndex (E V2) V2 Source # 
Instance details

Defined in Linear.V2

Methods

imap :: (E V2 -> a -> b) -> V2 a -> V2 b Source #

TraversableWithIndex (E V2) V2 Source # 
Instance details

Defined in Linear.V2

Methods

itraverse :: Applicative f => (E V2 -> a -> f b) -> V2 a -> f (V2 b) Source #

Each (V2 a) (V2 b) a b Source # 
Instance details

Defined in Linear.V2

Methods

each :: Traversal (V2 a) (V2 b) a b Source #

Field1 (V2 a) (V2 a) a a Source # 
Instance details

Defined in Linear.V2

Methods

_1 :: Lens (V2 a) (V2 a) a a Source #

Field2 (V2 a) (V2 a) a a Source # 
Instance details

Defined in Linear.V2

Methods

_2 :: Lens (V2 a) (V2 a) a a Source #

type Rep V2 Source # 
Instance details

Defined in Linear.V2

type Rep V2 = E V2
type Diff V2 Source # 
Instance details

Defined in Linear.Affine

type Diff V2 = V2
type Size V2 Source # 
Instance details

Defined in Linear.V2

type Size V2 = 2
type Rep1 V2 Source # 
Instance details

Defined in Linear.V2

data MVector s (V2 a) Source # 
Instance details

Defined in Linear.V2

data MVector s (V2 a) = MV_V2 !Int !(MVector s a)
type Rep (V2 a) Source # 
Instance details

Defined in Linear.V2

type Rep (V2 a) = D1 ('MetaData "V2" "Linear.V2" "linear-1.22-CRgBRfHw0OsL7QUZ7C9Pko" 'False) (C1 ('MetaCons "V2" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a)))
type Index (V2 a) Source # 
Instance details

Defined in Linear.V2

type Index (V2 a) = E V2
type IxValue (V2 a) Source # 
Instance details

Defined in Linear.V2

type IxValue (V2 a) = a
data Vector (V2 a) Source # 
Instance details

Defined in Linear.V2

data Vector (V2 a) = V_V2 !Int !(Vector a)

class R1 t where Source #

A space that has at least 1 basis vector _x.

Methods

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

>>> V1 2 ^._x
2
>>> V1 2 & _x .~ 3
V1 3

Instances

Instances details
R1 Identity Source # 
Instance details

Defined in Linear.V1

Methods

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

R1 Quaternion Source # 
Instance details

Defined in Linear.Quaternion

Methods

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

R1 V1 Source # 
Instance details

Defined in Linear.V1

Methods

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

R1 V2 Source # 
Instance details

Defined in Linear.V2

Methods

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

R1 V3 Source # 
Instance details

Defined in Linear.V3

Methods

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

R1 V4 Source # 
Instance details

Defined in Linear.V4

Methods

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

R1 f => R1 (Point f) Source # 
Instance details

Defined in Linear.Affine

Methods

_x :: Lens' (Point f a) a Source #

class R1 t => R2 t where Source #

A space that distinguishes 2 orthogonal basis vectors _x and _y, but may have more.

Minimal complete definition

_xy

Methods

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

>>> V2 1 2 ^._y
2
>>> V2 1 2 & _y .~ 3
V2 1 3

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

Instances

Instances details
R2 Quaternion Source # 
Instance details

Defined in Linear.Quaternion

Methods

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

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

R2 V2 Source # 
Instance details

Defined in Linear.V2

Methods

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

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

R2 V3 Source # 
Instance details

Defined in Linear.V3

Methods

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

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

R2 V4 Source # 
Instance details

Defined in Linear.V4

Methods

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

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

R2 f => R2 (Point f) Source # 
Instance details

Defined in Linear.Affine

Methods

_y :: Lens' (Point f a) a Source #

_xy :: Lens' (Point f a) (V2 a) Source #

_yx :: R2 t => Lens' (t a) (V2 a) Source #

>>> V2 1 2 ^. _yx
V2 2 1

ex :: R1 t => E t Source #

ey :: R2 t => E t Source #

perp :: Num a => V2 a -> V2 a Source #

the counter-clockwise perpendicular vector

>>> perp $ V2 10 20
V2 (-20) 10

angle :: Floating a => a -> V2 a Source #

unangle :: (Floating a, Ord a) => V2 a -> a Source #

crossZ :: Num a => V2 a -> V2 a -> a Source #

The Z-component of the cross product of two vectors in the XY-plane.

>>> crossZ (V2 1 0) (V2 0 1)
1