linear-1.20.2: 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

toVector :: Vector a
 

Instances

FunctorWithIndex Int (V k n) Source 
FoldableWithIndex Int (V k n) Source 
TraversableWithIndex Int (V k n) Source 
(Dim k n, Unbox a) => Vector Vector (V k n a) Source 
(Dim k n, Unbox a) => MVector MVector (V k n a) Source 
Dim k n => Dim * (V k n a) Source 
Dim k n => Monad (V k n) Source 
Functor (V k n) Source 
Dim k n => MonadFix (V k n) Source 
Dim k n => Applicative (V k n) Source 
Foldable (V k n) Source 
Traversable (V k n) Source 
Generic1 (V k n) Source 
Dim k n => Distributive (V k n) Source 
Dim k n => Representable (V k n) Source 
Dim k n => MonadZip (V k n) Source 
Dim k n => Serial1 (V k n) Source 
Apply (V k n) Source 
Bind (V k n) Source 
Dim k n => Eq1 (V k n) Source 
Dim k n => Ord1 (V k n) Source 
Dim k n => Read1 (V k n) Source 
Dim k n => Show1 (V k n) Source 
Dim k n => Additive (V k n) Source 
Dim k n => Metric (V k n) Source 
Dim * n => Trace (V * n) Source 
Dim * n => Affine (V * n) Source 
(Bounded a, Dim k n) => Bounded (V k n a) Source 
Eq a => Eq (V k n a) Source 
(Dim k n, Floating a) => Floating (V k n a) Source 
(Dim k n, Fractional a) => Fractional (V k n a) Source 
(Typeable (* -> *) (V k n), Typeable * (V k n a), Dim k n, Data a) => Data (V k n a) Source 
(Dim k n, Num a) => Num (V k n a) Source 
Ord a => Ord (V k n a) Source 
Read a => Read (V k n a) Source 
Show a => Show (V k n a) Source 
Generic (V k n a) Source 
(Dim k n, Storable a) => Storable (V k n a) Source 
(Dim k n, Binary a) => Binary (V k n a) Source 
(Dim k n, Serial a) => Serial (V k n a) Source 
(Dim k n, Serialize a) => Serialize (V k n a) Source 
NFData a => NFData (V k n a) Source 
(Dim k n, Unbox a) => Unbox (V k n a) Source 
Ixed (V k n a) Source 
(Dim k n, Epsilon a) => Epsilon (V k n a) Source 
Each (V k n a) (V k n b) a b Source 
data MVector s (V k n a) = MV_VN !Int !(MVector s a) Source 
type Rep1 (V k n) Source 
type Rep (V k n) = Int Source 
type Diff (V * n) = V * n Source 
type Rep (V k n a) Source 
data Vector (V k n a) = V_VN !Int !(Vector a) Source 
type Index (V k n a) = Int Source 
type IxValue (V k n a) = a Source 

int :: Int -> TypeQ

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

KnownNat n => Dim Nat n Source 
Dim k n => Dim * (V k n a) 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. KnownNat n => Proxy n -> r) -> r Source

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

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