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

Linear.V

Description

n-D Vectors

Synopsis

Documentation

newtype V n a Source #

Constructors

V 

Fields

Instances

Instances details
FunctorWithIndex Int (V n) Source # 
Instance details

Defined in Linear.V

Methods

imap :: (Int -> a -> b) -> V n a -> V n b Source #

imapped :: IndexedSetter Int (V n a) (V n b) a b Source #

FoldableWithIndex Int (V n) Source # 
Instance details

Defined in Linear.V

Methods

ifoldMap :: Monoid m => (Int -> a -> m) -> V n a -> m Source #

ifolded :: IndexedFold Int (V n a) a Source #

ifoldr :: (Int -> a -> b -> b) -> b -> V n a -> b Source #

ifoldl :: (Int -> b -> a -> b) -> b -> V n a -> b Source #

ifoldr' :: (Int -> a -> b -> b) -> b -> V n a -> b Source #

ifoldl' :: (Int -> b -> a -> b) -> b -> V n a -> b Source #

TraversableWithIndex Int (V n) Source # 
Instance details

Defined in Linear.V

Methods

itraverse :: Applicative f => (Int -> a -> f b) -> V n a -> f (V n b) Source #

itraversed :: IndexedTraversal Int (V n a) (V n b) a b Source #

(Dim n, Unbox a) => Vector Vector (V n a) Source # 
Instance details

Defined in Linear.V

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (V n a) -> m (Vector (V n a)) Source #

basicUnsafeThaw :: PrimMonad m => Vector (V n a) -> m (Mutable Vector (PrimState m) (V n a)) Source #

basicLength :: Vector (V n a) -> Int Source #

basicUnsafeSlice :: Int -> Int -> Vector (V n a) -> Vector (V n a) Source #

basicUnsafeIndexM :: Monad m => Vector (V n a) -> Int -> m (V n a) Source #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (V n a) -> Vector (V n a) -> m () Source #

elemseq :: Vector (V n a) -> V n a -> b -> b Source #

(Dim n, Unbox a) => MVector MVector (V n a) Source # 
Instance details

Defined in Linear.V

Methods

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

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

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

basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (V n a)) Source #

basicInitialize :: PrimMonad m => MVector (PrimState m) (V n a) -> m () Source #

basicUnsafeReplicate :: PrimMonad m => Int -> V n a -> m (MVector (PrimState m) (V n a)) Source #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (V n a) -> Int -> m (V n a) Source #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (V n a) -> Int -> V n a -> m () Source #

basicClear :: PrimMonad m => MVector (PrimState m) (V n a) -> m () Source #

basicSet :: PrimMonad m => MVector (PrimState m) (V n a) -> V n a -> m () Source #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (V n a) -> MVector (PrimState m) (V n a) -> m () Source #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (V n a) -> MVector (PrimState m) (V n a) -> m () Source #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (V n a) -> Int -> m (MVector (PrimState m) (V n a)) Source #

Generic1 (V n :: Type -> Type) Source # 
Instance details

Defined in Linear.V

Associated Types

type Rep1 (V n) :: k -> Type

Methods

from1 :: forall (a :: k). V n a -> Rep1 (V n) a

to1 :: forall (a :: k). Rep1 (V n) a -> V n a

Dim n => Dim (V n a :: Type) Source # 
Instance details

Defined in Linear.V

Methods

reflectDim :: p (V n a) -> Int Source #

Dim n => Monad (V n) Source # 
Instance details

Defined in Linear.V

Methods

(>>=) :: V n a -> (a -> V n b) -> V n b

(>>) :: V n a -> V n b -> V n b

return :: a -> V n a

Functor (V n) Source # 
Instance details

Defined in Linear.V

Methods

fmap :: (a -> b) -> V n a -> V n b #

(<$) :: a -> V n b -> V n a #

Dim n => MonadFix (V n) Source # 
Instance details

Defined in Linear.V

Methods

mfix :: (a -> V n a) -> V n a

Dim n => Applicative (V n) Source # 
Instance details

Defined in Linear.V

Methods

pure :: a -> V n a

(<*>) :: V n (a -> b) -> V n a -> V n b

liftA2 :: (a -> b -> c) -> V n a -> V n b -> V n c

(*>) :: V n a -> V n b -> V n b

(<*) :: V n a -> V n b -> V n a

Foldable (V n) Source # 
Instance details

Defined in Linear.V

Methods

fold :: Monoid m => V n m -> m

foldMap :: Monoid m => (a -> m) -> V n a -> m

foldMap' :: Monoid m => (a -> m) -> V n a -> m

foldr :: (a -> b -> b) -> b -> V n a -> b

foldr' :: (a -> b -> b) -> b -> V n a -> b

foldl :: (b -> a -> b) -> b -> V n a -> b

foldl' :: (b -> a -> b) -> b -> V n a -> b

foldr1 :: (a -> a -> a) -> V n a -> a

foldl1 :: (a -> a -> a) -> V n a -> a

toList :: V n a -> [a]

null :: V n a -> Bool

length :: V n a -> Int

elem :: Eq a => a -> V n a -> Bool

maximum :: Ord a => V n a -> a

minimum :: Ord a => V n a -> a

sum :: Num a => V n a -> a

product :: Num a => V n a -> a

Traversable (V n) Source # 
Instance details

Defined in Linear.V

Methods

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

sequenceA :: Applicative f => V n (f a) -> f (V n a)

mapM :: Monad m => (a -> m b) -> V n a -> m (V n b)

sequence :: Monad m => V n (m a) -> m (V n a)

Dim n => Distributive (V n) Source # 
Instance details

Defined in Linear.V

Methods

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

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

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

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

Dim n => Representable (V n) Source # 
Instance details

Defined in Linear.V

Associated Types

type Rep (V n) Source #

Methods

tabulate :: (Rep (V n) -> a) -> V n a Source #

index :: V n a -> Rep (V n) -> a Source #

Show1 (V n) Source # 
Instance details

Defined in Linear.V

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> V n a -> ShowS

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [V n a] -> ShowS

Dim n => Read1 (V n) Source # 
Instance details

Defined in Linear.V

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (V n a)

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [V n a]

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (V n a)

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [V n a]

Ord1 (V n) Source # 
Instance details

Defined in Linear.V

Methods

liftCompare :: (a -> b -> Ordering) -> V n a -> V n b -> Ordering

Eq1 (V n) Source # 
Instance details

Defined in Linear.V

Methods

liftEq :: (a -> b -> Bool) -> V n a -> V n b -> Bool

Dim n => MonadZip (V n) Source # 
Instance details

Defined in Linear.V

Methods

mzip :: V n a -> V n b -> V n (a, b)

mzipWith :: (a -> b -> c) -> V n a -> V n b -> V n c

munzip :: V n (a, b) -> (V n a, V n b)

Dim n => Serial1 (V n) Source # 
Instance details

Defined in Linear.V

Methods

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

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

Dim n => Hashable1 (V n) Source # 
Instance details

Defined in Linear.V

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> V n a -> Int Source #

Apply (V n) Source # 
Instance details

Defined in Linear.V

Methods

(<.>) :: V n (a -> b) -> V n a -> V n b Source #

(.>) :: V n a -> V n b -> V n b Source #

(<.) :: V n a -> V n b -> V n a Source #

liftF2 :: (a -> b -> c) -> V n a -> V n b -> V n c Source #

Bind (V n) Source # 
Instance details

Defined in Linear.V

Methods

(>>-) :: V n a -> (a -> V n b) -> V n b Source #

join :: V n (V n a) -> V n a Source #

Dim n => Additive (V n) Source # 
Instance details

Defined in Linear.V

Methods

zero :: Num a => V n a Source #

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

(^-^) :: Num a => V n a -> V n a -> V n a Source #

lerp :: Num a => a -> V n a -> V n a -> V n a Source #

liftU2 :: (a -> a -> a) -> V n a -> V n a -> V n a Source #

liftI2 :: (a -> b -> c) -> V n a -> V n b -> V n c Source #

Dim n => Metric (V n) Source # 
Instance details

Defined in Linear.V

Methods

dot :: Num a => V n a -> V n a -> a Source #

quadrance :: Num a => V n a -> a Source #

qd :: Num a => V n a -> V n a -> a Source #

distance :: Floating a => V n a -> V n a -> a Source #

norm :: Floating a => V n a -> a Source #

signorm :: Floating a => V n a -> V n a Source #

Finite (V n) Source # 
Instance details

Defined in Linear.V

Associated Types

type Size (V n) :: Nat Source #

Methods

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

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

Dim n => Trace (V n) Source # 
Instance details

Defined in Linear.Trace

Methods

trace :: Num a => V n (V n a) -> a Source #

diagonal :: V n (V n a) -> V n a Source #

Dim n => Affine (V n) Source # 
Instance details

Defined in Linear.Affine

Associated Types

type Diff (V n) :: Type -> Type Source #

Methods

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

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

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

(Bounded a, Dim n) => Bounded (V n a) Source # 
Instance details

Defined in Linear.V

Methods

minBound :: V n a

maxBound :: V n a

Eq a => Eq (V n a) Source # 
Instance details

Defined in Linear.V

Methods

(==) :: V n a -> V n a -> Bool

(/=) :: V n a -> V n a -> Bool

(Dim n, Floating a) => Floating (V n a) Source # 
Instance details

Defined in Linear.V

Methods

pi :: V n a

exp :: V n a -> V n a

log :: V n a -> V n a

sqrt :: V n a -> V n a

(**) :: V n a -> V n a -> V n a

logBase :: V n a -> V n a -> V n a

sin :: V n a -> V n a

cos :: V n a -> V n a

tan :: V n a -> V n a

asin :: V n a -> V n a

acos :: V n a -> V n a

atan :: V n a -> V n a

sinh :: V n a -> V n a

cosh :: V n a -> V n a

tanh :: V n a -> V n a

asinh :: V n a -> V n a

acosh :: V n a -> V n a

atanh :: V n a -> V n a

log1p :: V n a -> V n a

expm1 :: V n a -> V n a

log1pexp :: V n a -> V n a

log1mexp :: V n a -> V n a

(Dim n, Fractional a) => Fractional (V n a) Source # 
Instance details

Defined in Linear.V

Methods

(/) :: V n a -> V n a -> V n a

recip :: V n a -> V n a

fromRational :: Rational -> V n a

(Typeable (V n), Typeable (V n a), Dim n, Data a) => Data (V n a) Source # 
Instance details

Defined in Linear.V

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> V n a -> c (V n a)

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (V n a)

toConstr :: V n a -> Constr

dataTypeOf :: V n a -> DataType

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

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

gmapT :: (forall b. Data b => b -> b) -> V n a -> V n a

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> V n a -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> V n a -> r

gmapQ :: (forall d. Data d => d -> u) -> V n a -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> V n a -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> V n a -> m (V n a)

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> V n a -> m (V n a)

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> V n a -> m (V n a)

(Dim n, Num a) => Num (V n a) Source # 
Instance details

Defined in Linear.V

Methods

(+) :: V n a -> V n a -> V n a

(-) :: V n a -> V n a -> V n a

(*) :: V n a -> V n a -> V n a

negate :: V n a -> V n a

abs :: V n a -> V n a

signum :: V n a -> V n a

fromInteger :: Integer -> V n a

Ord a => Ord (V n a) Source # 
Instance details

Defined in Linear.V

Methods

compare :: V n a -> V n a -> Ordering

(<) :: V n a -> V n a -> Bool

(<=) :: V n a -> V n a -> Bool

(>) :: V n a -> V n a -> Bool

(>=) :: V n a -> V n a -> Bool

max :: V n a -> V n a -> V n a

min :: V n a -> V n a -> V n a

Read a => Read (V n a) Source # 
Instance details

Defined in Linear.V

Methods

readsPrec :: Int -> ReadS (V n a)

readList :: ReadS [V n a]

readPrec :: ReadPrec (V n a)

readListPrec :: ReadPrec [V n a]

Show a => Show (V n a) Source # 
Instance details

Defined in Linear.V

Methods

showsPrec :: Int -> V n a -> ShowS

show :: V n a -> String

showList :: [V n a] -> ShowS

Generic (V n a) Source # 
Instance details

Defined in Linear.V

Associated Types

type Rep (V n a) :: Type -> Type

Methods

from :: V n a -> Rep (V n a) x

to :: Rep (V n a) x -> V n a

(Dim n, Storable a) => Storable (V n a) Source # 
Instance details

Defined in Linear.V

Methods

sizeOf :: V n a -> Int

alignment :: V n a -> Int

peekElemOff :: Ptr (V n a) -> Int -> IO (V n a)

pokeElemOff :: Ptr (V n a) -> Int -> V n a -> IO ()

peekByteOff :: Ptr b -> Int -> IO (V n a)

pokeByteOff :: Ptr b -> Int -> V n a -> IO ()

peek :: Ptr (V n a) -> IO (V n a)

poke :: Ptr (V n a) -> V n a -> IO ()

(Dim n, Serial a) => Serial (V n a) Source # 
Instance details

Defined in Linear.V

Methods

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

deserialize :: MonadGet m => m (V n a) Source #

(Dim n, Serialize a) => Serialize (V n a) Source # 
Instance details

Defined in Linear.V

Methods

put :: Putter (V n a) Source #

get :: Get (V n a) Source #

Hashable a => Hashable (V n a) Source # 
Instance details

Defined in Linear.V

Methods

hashWithSalt :: Int -> V n a -> Int Source #

hash :: V n a -> Int Source #

(Dim n, Unbox a) => Unbox (V n a) Source # 
Instance details

Defined in Linear.V

Ixed (V n a) Source # 
Instance details

Defined in Linear.V

Methods

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

(Dim n, Binary a) => Binary (V n a) Source # 
Instance details

Defined in Linear.V

Methods

put :: V n a -> Put

get :: Get (V n a)

putList :: [V n a] -> Put

NFData a => NFData (V n a) Source # 
Instance details

Defined in Linear.V

Methods

rnf :: V n a -> ()

(Dim n, Epsilon a) => Epsilon (V n a) Source # 
Instance details

Defined in Linear.V

Methods

nearZero :: V n a -> Bool Source #

Each (V n a) (V n b) a b Source # 
Instance details

Defined in Linear.V

Methods

each :: Traversal (V n a) (V n b) a b Source #

1 <= n => Field1 (V n a) (V n a) a a Source # 
Instance details

Defined in Linear.V

Methods

_1 :: Lens (V n a) (V n a) a a Source #

2 <= n => Field2 (V n a) (V n a) a a Source # 
Instance details

Defined in Linear.V

Methods

_2 :: Lens (V n a) (V n a) a a Source #

3 <= n => Field3 (V n a) (V n a) a a Source # 
Instance details

Defined in Linear.V

Methods

_3 :: Lens (V n a) (V n a) a a Source #

4 <= n => Field4 (V n a) (V n a) a a Source # 
Instance details

Defined in Linear.V

Methods

_4 :: Lens (V n a) (V n a) a a Source #

5 <= n => Field5 (V n a) (V n a) a a Source # 
Instance details

Defined in Linear.V

Methods

_5 :: Lens (V n a) (V n a) a a Source #

6 <= n => Field6 (V n a) (V n a) a a Source # 
Instance details

Defined in Linear.V

Methods

_6 :: Lens (V n a) (V n a) a a Source #

7 <= n => Field7 (V n a) (V n a) a a Source # 
Instance details

Defined in Linear.V

Methods

_7 :: Lens (V n a) (V n a) a a Source #

8 <= n => Field8 (V n a) (V n a) a a Source # 
Instance details

Defined in Linear.V

Methods

_8 :: Lens (V n a) (V n a) a a Source #

9 <= n => Field9 (V n a) (V n a) a a Source # 
Instance details

Defined in Linear.V

Methods

_9 :: Lens (V n a) (V n a) a a Source #

10 <= n => Field10 (V n a) (V n a) a a Source # 
Instance details

Defined in Linear.V

Methods

_10 :: Lens (V n a) (V n a) a a Source #

11 <= n => Field11 (V n a) (V n a) a a Source # 
Instance details

Defined in Linear.V

Methods

_11 :: Lens (V n a) (V n a) a a Source #

12 <= n => Field12 (V n a) (V n a) a a Source # 
Instance details

Defined in Linear.V

Methods

_12 :: Lens (V n a) (V n a) a a Source #

13 <= n => Field13 (V n a) (V n a) a a Source # 
Instance details

Defined in Linear.V

Methods

_13 :: Lens (V n a) (V n a) a a Source #

14 <= n => Field14 (V n a) (V n a) a a Source # 
Instance details

Defined in Linear.V

Methods

_14 :: Lens (V n a) (V n a) a a Source #

15 <= n => Field15 (V n a) (V n a) a a Source # 
Instance details

Defined in Linear.V

Methods

_15 :: Lens (V n a) (V n a) a a Source #

16 <= n => Field16 (V n a) (V n a) a a Source # 
Instance details

Defined in Linear.V

Methods

_16 :: Lens (V n a) (V n a) a a Source #

17 <= n => Field17 (V n a) (V n a) a a Source # 
Instance details

Defined in Linear.V

Methods

_17 :: Lens (V n a) (V n a) a a Source #

18 <= n => Field18 (V n a) (V n a) a a Source # 
Instance details

Defined in Linear.V

Methods

_18 :: Lens (V n a) (V n a) a a Source #

19 <= n => Field19 (V n a) (V n a) a a Source # 
Instance details

Defined in Linear.V

Methods

_19 :: Lens (V n a) (V n a) a a Source #

data MVector s (V n a) Source # 
Instance details

Defined in Linear.V

data MVector s (V n a) = MV_VN !Int !(MVector s a)
type Rep1 (V n :: Type -> Type) Source # 
Instance details

Defined in Linear.V

type Rep1 (V n :: Type -> Type) = D1 ('MetaData "V" "Linear.V" "linear-1.20.9-RPUBINYq384VPzdgkhYOj" 'True) (C1 ('MetaCons "V" 'PrefixI 'True) (S1 ('MetaSel ('Just "toVector") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 Vector)))
type Rep (V n) Source # 
Instance details

Defined in Linear.V

type Rep (V n) = Int
type Size (V n) Source # 
Instance details

Defined in Linear.V

type Size (V n) = n
type Diff (V n) Source # 
Instance details

Defined in Linear.Affine

type Diff (V n) = V n
type Rep (V n a) Source # 
Instance details

Defined in Linear.V

type Rep (V n a) = D1 ('MetaData "V" "Linear.V" "linear-1.20.9-RPUBINYq384VPzdgkhYOj" 'True) (C1 ('MetaCons "V" 'PrefixI 'True) (S1 ('MetaSel ('Just "toVector") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Vector a))))
data Vector (V n a) Source # 
Instance details

Defined in Linear.V

data Vector (V n a) = V_VN !Int !(Vector a)
type Index (V n a) Source # 
Instance details

Defined in Linear.V

type Index (V n a) = Int
type IxValue (V n a) Source # 
Instance details

Defined in Linear.V

type IxValue (V n a) = a

int :: Int -> TypeQ Source #

This can be used to generate a template haskell splice for a type level version of a given int.

This does not use GHC TypeLits, instead it generates a numeric type by hand similar to the ones used in the "Functional Pearl: Implicit Configurations" paper by Oleg Kiselyov and Chung-Chieh Shan.

instance Num (Q Exp) provided in this package allows writing $(3) instead of $(int 3). Sometimes the two will produce the same representation (if compiled without the -DUSE_TYPE_LITS preprocessor directive).

dim :: forall n a. Dim n => V n a -> Int Source #

class Dim n where Source #

Methods

reflectDim :: p n -> Int Source #

Instances

Instances details
KnownNat n => Dim (n :: Nat) Source # 
Instance details

Defined in Linear.V

Methods

reflectDim :: p n -> Int Source #

Dim n => Dim (V n a :: Type) Source # 
Instance details

Defined in Linear.V

Methods

reflectDim :: p (V n a) -> Int Source #

reifyDim :: Int -> (forall (n :: *). Dim n => Proxy n -> r) -> r Source #

reifyVector :: forall a r. Vector a -> (forall (n :: *). Dim n => V n a -> r) -> r Source #

reifyDimNat :: Int -> (forall (n :: Nat). KnownNat n => Proxy n -> r) -> r Source #

reifyVectorNat :: forall a r. Vector a -> (forall (n :: Nat). KnownNat n => V n a -> r) -> r Source #

fromVector :: forall n a. Dim n => Vector a -> Maybe (V n a) Source #

class Finite v where Source #

Minimal complete definition

fromV

Associated Types

type Size (v :: * -> *) :: Nat Source #

Methods

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

default toV :: Foldable v => v a -> V (Size v) a Source #

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

Instances

Instances details
Finite Complex Source # 
Instance details

Defined in Linear.V

Associated Types

type Size Complex :: Nat Source #

Methods

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

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

Finite V1 Source # 
Instance details

Defined in Linear.V1

Associated Types

type Size V1 :: Nat Source #

Methods

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

fromV :: V (Size V1) a -> V1 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 #

Finite V3 Source # 
Instance details

Defined in Linear.V3

Associated Types

type Size V3 :: Nat Source #

Methods

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

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

Finite V4 Source # 
Instance details

Defined in Linear.V4

Associated Types

type Size V4 :: Nat Source #

Methods

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

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

Finite V0 Source # 
Instance details

Defined in Linear.V0

Associated Types

type Size V0 :: Nat Source #

Methods

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

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

Finite Quaternion Source # 
Instance details

Defined in Linear.Quaternion

Associated Types

type Size Quaternion :: Nat Source #

Finite Plucker Source # 
Instance details

Defined in Linear.Plucker

Associated Types

type Size Plucker :: Nat Source #

Methods

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

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

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

Defined in Linear.Affine

Associated Types

type Size (Point f) :: Nat Source #

Methods

toV :: Point f a -> V (Size (Point f)) a Source #

fromV :: V (Size (Point f)) a -> Point f a Source #

Finite (V n) Source # 
Instance details

Defined in Linear.V

Associated Types

type Size (V n) :: Nat Source #

Methods

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

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

_V :: (Finite u, Finite v) => Iso (V (Size u) a) (V (Size v) b) (u a) (v b) Source #

_V' :: Finite v => Iso (V (Size v) a) (V (Size v) b) (v a) (v b) Source #