fixed-vector-2.0.0.0: Generic vectors with statically known size.
Safe HaskellNone
LanguageHaskell2010

Data.Vector.Fixed

Description

fixed-vector library provides general API for working with short N-element arrays. Functions in this module work on data types which are instances of Vector type class. We provide instances for data types from base: tuples, Complex, and few others. There are several length polymorphic arrays:

Type level naturals don't have support for induction so all type level computation with length and indices are done using Peano numerals (PeanoNum). Type level naturals are only used as type parameters for defining length of arrays.

Instances for tuples

Library provides instances for tuples. They however come with caveat. Let look at Vector instance for 2-tuple:

instance b ~ a => Vector ((,) b) a

Tuple could only be Vector instance if all elements have same type. so first element fixes type of second one. Thus functions which change element type like map won't work:

>>> map (== 1) ((1,2) :: (Int,Int))

<interactive>:3:1:
    Couldn't match type `Int' with `Bool'
    In the expression: F.map (== 1) ((1, 2) :: (Int, Int))
    In an equation for `it': it = map (== 1) ((1, 2) :: (Int, Int))

This could be solved either by switching to ContVec manually:

>>> (vector . map (==1) . cvec) ((1, 2) :: Tuple2 Int) :: Tuple2 Bool
(True,False)

or by using functions genereic in vector type from module Data.Vector.Fixed.Generic.

Synopsis

Vector type class

class ArityPeano (Dim v) => Vector (v :: Type -> Type) a where Source #

Type class for vectors with fixed length. Instance should provide two functions: one to create vector from N elements and another for vector deconstruction. They must obey following law:

inspect v construct = v

For example instance for 2D vectors could be written as:

data V2 a = V2 a a

type instance V2 = 2
instance Vector V2 a where
  construct                = Fun V2
  inspect (V2 a b) (Fun f) = f a b

Minimal complete definition

construct, inspect

Methods

construct :: Fun (Dim v) a (v a) Source #

N-ary function for creation of vectors. It takes N elements of array as parameters and return vector.

inspect :: v a -> Fun (Dim v) a b -> b Source #

Deconstruction of vector. It takes N-ary function as parameters and applies vector's elements to it.

basicIndex :: v a -> Int -> a Source #

Optional more efficient implementation of indexing. Shouldn't be used directly, use ! instead.

Instances

Instances details
Vector Complex a Source # 
Instance details

Defined in Data.Vector.Fixed.Cont

Methods

construct :: Fun (Dim Complex) a (Complex a) Source #

inspect :: Complex a -> Fun (Dim Complex) a b -> b Source #

basicIndex :: Complex a -> Int -> a Source #

Vector Identity a Source # 
Instance details

Defined in Data.Vector.Fixed.Cont

Vector Only a Source # 
Instance details

Defined in Data.Vector.Fixed

Methods

construct :: Fun (Dim Only) a (Only a) Source #

inspect :: Only a -> Fun (Dim Only) a b -> b Source #

basicIndex :: Only a -> Int -> a Source #

Vector (Proxy :: Type -> Type) a Source # 
Instance details

Defined in Data.Vector.Fixed.Cont

Methods

construct :: Fun (Dim (Proxy :: Type -> Type)) a (Proxy a) Source #

inspect :: Proxy a -> Fun (Dim (Proxy :: Type -> Type)) a b -> b Source #

basicIndex :: Proxy a -> Int -> a Source #

Vector (Empty :: Type -> Type) a Source # 
Instance details

Defined in Data.Vector.Fixed

Methods

construct :: Fun (Dim (Empty :: Type -> Type)) a (Empty a) Source #

inspect :: Empty a -> Fun (Dim (Empty :: Type -> Type)) a b -> b Source #

basicIndex :: Empty a -> Int -> a Source #

Arity n => Vector (VecList n) a Source # 
Instance details

Defined in Data.Vector.Fixed

Methods

construct :: Fun (Dim (VecList n)) a (VecList n a) Source #

inspect :: VecList n a -> Fun (Dim (VecList n)) a b -> b Source #

basicIndex :: VecList n a -> Int -> a Source #

ArityPeano n => Vector (VecPeano n) a Source # 
Instance details

Defined in Data.Vector.Fixed

Methods

construct :: Fun (Dim (VecPeano n)) a (VecPeano n a) Source #

inspect :: VecPeano n a -> Fun (Dim (VecPeano n)) a b -> b Source #

basicIndex :: VecPeano n a -> Int -> a Source #

Arity n => Vector (Vec n) a Source # 
Instance details

Defined in Data.Vector.Fixed.Boxed

Methods

construct :: Fun (Dim (Vec n)) a (Vec n a) Source #

inspect :: Vec n a -> Fun (Dim (Vec n)) a b -> b Source #

basicIndex :: Vec n a -> Int -> a Source #

ArityPeano n => Vector (ContVec n) a Source # 
Instance details

Defined in Data.Vector.Fixed.Cont

Methods

construct :: Fun (Dim (ContVec n)) a (ContVec n a) Source #

inspect :: ContVec n a -> Fun (Dim (ContVec n)) a b -> b Source #

basicIndex :: ContVec n a -> Int -> a Source #

(Arity n, Prim a) => Vector (Vec n) a Source # 
Instance details

Defined in Data.Vector.Fixed.Primitive

Methods

construct :: Fun (Dim (Vec n)) a (Vec n a) Source #

inspect :: Vec n a -> Fun (Dim (Vec n)) a b -> b Source #

basicIndex :: Vec n a -> Int -> a Source #

(Arity n, Storable a) => Vector (Vec n) a Source # 
Instance details

Defined in Data.Vector.Fixed.Storable

Methods

construct :: Fun (Dim (Vec n)) a (Vec n a) Source #

inspect :: Vec n a -> Fun (Dim (Vec n)) a b -> b Source #

basicIndex :: Vec n a -> Int -> a Source #

Arity n => Vector (Vec n) a Source # 
Instance details

Defined in Data.Vector.Fixed.Strict

Methods

construct :: Fun (Dim (Vec n)) a (Vec n a) Source #

inspect :: Vec n a -> Fun (Dim (Vec n)) a b -> b Source #

basicIndex :: Vec n a -> Int -> a Source #

(n <= 64, Arity n, a ~ Bool) => Vector (BitVec n) a Source # 
Instance details

Defined in Data.Vector.Fixed.Unboxed

Methods

construct :: Fun (Dim (BitVec n)) a (BitVec n a) Source #

inspect :: BitVec n a -> Fun (Dim (BitVec n)) a b -> b Source #

basicIndex :: BitVec n a -> Int -> a Source #

(Arity n, Unbox n a) => Vector (Vec n) a Source # 
Instance details

Defined in Data.Vector.Fixed.Unboxed

Methods

construct :: Fun (Dim (Vec n)) a (Vec n a) Source #

inspect :: Vec n a -> Fun (Dim (Vec n)) a b -> b Source #

basicIndex :: Vec n a -> Int -> a Source #

b ~ a => Vector ((,) b) a Source #

Note this instance (and other instances for tuples) is essentially monomorphic in element type. Vector type v of 2 element tuple (Int,Int) is (,) Int so it will only work with elements of type Int.

Instance details

Defined in Data.Vector.Fixed.Cont

Methods

construct :: Fun (Dim ((,) b)) a (b, a) Source #

inspect :: (b, a) -> Fun (Dim ((,) b)) a b0 -> b0 Source #

basicIndex :: (b, a) -> Int -> a Source #

Vector v a => Vector (ViaFixed v) a Source # 
Instance details

Defined in Data.Vector.Fixed

Methods

construct :: Fun (Dim (ViaFixed v)) a (ViaFixed v a) Source #

inspect :: ViaFixed v a -> Fun (Dim (ViaFixed v)) a b -> b Source #

basicIndex :: ViaFixed v a -> Int -> a Source #

(b ~ a, c ~ a) => Vector ((,,) b c) a Source # 
Instance details

Defined in Data.Vector.Fixed.Cont

Methods

construct :: Fun (Dim ((,,) b c)) a (b, c, a) Source #

inspect :: (b, c, a) -> Fun (Dim ((,,) b c)) a b0 -> b0 Source #

basicIndex :: (b, c, a) -> Int -> a Source #

(b ~ a, c ~ a, d ~ a) => Vector ((,,,) b c d) a Source # 
Instance details

Defined in Data.Vector.Fixed.Cont

Methods

construct :: Fun (Dim ((,,,) b c d)) a (b, c, d, a) Source #

inspect :: (b, c, d, a) -> Fun (Dim ((,,,) b c d)) a b0 -> b0 Source #

basicIndex :: (b, c, d, a) -> Int -> a Source #

(Arity n, Unbox n a, Unbox n b) => Vector (T2 n a b) (a, b) Source # 
Instance details

Defined in Data.Vector.Fixed.Unboxed

Methods

construct :: Fun (Dim (T2 n a b)) (a, b) (T2 n a b (a, b)) Source #

inspect :: T2 n a b (a, b) -> Fun (Dim (T2 n a b)) (a, b) b0 -> b0 Source #

basicIndex :: T2 n a b (a, b) -> Int -> (a, b) Source #

(b ~ a, c ~ a, d ~ a, e ~ a) => Vector ((,,,,) b c d e) a Source # 
Instance details

Defined in Data.Vector.Fixed.Cont

Methods

construct :: Fun (Dim ((,,,,) b c d e)) a (b, c, d, e, a) Source #

inspect :: (b, c, d, e, a) -> Fun (Dim ((,,,,) b c d e)) a b0 -> b0 Source #

basicIndex :: (b, c, d, e, a) -> Int -> a Source #

(Arity n, Unbox n a, Unbox n b, Unbox n c) => Vector (T3 n a b c) (a, b, c) Source # 
Instance details

Defined in Data.Vector.Fixed.Unboxed

Methods

construct :: Fun (Dim (T3 n a b c)) (a, b, c) (T3 n a b c (a, b, c)) Source #

inspect :: T3 n a b c (a, b, c) -> Fun (Dim (T3 n a b c)) (a, b, c) b0 -> b0 Source #

basicIndex :: T3 n a b c (a, b, c) -> Int -> (a, b, c) Source #

(b ~ a, c ~ a, d ~ a, e ~ a, f ~ a) => Vector ((,,,,,) b c d e f) a Source # 
Instance details

Defined in Data.Vector.Fixed.Cont

Methods

construct :: Fun (Dim ((,,,,,) b c d e f)) a (b, c, d, e, f, a) Source #

inspect :: (b, c, d, e, f, a) -> Fun (Dim ((,,,,,) b c d e f)) a b0 -> b0 Source #

basicIndex :: (b, c, d, e, f, a) -> Int -> a Source #

(b ~ a, c ~ a, d ~ a, e ~ a, f ~ a, g ~ a) => Vector ((,,,,,,) b c d e f g) a Source # 
Instance details

Defined in Data.Vector.Fixed.Cont

Methods

construct :: Fun (Dim ((,,,,,,) b c d e f g)) a (b, c, d, e, f, g, a) Source #

inspect :: (b, c, d, e, f, g, a) -> Fun (Dim ((,,,,,,) b c d e f g)) a b0 -> b0 Source #

basicIndex :: (b, c, d, e, f, g, a) -> Int -> a Source #

type family Dim (v :: Type -> Type) :: PeanoNum Source #

Size of vector expressed as Peano natural.

Instances

Instances details
type Dim Complex Source # 
Instance details

Defined in Data.Vector.Fixed.Cont

type Dim Complex = N2
type Dim Identity Source # 
Instance details

Defined in Data.Vector.Fixed.Cont

type Dim Identity = N1
type Dim Only Source # 
Instance details

Defined in Data.Vector.Fixed

type Dim Only = N1
type Dim (Proxy :: Type -> Type) Source # 
Instance details

Defined in Data.Vector.Fixed.Cont

type Dim (Proxy :: Type -> Type) = 'Z
type Dim (Empty :: Type -> Type) Source # 
Instance details

Defined in Data.Vector.Fixed

type Dim (Empty :: Type -> Type) = 'Z
type Dim (VecList n) Source # 
Instance details

Defined in Data.Vector.Fixed

type Dim (VecList n) = Peano n
type Dim (VecPeano n) Source # 
Instance details

Defined in Data.Vector.Fixed

type Dim (VecPeano n) = n
type Dim (Vec n) Source # 
Instance details

Defined in Data.Vector.Fixed.Boxed

type Dim (Vec n) = Peano n
type Dim (ContVec n) Source # 
Instance details

Defined in Data.Vector.Fixed.Cont

type Dim (ContVec n) = n
type Dim (Vec n) Source # 
Instance details

Defined in Data.Vector.Fixed.Primitive

type Dim (Vec n) = Peano n
type Dim (Vec n) Source # 
Instance details

Defined in Data.Vector.Fixed.Storable

type Dim (Vec n) = Peano n
type Dim (Vec n) Source # 
Instance details

Defined in Data.Vector.Fixed.Strict

type Dim (Vec n) = Peano n
type Dim (BitVec n) Source # 
Instance details

Defined in Data.Vector.Fixed.Unboxed

type Dim (BitVec n) = Peano n
type Dim (Vec n) Source # 
Instance details

Defined in Data.Vector.Fixed.Unboxed

type Dim (Vec n) = Peano n
type Dim ((,) a) Source # 
Instance details

Defined in Data.Vector.Fixed.Cont

type Dim ((,) a) = N2
type Dim (ViaFixed v) Source # 
Instance details

Defined in Data.Vector.Fixed

type Dim (ViaFixed v) = Dim v
type Dim ((,,) a b) Source # 
Instance details

Defined in Data.Vector.Fixed.Cont

type Dim ((,,) a b) = N3
type Dim (T2 n a b) Source # 
Instance details

Defined in Data.Vector.Fixed.Unboxed

type Dim (T2 n a b) = Peano n
type Dim ((,,,) a b c) Source # 
Instance details

Defined in Data.Vector.Fixed.Cont

type Dim ((,,,) a b c) = N4
type Dim (T3 n a b c) Source # 
Instance details

Defined in Data.Vector.Fixed.Unboxed

type Dim (T3 n a b c) = Peano n
type Dim ((,,,,) a b c d) Source # 
Instance details

Defined in Data.Vector.Fixed.Cont

type Dim ((,,,,) a b c d) = N5
type Dim ((,,,,,) a b c d e) Source # 
Instance details

Defined in Data.Vector.Fixed.Cont

type Dim ((,,,,,) a b c d e) = N6
type Dim ((,,,,,,) a b c d e f) Source # 
Instance details

Defined in Data.Vector.Fixed.Cont

type Dim ((,,,,,,) a b c d e f) = N7

type Arity (n :: Nat) = ArityPeano (Peano n) Source #

Synonym for writing constrains using type level naturals.

class ArityPeano (n :: PeanoNum) Source #

Type class for defining and applying n-ary functions.

Instances

Instances details
ArityPeano 'Z Source # 
Instance details

Defined in Data.Vector.Fixed.Cont

Methods

accum :: (forall (k :: PeanoNum). t ('S k) -> a -> t k) -> (t 'Z -> b) -> t 'Z -> Fun 'Z a b Source #

accumPeano :: (forall (k :: PeanoNum). ArityPeano k => t ('S k) -> a -> t k) -> (t 'Z -> b) -> t 'Z -> Fun 'Z a b Source #

applyFun :: (forall (k :: PeanoNum). t ('S k) -> (a, t k)) -> t 'Z -> (ContVec 'Z a, t 'Z) Source #

applyFunM :: Applicative f => (forall (k :: PeanoNum). t ('S k) -> (f a, t k)) -> t 'Z -> (f (ContVec 'Z a), t 'Z) Source #

reducePeano :: (forall (k :: PeanoNum). t ('S k) -> t k) -> t 'Z -> t 'Z Source #

peanoToInt :: Proxy# 'Z -> Int Source #

dictionaryPred :: forall (k :: PeanoNum) r. 'Z ~ 'S k => Proxy# 'Z -> (ArityPeano k => r) -> r Source #

ArityPeano n => ArityPeano ('S n) Source # 
Instance details

Defined in Data.Vector.Fixed.Cont

Methods

accum :: (forall (k :: PeanoNum). t ('S k) -> a -> t k) -> (t 'Z -> b) -> t ('S n) -> Fun ('S n) a b Source #

accumPeano :: (forall (k :: PeanoNum). ArityPeano k => t ('S k) -> a -> t k) -> (t 'Z -> b) -> t ('S n) -> Fun ('S n) a b Source #

applyFun :: (forall (k :: PeanoNum). t ('S k) -> (a, t k)) -> t ('S n) -> (ContVec ('S n) a, t 'Z) Source #

applyFunM :: Applicative f => (forall (k :: PeanoNum). t ('S k) -> (f a, t k)) -> t ('S n) -> (f (ContVec ('S n) a), t 'Z) Source #

reducePeano :: (forall (k :: PeanoNum). t ('S k) -> t k) -> t ('S n) -> t 'Z Source #

peanoToInt :: Proxy# ('S n) -> Int Source #

dictionaryPred :: forall (k :: PeanoNum) r. 'S n ~ 'S k => Proxy# ('S n) -> (ArityPeano k => r) -> r Source #

newtype Fun (n :: PeanoNum) a b Source #

Newtype wrapper which is used to make Fn injective. It's a function which takes n parameters of type a and returns value of type b.

Constructors

Fun 

Fields

Instances

Instances details
ArityPeano n => Applicative (Fun n a) Source # 
Instance details

Defined in Data.Vector.Fixed.Cont

Methods

pure :: a0 -> Fun n a a0 #

(<*>) :: Fun n a (a0 -> b) -> Fun n a a0 -> Fun n a b #

liftA2 :: (a0 -> b -> c) -> Fun n a a0 -> Fun n a b -> Fun n a c #

(*>) :: Fun n a a0 -> Fun n a b -> Fun n a b #

(<*) :: Fun n a a0 -> Fun n a b -> Fun n a a0 #

ArityPeano n => Functor (Fun n a) Source # 
Instance details

Defined in Data.Vector.Fixed.Cont

Methods

fmap :: (a0 -> b) -> Fun n a a0 -> Fun n a b #

(<$) :: a0 -> Fun n a b -> Fun n a a0 #

ArityPeano n => Monad (Fun n a) Source #

Reader

Instance details

Defined in Data.Vector.Fixed.Cont

Methods

(>>=) :: Fun n a a0 -> (a0 -> Fun n a b) -> Fun n a b #

(>>) :: Fun n a a0 -> Fun n a b -> Fun n a b #

return :: a0 -> Fun n a a0 #

length :: ArityPeano (Dim v) => v a -> Int Source #

Length of vector. Function doesn't evaluate its argument.

Peano numbers

data PeanoNum Source #

Peano numbers. Since type level naturals don't support induction we have to convert type nats to Peano representation first and work with it,

Constructors

Z 
S PeanoNum 

type family Peano (n :: Nat) :: PeanoNum where ... Source #

Convert type level natural to Peano representation

Equations

Peano 0 = 'Z 
Peano n = 'S (Peano (n - 1)) 

type N1 = 'S 'Z Source #

type N2 = 'S N1 Source #

type N3 = 'S N2 Source #

type N4 = 'S N3 Source #

type N5 = 'S N4 Source #

type N6 = 'S N5 Source #

type N7 = 'S N6 Source #

type N8 = 'S N7 Source #

Construction and destructions

There are several ways to construct fixed vectors except using their constructor if it's available. For small ones it's possible to use functions mk1, mk2, etc.

>>> mk3 'a' 'b' 'c' :: (Char,Char,Char)
('a','b','c')

Another way is to use pattern synonyms for construction and inspection of vectors:

>>> V2 'a' 'b' :: (Char,Char)
('a','b')
>>> case ('a','b') of V2 a b -> [a,b]
"ab"

Last option is to use convert to convert between different vector types of same length. For example

v = convert (x,y,z)

This could be used in view patterns as well:

foo :: Vec3 Double -> Foo
foo (convert -> (x,y,z)) = ...

Pattern synonyms use this trick internally.

Constructors

mk0 :: (Vector v a, Dim v ~ 'Z) => v a Source #

mk1 :: (Vector v a, Dim v ~ N1) => a -> v a Source #

mk2 :: (Vector v a, Dim v ~ N2) => a -> a -> v a Source #

mk3 :: (Vector v a, Dim v ~ N3) => a -> a -> a -> v a Source #

mk4 :: (Vector v a, Dim v ~ N4) => a -> a -> a -> a -> v a Source #

mk5 :: (Vector v a, Dim v ~ N5) => a -> a -> a -> a -> a -> v a Source #

mk6 :: (Vector v a, Dim v ~ N6) => a -> a -> a -> a -> a -> a -> v a Source #

mk7 :: (Vector v a, Dim v ~ N7) => a -> a -> a -> a -> a -> a -> a -> v a Source #

mk8 :: (Vector v a, Dim v ~ N8) => a -> a -> a -> a -> a -> a -> a -> a -> v a Source #

mkN :: forall proxy v a. Vector v a => proxy (v a) -> Fn (Dim v) a (v a) Source #

N-ary constructor. Despite scary signature it's just N-ary function with additional type parameter which is used to fix type of vector being constructed. It could be used as:

v = mkN (Proxy :: Proxy (Int,Int,Int)) 1 2 3

or using TypeApplications syntax:

v = mkN (Proxy @(Int,Int,Int)) 1 2 3

or if type of v is fixed elsewhere

v = mkN [v] 1 2 3

Pattern synonyms

pattern V1 :: (Vector v a, Dim v ~ N1) => a -> v a Source #

pattern V2 :: (Vector v a, Dim v ~ N2) => a -> a -> v a Source #

pattern V3 :: (Vector v a, Dim v ~ N3) => a -> a -> a -> v a Source #

pattern V4 :: (Vector v a, Dim v ~ N4) => a -> a -> a -> a -> v a Source #

Functions

Creation

replicate :: Vector v a => a -> v a Source #

Replicate value n times.

Examples:

>>> import Data.Vector.Fixed.Boxed (Vec2)
>>> replicate 1 :: Vec2 Int
[1,1]
>>> replicate 2 :: (Double,Double,Double)
(2.0,2.0,2.0)
>>> import Data.Vector.Fixed.Boxed (Vec4)
>>> replicate "foo" :: Vec4 String
["foo","foo","foo","foo"]

replicateM :: (Vector v a, Applicative f) => f a -> f (v a) Source #

Execute monadic action for every element of vector.

Examples:

>>> import Data.Vector.Fixed.Boxed (Vec2,Vec3)
>>> replicateM (Just 3) :: Maybe (Vec3 Int)
Just [3,3,3]
>>> replicateM (putStrLn "Hi!") :: IO (Vec2 ())
Hi!
Hi!
[(),()]

generate :: Vector v a => (Int -> a) -> v a Source #

Generate vector from function which maps element's index to its value.

Examples:

>>> import Data.Vector.Fixed.Unboxed (Vec4)
>>> generate (^2) :: Vec4 Int
[0,1,4,9]

generateM :: (Applicative f, Vector v a) => (Int -> f a) -> f (v a) Source #

Generate vector from monadic function which maps element's index to its value.

unfoldr :: Vector v a => (b -> (a, b)) -> b -> v a Source #

Unfold vector.

basis :: (Vector v a, Num a) => Int -> v a Source #

Unit vector along Nth axis. If index is larger than vector dimensions returns zero vector.

Examples:

>>> import Data.Vector.Fixed.Boxed (Vec3)
>>> basis 0 :: Vec3 Int
[1,0,0]
>>> basis 1 :: Vec3 Int
[0,1,0]
>>> basis 3 :: Vec3 Int
[0,0,0]

Transformations

head :: forall v a (k :: PeanoNum). (Vector v a, Dim v ~ 'S k) => v a -> a Source #

First element of vector.

Examples:

>>> import Data.Vector.Fixed.Boxed (Vec3)
>>> let x = mk3 1 2 3 :: Vec3 Int
>>> head x
1

tail :: (Vector v a, Vector w a, Dim v ~ 'S (Dim w)) => v a -> w a Source #

Tail of vector.

Examples:

>>> import Data.Complex
>>> tail (1,2,3) :: Complex Double
2.0 :+ 3.0

cons :: (Vector v a, Vector w a, Dim w ~ 'S (Dim v)) => a -> v a -> w a Source #

Cons element to the vector

snoc :: (Vector v a, Vector w a, Dim w ~ 'S (Dim v)) => a -> v a -> w a Source #

Append element to the vector

concat :: (Vector v a, Vector u a, Vector w a, Add (Dim v) (Dim u) ~ Dim w) => v a -> u a -> w a Source #

reverse :: Vector v a => v a -> v a Source #

Reverse order of elements in the vector

Indexing & lenses

class Index (k :: PeanoNum) (n :: PeanoNum) Source #

Type class for indexing of vector of length n with statically known index k

Minimal complete definition

getF, putF, lensF

Instances

Instances details
ArityPeano n => Index 'Z ('S n) Source # 
Instance details

Defined in Data.Vector.Fixed.Cont

Methods

getF :: Proxy# 'Z -> Fun ('S n) a a Source #

putF :: Proxy# 'Z -> a -> Fun ('S n) a r -> Fun ('S n) a r Source #

lensF :: Functor f => Proxy# 'Z -> (a -> f a) -> Fun ('S n) a r -> Fun ('S n) a (f r) Source #

Index k n => Index ('S k) ('S n) Source # 
Instance details

Defined in Data.Vector.Fixed.Cont

Methods

getF :: Proxy# ('S k) -> Fun ('S n) a a Source #

putF :: Proxy# ('S k) -> a -> Fun ('S n) a r -> Fun ('S n) a r Source #

lensF :: Functor f => Proxy# ('S k) -> (a -> f a) -> Fun ('S n) a r -> Fun ('S n) a (f r) Source #

(!) :: Vector v a => v a -> Int -> a Source #

Retrieve vector's element at index. Generic implementation is O(n) but more efficient one is used when possible.

index :: forall (k :: Nat) v a proxy. (Vector v a, Index (Peano k) (Dim v)) => v a -> proxy k -> a Source #

Get element from vector at statically known index

set :: forall (k :: Nat) v a proxy. (Vector v a, Index (Peano k) (Dim v)) => proxy k -> a -> v a -> v a Source #

Set n'th element in the vector

element :: (Vector v a, Functor f) => Int -> (a -> f a) -> v a -> f (v a) Source #

Twan van Laarhoven's lens for element of vector

elementTy :: forall (k :: Nat) v a f proxy. (Vector v a, Index (Peano k) (Dim v), Functor f) => proxy k -> (a -> f a) -> v a -> f (v a) Source #

Twan van Laarhoven's lens for element of vector with statically known index.

Maps

map :: (Vector v a, Vector v b) => (a -> b) -> v a -> v b Source #

Map over vector

mapM :: (Vector v a, Vector v b, Applicative f) => (a -> f b) -> v a -> f (v b) Source #

Effectful map over vector.

mapM_ :: (Vector v a, Applicative f) => (a -> f b) -> v a -> f () Source #

Apply monadic action to each element of vector and ignore result.

imap :: (Vector v a, Vector v b) => (Int -> a -> b) -> v a -> v b Source #

Apply function to every element of the vector and its index.

imapM :: (Vector v a, Vector v b, Applicative f) => (Int -> a -> f b) -> v a -> f (v b) Source #

Apply monadic function to every element of the vector and its index.

imapM_ :: (Vector v a, Applicative f) => (Int -> a -> f b) -> v a -> f () Source #

Apply monadic function to every element of the vector and its index and discard result.

scanl :: (Vector v a, Vector w b, Dim w ~ 'S (Dim v)) => (b -> a -> b) -> b -> v a -> w b Source #

Left scan over vector

scanl1 :: Vector v a => (a -> a -> a) -> v a -> v a Source #

Left scan over vector

sequence :: (Vector v a, Vector v (f a), Applicative f) => v (f a) -> f (v a) Source #

Evaluate every action in the vector from left to right.

sequence_ :: (Vector v (f a), Applicative f) => v (f a) -> f () Source #

Evaluate every action in the vector from left to right and ignore result

traverse :: (Vector v a, Vector v b, Applicative f) => (a -> f b) -> v a -> f (v b) Source #

Analog of traverse from Traversable.

distribute :: (Vector v a, Vector v (f a), Functor f) => f (v a) -> v (f a) Source #

collect :: (Vector v a, Vector v b, Vector v (f b), Functor f) => (a -> v b) -> f a -> v (f b) Source #

Folds

foldl :: Vector v a => (b -> a -> b) -> b -> v a -> b Source #

Left fold over vector

foldl' :: Vector v a => (b -> a -> b) -> b -> v a -> b Source #

Strict left fold over vector

foldr :: Vector v a => (a -> b -> b) -> b -> v a -> b Source #

Right fold over vector

foldl1 :: forall v a (k :: PeanoNum). (Vector v a, Dim v ~ 'S k) => (a -> a -> a) -> v a -> a Source #

Left fold over vector

fold :: (Vector v m, Monoid m) => v m -> m Source #

Combine the elements of a structure using a monoid. Similar to fold

foldMap :: (Vector v a, Monoid m) => (a -> m) -> v a -> m Source #

Map each element of the structure to a monoid, and combine the results. Similar to foldMap

ifoldl :: Vector v a => (b -> Int -> a -> b) -> b -> v a -> b Source #

Left fold over vector. Function is applied to each element and its index.

ifoldr :: Vector v a => (Int -> a -> b -> b) -> b -> v a -> b Source #

Right fold over vector

foldM :: (Vector v a, Monad m) => (b -> a -> m b) -> b -> v a -> m b Source #

Monadic fold over vector.

ifoldM :: (Vector v a, Monad m) => (b -> Int -> a -> m b) -> b -> v a -> m b Source #

Left monadic fold over vector. Function is applied to each element and its index.

Special folds

sum :: (Vector v a, Num a) => v a -> a Source #

Sum all elements in the vector.

maximum :: forall v a (k :: PeanoNum). (Vector v a, Dim v ~ 'S k, Ord a) => v a -> a Source #

Maximal element of vector.

Examples:

>>> import Data.Vector.Fixed.Boxed (Vec3)
>>> let x = mk3 1 2 3 :: Vec3 Int
>>> maximum x
3

minimum :: forall v a (k :: PeanoNum). (Vector v a, Dim v ~ 'S k, Ord a) => v a -> a Source #

Minimal element of vector.

Examples:

>>> import Data.Vector.Fixed.Boxed (Vec3)
>>> let x = mk3 1 2 3 :: Vec3 Int
>>> minimum x
1

and :: Vector v Bool => v Bool -> Bool Source #

Conjunction of all elements of a vector.

or :: Vector v Bool => v Bool -> Bool Source #

Disjunction of all elements of a vector.

all :: Vector v a => (a -> Bool) -> v a -> Bool Source #

Determines whether all elements of vector satisfy predicate.

any :: Vector v a => (a -> Bool) -> v a -> Bool Source #

Determines whether any of element of vector satisfy predicate.

find :: Vector v a => (a -> Bool) -> v a -> Maybe a Source #

The find function takes a predicate and a vector and returns the leftmost element of the vector matching the predicate, or Nothing if there is no such element.

Zips

zipWith :: (Vector v a, Vector v b, Vector v c) => (a -> b -> c) -> v a -> v b -> v c Source #

Zip two vector together using function.

Examples:

>>> import Data.Vector.Fixed.Boxed (Vec3)
>>> let b0 = basis 0 :: Vec3 Int
>>> let b1 = basis 1 :: Vec3 Int
>>> let b2 = basis 2 :: Vec3 Int
>>> let vplus x y = zipWith (+) x y
>>> vplus b0 b1
[1,1,0]
>>> vplus b0 b2
[1,0,1]
>>> vplus b1 b2
[0,1,1]

zipWith3 :: (Vector v a, Vector v b, Vector v c, Vector v d) => (a -> b -> c -> d) -> v a -> v b -> v c -> v d Source #

Zip three vector together

zipWithM :: (Vector v a, Vector v b, Vector v c, Applicative f) => (a -> b -> f c) -> v a -> v b -> f (v c) Source #

Zip two vector together using monadic function.

zipWithM_ :: (Vector v a, Vector v b, Applicative f) => (a -> b -> f c) -> v a -> v b -> f () Source #

Zip two vector elementwise using monadic function and discard result

izipWith :: (Vector v a, Vector v b, Vector v c) => (Int -> a -> b -> c) -> v a -> v b -> v c Source #

Zip two vector together using function which takes element index as well.

izipWith3 :: (Vector v a, Vector v b, Vector v c, Vector v d) => (Int -> a -> b -> c -> d) -> v a -> v b -> v c -> v d Source #

Zip three vector together

izipWithM :: (Vector v a, Vector v b, Vector v c, Applicative f) => (Int -> a -> b -> f c) -> v a -> v b -> f (v c) Source #

Zip two vector together using monadic function which takes element index as well..

izipWithM_ :: (Vector v a, Vector v b, Vector v c, Applicative f, Vector v (f c)) => (Int -> a -> b -> f c) -> v a -> v b -> f () Source #

Zip two vector elementwise using monadic function and discard result

Special zips

eq :: (Vector v a, Eq a) => v a -> v a -> Bool Source #

Test two vectors for equality.

Examples:

>>> import Data.Vector.Fixed.Boxed (Vec2)
>>> let v0 = basis 0 :: Vec2 Int
>>> let v1 = basis 1 :: Vec2 Int
>>> v0 `eq` v0
True
>>> v0 `eq` v1
False

ord :: (Vector v a, Ord a) => v a -> v a -> Ordering Source #

Lexicographic ordering of two vectors.

Conversion

convert :: (Vector v a, Vector w a, Dim v ~ Dim w) => v a -> w a Source #

Convert between different vector types

toList :: Vector v a => v a -> [a] Source #

Convert vector to the list

fromList :: Vector v a => [a] -> v a Source #

Create vector form list. Will throw error if list is shorter than resulting vector.

fromList' :: Vector v a => [a] -> v a Source #

Create vector form list. Will throw error if list has different length from resulting vector.

fromListM :: Vector v a => [a] -> Maybe (v a) Source #

Create vector form list. Will return Nothing if list has different length from resulting vector.

fromFoldable :: (Vector v a, Foldable f) => f a -> Maybe (v a) Source #

Create vector from Foldable data type. Will return Nothing if data type different number of elements that resulting vector.

Data types

newtype VecList (n :: Nat) a Source #

Type-based vector with statically known length parametrized by GHC's type naturals

Constructors

VecList (VecPeano (Peano n) a) 

Instances

Instances details
Arity n => Foldable (VecList n) Source # 
Instance details

Defined in Data.Vector.Fixed

Methods

fold :: Monoid m => VecList n m -> m #

foldMap :: Monoid m => (a -> m) -> VecList n a -> m #

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

foldr :: (a -> b -> b) -> b -> VecList n a -> b #

foldr' :: (a -> b -> b) -> b -> VecList n a -> b #

foldl :: (b -> a -> b) -> b -> VecList n a -> b #

foldl' :: (b -> a -> b) -> b -> VecList n a -> b #

foldr1 :: (a -> a -> a) -> VecList n a -> a #

foldl1 :: (a -> a -> a) -> VecList n a -> a #

toList :: VecList n a -> [a] #

null :: VecList n a -> Bool #

length :: VecList n a -> Int #

elem :: Eq a => a -> VecList n a -> Bool #

maximum :: Ord a => VecList n a -> a #

minimum :: Ord a => VecList n a -> a #

sum :: Num a => VecList n a -> a #

product :: Num a => VecList n a -> a #

Arity n => Traversable (VecList n) Source # 
Instance details

Defined in Data.Vector.Fixed

Methods

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

sequenceA :: Applicative f => VecList n (f a) -> f (VecList n a) #

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

sequence :: Monad m => VecList n (m a) -> m (VecList n a) #

Arity n => Applicative (VecList n) Source # 
Instance details

Defined in Data.Vector.Fixed

Methods

pure :: a -> VecList n a #

(<*>) :: VecList n (a -> b) -> VecList n a -> VecList n b #

liftA2 :: (a -> b -> c) -> VecList n a -> VecList n b -> VecList n c #

(*>) :: VecList n a -> VecList n b -> VecList n b #

(<*) :: VecList n a -> VecList n b -> VecList n a #

Arity n => Functor (VecList n) Source # 
Instance details

Defined in Data.Vector.Fixed

Methods

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

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

Arity n => Vector (VecList n) a Source # 
Instance details

Defined in Data.Vector.Fixed

Methods

construct :: Fun (Dim (VecList n)) a (VecList n a) Source #

inspect :: VecList n a -> Fun (Dim (VecList n)) a b -> b Source #

basicIndex :: VecList n a -> Int -> a Source #

(Arity n, Storable a) => Storable (VecList n a) Source # 
Instance details

Defined in Data.Vector.Fixed

Methods

sizeOf :: VecList n a -> Int #

alignment :: VecList n a -> Int #

peekElemOff :: Ptr (VecList n a) -> Int -> IO (VecList n a) #

pokeElemOff :: Ptr (VecList n a) -> Int -> VecList n a -> IO () #

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

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

peek :: Ptr (VecList n a) -> IO (VecList n a) #

poke :: Ptr (VecList n a) -> VecList n a -> IO () #

(Arity n, Monoid a) => Monoid (VecList n a) Source # 
Instance details

Defined in Data.Vector.Fixed

Methods

mempty :: VecList n a #

mappend :: VecList n a -> VecList n a -> VecList n a #

mconcat :: [VecList n a] -> VecList n a #

(Arity n, Semigroup a) => Semigroup (VecList n a) Source # 
Instance details

Defined in Data.Vector.Fixed

Methods

(<>) :: VecList n a -> VecList n a -> VecList n a #

sconcat :: NonEmpty (VecList n a) -> VecList n a #

stimes :: Integral b => b -> VecList n a -> VecList n a #

(Arity n, Show a) => Show (VecList n a) Source # 
Instance details

Defined in Data.Vector.Fixed

Methods

showsPrec :: Int -> VecList n a -> ShowS #

show :: VecList n a -> String #

showList :: [VecList n a] -> ShowS #

(Arity n, NFData a) => NFData (VecList n a) Source # 
Instance details

Defined in Data.Vector.Fixed

Methods

rnf :: VecList n a -> () #

(Arity n, Eq a) => Eq (VecList n a) Source # 
Instance details

Defined in Data.Vector.Fixed

Methods

(==) :: VecList n a -> VecList n a -> Bool #

(/=) :: VecList n a -> VecList n a -> Bool #

(Arity n, Ord a) => Ord (VecList n a) Source # 
Instance details

Defined in Data.Vector.Fixed

Methods

compare :: VecList n a -> VecList n a -> Ordering #

(<) :: VecList n a -> VecList n a -> Bool #

(<=) :: VecList n a -> VecList n a -> Bool #

(>) :: VecList n a -> VecList n a -> Bool #

(>=) :: VecList n a -> VecList n a -> Bool #

max :: VecList n a -> VecList n a -> VecList n a #

min :: VecList n a -> VecList n a -> VecList n a #

type Dim (VecList n) Source # 
Instance details

Defined in Data.Vector.Fixed

type Dim (VecList n) = Peano n

data VecPeano (n :: PeanoNum) a where Source #

Standard GADT-based vector with statically known length parametrized by Peano numbers.

Constructors

Nil :: forall a. VecPeano 'Z a 
Cons :: forall a (n1 :: PeanoNum). a -> VecPeano n1 a -> VecPeano ('S n1) a 

Instances

Instances details
ArityPeano n => Foldable (VecPeano n) Source # 
Instance details

Defined in Data.Vector.Fixed

Methods

fold :: Monoid m => VecPeano n m -> m #

foldMap :: Monoid m => (a -> m) -> VecPeano n a -> m #

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

foldr :: (a -> b -> b) -> b -> VecPeano n a -> b #

foldr' :: (a -> b -> b) -> b -> VecPeano n a -> b #

foldl :: (b -> a -> b) -> b -> VecPeano n a -> b #

foldl' :: (b -> a -> b) -> b -> VecPeano n a -> b #

foldr1 :: (a -> a -> a) -> VecPeano n a -> a #

foldl1 :: (a -> a -> a) -> VecPeano n a -> a #

toList :: VecPeano n a -> [a] #

null :: VecPeano n a -> Bool #

length :: VecPeano n a -> Int #

elem :: Eq a => a -> VecPeano n a -> Bool #

maximum :: Ord a => VecPeano n a -> a #

minimum :: Ord a => VecPeano n a -> a #

sum :: Num a => VecPeano n a -> a #

product :: Num a => VecPeano n a -> a #

ArityPeano n => Traversable (VecPeano n) Source # 
Instance details

Defined in Data.Vector.Fixed

Methods

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

sequenceA :: Applicative f => VecPeano n (f a) -> f (VecPeano n a) #

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

sequence :: Monad m => VecPeano n (m a) -> m (VecPeano n a) #

ArityPeano n => Applicative (VecPeano n) Source # 
Instance details

Defined in Data.Vector.Fixed

Methods

pure :: a -> VecPeano n a #

(<*>) :: VecPeano n (a -> b) -> VecPeano n a -> VecPeano n b #

liftA2 :: (a -> b -> c) -> VecPeano n a -> VecPeano n b -> VecPeano n c #

(*>) :: VecPeano n a -> VecPeano n b -> VecPeano n b #

(<*) :: VecPeano n a -> VecPeano n b -> VecPeano n a #

ArityPeano n => Functor (VecPeano n) Source # 
Instance details

Defined in Data.Vector.Fixed

Methods

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

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

ArityPeano n => Vector (VecPeano n) a Source # 
Instance details

Defined in Data.Vector.Fixed

Methods

construct :: Fun (Dim (VecPeano n)) a (VecPeano n a) Source #

inspect :: VecPeano n a -> Fun (Dim (VecPeano n)) a b -> b Source #

basicIndex :: VecPeano n a -> Int -> a Source #

(ArityPeano n, Storable a) => Storable (VecPeano n a) Source # 
Instance details

Defined in Data.Vector.Fixed

Methods

sizeOf :: VecPeano n a -> Int #

alignment :: VecPeano n a -> Int #

peekElemOff :: Ptr (VecPeano n a) -> Int -> IO (VecPeano n a) #

pokeElemOff :: Ptr (VecPeano n a) -> Int -> VecPeano n a -> IO () #

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

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

peek :: Ptr (VecPeano n a) -> IO (VecPeano n a) #

poke :: Ptr (VecPeano n a) -> VecPeano n a -> IO () #

(ArityPeano n, Monoid a) => Monoid (VecPeano n a) Source # 
Instance details

Defined in Data.Vector.Fixed

Methods

mempty :: VecPeano n a #

mappend :: VecPeano n a -> VecPeano n a -> VecPeano n a #

mconcat :: [VecPeano n a] -> VecPeano n a #

(ArityPeano n, Semigroup a) => Semigroup (VecPeano n a) Source # 
Instance details

Defined in Data.Vector.Fixed

Methods

(<>) :: VecPeano n a -> VecPeano n a -> VecPeano n a #

sconcat :: NonEmpty (VecPeano n a) -> VecPeano n a #

stimes :: Integral b => b -> VecPeano n a -> VecPeano n a #

(ArityPeano n, Show a) => Show (VecPeano n a) Source # 
Instance details

Defined in Data.Vector.Fixed

Methods

showsPrec :: Int -> VecPeano n a -> ShowS #

show :: VecPeano n a -> String #

showList :: [VecPeano n a] -> ShowS #

(ArityPeano n, NFData a) => NFData (VecPeano n a) Source # 
Instance details

Defined in Data.Vector.Fixed

Methods

rnf :: VecPeano n a -> () #

(ArityPeano n, Eq a) => Eq (VecPeano n a) Source # 
Instance details

Defined in Data.Vector.Fixed

Methods

(==) :: VecPeano n a -> VecPeano n a -> Bool #

(/=) :: VecPeano n a -> VecPeano n a -> Bool #

(ArityPeano n, Ord a) => Ord (VecPeano n a) Source # 
Instance details

Defined in Data.Vector.Fixed

Methods

compare :: VecPeano n a -> VecPeano n a -> Ordering #

(<) :: VecPeano n a -> VecPeano n a -> Bool #

(<=) :: VecPeano n a -> VecPeano n a -> Bool #

(>) :: VecPeano n a -> VecPeano n a -> Bool #

(>=) :: VecPeano n a -> VecPeano n a -> Bool #

max :: VecPeano n a -> VecPeano n a -> VecPeano n a #

min :: VecPeano n a -> VecPeano n a -> VecPeano n a #

type Dim (VecPeano n) Source # 
Instance details

Defined in Data.Vector.Fixed

type Dim (VecPeano n) = n

newtype Only a Source #

Single-element tuple.

Constructors

Only a 

Instances

Instances details
Foldable Only Source # 
Instance details

Defined in Data.Vector.Fixed

Methods

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

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

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

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

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

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

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

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

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

toList :: Only a -> [a] #

null :: Only a -> Bool #

length :: Only a -> Int #

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

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

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

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

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

Traversable Only Source # 
Instance details

Defined in Data.Vector.Fixed

Methods

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

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

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

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

Functor Only Source # 
Instance details

Defined in Data.Vector.Fixed

Methods

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

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

Vector Only a Source # 
Instance details

Defined in Data.Vector.Fixed

Methods

construct :: Fun (Dim Only) a (Only a) Source #

inspect :: Only a -> Fun (Dim Only) a b -> b Source #

basicIndex :: Only a -> Int -> a Source #

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

Defined in Data.Vector.Fixed

Methods

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

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

toConstr :: Only a -> Constr #

dataTypeOf :: Only a -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Defined in Data.Vector.Fixed

Methods

sizeOf :: Only a -> Int #

alignment :: Only a -> Int #

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

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

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

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

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

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

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

Defined in Data.Vector.Fixed

Methods

mempty :: Only a #

mappend :: Only a -> Only a -> Only a #

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

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

Defined in Data.Vector.Fixed

Methods

(<>) :: Only a -> Only a -> Only a #

sconcat :: NonEmpty (Only a) -> Only a #

stimes :: Integral b => b -> Only a -> Only a #

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

Defined in Data.Vector.Fixed

Methods

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

show :: Only a -> String #

showList :: [Only a] -> ShowS #

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

Defined in Data.Vector.Fixed

Methods

rnf :: Only a -> () #

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

Defined in Data.Vector.Fixed

Methods

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

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

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

Defined in Data.Vector.Fixed

Methods

compare :: Only a -> Only a -> Ordering #

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

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

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

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

max :: Only a -> Only a -> Only a #

min :: Only a -> Only a -> Only a #

type Dim Only Source # 
Instance details

Defined in Data.Vector.Fixed

type Dim Only = N1

data Empty (a :: k) Source #

Empty tuple.

Constructors

Empty 

Instances

Instances details
Foldable (Empty :: Type -> Type) Source # 
Instance details

Defined in Data.Vector.Fixed

Methods

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

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

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

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

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

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

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

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

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

toList :: Empty a -> [a] #

null :: Empty a -> Bool #

length :: Empty a -> Int #

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

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

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

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

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

Traversable (Empty :: Type -> Type) Source # 
Instance details

Defined in Data.Vector.Fixed

Methods

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

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

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

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

Functor (Empty :: Type -> Type) Source # 
Instance details

Defined in Data.Vector.Fixed

Methods

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

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

Vector (Empty :: Type -> Type) a Source # 
Instance details

Defined in Data.Vector.Fixed

Methods

construct :: Fun (Dim (Empty :: Type -> Type)) a (Empty a) Source #

inspect :: Empty a -> Fun (Dim (Empty :: Type -> Type)) a b -> b Source #

basicIndex :: Empty a -> Int -> a Source #

(Typeable a, Typeable k) => Data (Empty a) Source # 
Instance details

Defined in Data.Vector.Fixed

Methods

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

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

toConstr :: Empty a -> Constr #

dataTypeOf :: Empty a -> DataType #

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

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

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

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

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

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

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

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

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

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

Show (Empty a) Source # 
Instance details

Defined in Data.Vector.Fixed

Methods

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

show :: Empty a -> String #

showList :: [Empty a] -> ShowS #

NFData (Empty a) Source # 
Instance details

Defined in Data.Vector.Fixed

Methods

rnf :: Empty a -> () #

Eq (Empty a) Source # 
Instance details

Defined in Data.Vector.Fixed

Methods

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

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

Ord (Empty a) Source # 
Instance details

Defined in Data.Vector.Fixed

Methods

compare :: Empty a -> Empty a -> Ordering #

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

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

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

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

max :: Empty a -> Empty a -> Empty a #

min :: Empty a -> Empty a -> Empty a #

type Dim (Empty :: Type -> Type) Source # 
Instance details

Defined in Data.Vector.Fixed

type Dim (Empty :: Type -> Type) = 'Z

Tuple synonyms

type Tuple2 a = (a, a) Source #

type Tuple3 a = (a, a, a) Source #

type Tuple4 a = (a, a, a, a) Source #

type Tuple5 a = (a, a, a, a, a) Source #

Continuation-based vectors

data ContVec (n :: PeanoNum) a Source #

Vector represented as continuation. Alternative wording: it's Church encoded N-element vector.

Instances

Instances details
ArityPeano n => Foldable (ContVec n) Source # 
Instance details

Defined in Data.Vector.Fixed.Cont

Methods

fold :: Monoid m => ContVec n m -> m #

foldMap :: Monoid m => (a -> m) -> ContVec n a -> m #

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

foldr :: (a -> b -> b) -> b -> ContVec n a -> b #

foldr' :: (a -> b -> b) -> b -> ContVec n a -> b #

foldl :: (b -> a -> b) -> b -> ContVec n a -> b #

foldl' :: (b -> a -> b) -> b -> ContVec n a -> b #

foldr1 :: (a -> a -> a) -> ContVec n a -> a #

foldl1 :: (a -> a -> a) -> ContVec n a -> a #

toList :: ContVec n a -> [a] #

null :: ContVec n a -> Bool #

length :: ContVec n a -> Int #

elem :: Eq a => a -> ContVec n a -> Bool #

maximum :: Ord a => ContVec n a -> a #

minimum :: Ord a => ContVec n a -> a #

sum :: Num a => ContVec n a -> a #

product :: Num a => ContVec n a -> a #

ArityPeano n => Traversable (ContVec n) Source # 
Instance details

Defined in Data.Vector.Fixed.Cont

Methods

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

sequenceA :: Applicative f => ContVec n (f a) -> f (ContVec n a) #

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

sequence :: Monad m => ContVec n (m a) -> m (ContVec n a) #

ArityPeano n => Applicative (ContVec n) Source # 
Instance details

Defined in Data.Vector.Fixed.Cont

Methods

pure :: a -> ContVec n a #

(<*>) :: ContVec n (a -> b) -> ContVec n a -> ContVec n b #

liftA2 :: (a -> b -> c) -> ContVec n a -> ContVec n b -> ContVec n c #

(*>) :: ContVec n a -> ContVec n b -> ContVec n b #

(<*) :: ContVec n a -> ContVec n b -> ContVec n a #

ArityPeano n => Functor (ContVec n) Source # 
Instance details

Defined in Data.Vector.Fixed.Cont

Methods

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

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

ArityPeano n => Vector (ContVec n) a Source # 
Instance details

Defined in Data.Vector.Fixed.Cont

Methods

construct :: Fun (Dim (ContVec n)) a (ContVec n a) Source #

inspect :: ContVec n a -> Fun (Dim (ContVec n)) a b -> b Source #

basicIndex :: ContVec n a -> Int -> a Source #

(ArityPeano n, Monoid a) => Monoid (ContVec n a) Source # 
Instance details

Defined in Data.Vector.Fixed.Cont

Methods

mempty :: ContVec n a #

mappend :: ContVec n a -> ContVec n a -> ContVec n a #

mconcat :: [ContVec n a] -> ContVec n a #

(ArityPeano n, Semigroup a) => Semigroup (ContVec n a) Source # 
Instance details

Defined in Data.Vector.Fixed.Cont

Methods

(<>) :: ContVec n a -> ContVec n a -> ContVec n a #

sconcat :: NonEmpty (ContVec n a) -> ContVec n a #

stimes :: Integral b => b -> ContVec n a -> ContVec n a #

(Eq a, ArityPeano n) => Eq (ContVec n a) Source # 
Instance details

Defined in Data.Vector.Fixed.Cont

Methods

(==) :: ContVec n a -> ContVec n a -> Bool #

(/=) :: ContVec n a -> ContVec n a -> Bool #

(Ord a, ArityPeano n) => Ord (ContVec n a) Source # 
Instance details

Defined in Data.Vector.Fixed.Cont

Methods

compare :: ContVec n a -> ContVec n a -> Ordering #

(<) :: ContVec n a -> ContVec n a -> Bool #

(<=) :: ContVec n a -> ContVec n a -> Bool #

(>) :: ContVec n a -> ContVec n a -> Bool #

(>=) :: ContVec n a -> ContVec n a -> Bool #

max :: ContVec n a -> ContVec n a -> ContVec n a #

min :: ContVec n a -> ContVec n a -> ContVec n a #

type Dim (ContVec n) Source # 
Instance details

Defined in Data.Vector.Fixed.Cont

type Dim (ContVec n) = n

empty :: ContVec 'Z a Source #

Create empty vector.

vector :: Vector v a => ContVec (Dim v) a -> v a Source #

Convert continuation to the vector.

cvec :: Vector v a => v a -> ContVec (Dim v) a Source #

Convert regular vector to continuation based one.

Instance deriving

newtype ViaFixed (v :: k -> Type) (a :: k) Source #

Newtype for deriving instance for data types which has instance of Vector. It supports Eq, Ord, Semigroup, Monoid, Storable, NFData, Functor, Applicative, Foldable.

Constructors

ViaFixed (v a) 

Instances

Instances details
(forall a. Vector v a) => Foldable (ViaFixed v) Source # 
Instance details

Defined in Data.Vector.Fixed

Methods

fold :: Monoid m => ViaFixed v m -> m #

foldMap :: Monoid m => (a -> m) -> ViaFixed v a -> m #

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

foldr :: (a -> b -> b) -> b -> ViaFixed v a -> b #

foldr' :: (a -> b -> b) -> b -> ViaFixed v a -> b #

foldl :: (b -> a -> b) -> b -> ViaFixed v a -> b #

foldl' :: (b -> a -> b) -> b -> ViaFixed v a -> b #

foldr1 :: (a -> a -> a) -> ViaFixed v a -> a #

foldl1 :: (a -> a -> a) -> ViaFixed v a -> a #

toList :: ViaFixed v a -> [a] #

null :: ViaFixed v a -> Bool #

length :: ViaFixed v a -> Int #

elem :: Eq a => a -> ViaFixed v a -> Bool #

maximum :: Ord a => ViaFixed v a -> a #

minimum :: Ord a => ViaFixed v a -> a #

sum :: Num a => ViaFixed v a -> a #

product :: Num a => ViaFixed v a -> a #

(forall a. Vector v a) => Applicative (ViaFixed v) Source # 
Instance details

Defined in Data.Vector.Fixed

Methods

pure :: a -> ViaFixed v a #

(<*>) :: ViaFixed v (a -> b) -> ViaFixed v a -> ViaFixed v b #

liftA2 :: (a -> b -> c) -> ViaFixed v a -> ViaFixed v b -> ViaFixed v c #

(*>) :: ViaFixed v a -> ViaFixed v b -> ViaFixed v b #

(<*) :: ViaFixed v a -> ViaFixed v b -> ViaFixed v a #

(forall a. Vector v a) => Functor (ViaFixed v) Source # 
Instance details

Defined in Data.Vector.Fixed

Methods

fmap :: (a -> b) -> ViaFixed v a -> ViaFixed v b #

(<$) :: a -> ViaFixed v b -> ViaFixed v a #

Vector v a => Vector (ViaFixed v) a Source # 
Instance details

Defined in Data.Vector.Fixed

Methods

construct :: Fun (Dim (ViaFixed v)) a (ViaFixed v a) Source #

inspect :: ViaFixed v a -> Fun (Dim (ViaFixed v)) a b -> b Source #

basicIndex :: ViaFixed v a -> Int -> a Source #

(Vector v a, Storable a) => Storable (ViaFixed v a) Source # 
Instance details

Defined in Data.Vector.Fixed

Methods

sizeOf :: ViaFixed v a -> Int #

alignment :: ViaFixed v a -> Int #

peekElemOff :: Ptr (ViaFixed v a) -> Int -> IO (ViaFixed v a) #

pokeElemOff :: Ptr (ViaFixed v a) -> Int -> ViaFixed v a -> IO () #

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

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

peek :: Ptr (ViaFixed v a) -> IO (ViaFixed v a) #

poke :: Ptr (ViaFixed v a) -> ViaFixed v a -> IO () #

(Vector v a, Monoid a) => Monoid (ViaFixed v a) Source # 
Instance details

Defined in Data.Vector.Fixed

Methods

mempty :: ViaFixed v a #

mappend :: ViaFixed v a -> ViaFixed v a -> ViaFixed v a #

mconcat :: [ViaFixed v a] -> ViaFixed v a #

(Vector v a, Semigroup a) => Semigroup (ViaFixed v a) Source # 
Instance details

Defined in Data.Vector.Fixed

Methods

(<>) :: ViaFixed v a -> ViaFixed v a -> ViaFixed v a #

sconcat :: NonEmpty (ViaFixed v a) -> ViaFixed v a #

stimes :: Integral b => b -> ViaFixed v a -> ViaFixed v a #

(Vector v a, Show a) => Show (ViaFixed v a) Source # 
Instance details

Defined in Data.Vector.Fixed

Methods

showsPrec :: Int -> ViaFixed v a -> ShowS #

show :: ViaFixed v a -> String #

showList :: [ViaFixed v a] -> ShowS #

(Vector v a, NFData a) => NFData (ViaFixed v a) Source # 
Instance details

Defined in Data.Vector.Fixed

Methods

rnf :: ViaFixed v a -> () #

(Vector v a, Eq a) => Eq (ViaFixed v a) Source # 
Instance details

Defined in Data.Vector.Fixed

Methods

(==) :: ViaFixed v a -> ViaFixed v a -> Bool #

(/=) :: ViaFixed v a -> ViaFixed v a -> Bool #

(Vector v a, Ord a) => Ord (ViaFixed v a) Source # 
Instance details

Defined in Data.Vector.Fixed

Methods

compare :: ViaFixed v a -> ViaFixed v a -> Ordering #

(<) :: ViaFixed v a -> ViaFixed v a -> Bool #

(<=) :: ViaFixed v a -> ViaFixed v a -> Bool #

(>) :: ViaFixed v a -> ViaFixed v a -> Bool #

(>=) :: ViaFixed v a -> ViaFixed v a -> Bool #

max :: ViaFixed v a -> ViaFixed v a -> ViaFixed v a #

min :: ViaFixed v a -> ViaFixed v a -> ViaFixed v a #

type Dim (ViaFixed v) Source # 
Instance details

Defined in Data.Vector.Fixed

type Dim (ViaFixed v) = Dim v

Storable

Default implementation of methods for Storable type class assumes that individual elements of vector are stored as N-element array.

defaultAlignemnt :: Storable a => v a -> Int Source #

Default implementation of alignment for Storable type class for fixed vectors.

defaultSizeOf :: (Storable a, Vector v a) => v a -> Int Source #

Default implementation of sizeOf for Storable type class for fixed vectors

defaultPeek :: (Storable a, Vector v a) => Ptr (v a) -> IO (v a) Source #

Default implementation of peek for Storable type class for fixed vector

defaultPoke :: (Storable a, Vector v a) => Ptr (v a) -> v a -> IO () Source #

Default implementation of poke for Storable type class for fixed vector

NFData

defaultRnf :: (NFData a, Vector v a) => v a -> () Source #

Default implementation of rnf from NFData type class

Deprecated functions

sequenceA :: (Vector v a, Vector v (f a), Applicative f) => v (f a) -> f (v a) Source #

Deprecated: Use sequence instead

Analog of sequenceA from Traversable.