Copyright | (c) Christopher Chalmers |
---|---|
License | BSD3 |
Maintainer | Christopher Chalmers |
Stability | provisional |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
This module provides a large subset of the full functionality of "dense" without exporting names that conflict with names in prelude, so it can often be imported unqualified. It also includes reexported classes and data types from other modules. However it does not contain much functions necessary to construct arrays, for that see Data.Dense.Generic or one of the type specific modules intended to be imported qualified. Typical imports for shaped will look like this:
import Data.Dense import qualified Data.Dense.Unboxed as U
For boxed-specific arrays (a la Data.Vector) see Data.Dense.Boxed.
Synopsis
- data Array v f a
- type BArray = Array Vector
- type UArray = Array Vector
- type SArray = Array Vector
- type PArray = Array Vector
- type Layout f = f Int
- class Shape f => HasLayout f a | a -> f where
- class (Eq1 f, Additive f, Traversable f) => Shape f
- extent :: HasLayout f a => a -> f Int
- size :: HasLayout f a => a -> Int
- indexes :: HasLayout f a => IndexedFold Int a (f Int)
- indexesBetween :: HasLayout f a => f Int -> f Int -> IndexedFold Int a (f Int)
- indexesFrom :: HasLayout f a => f Int -> IndexedFold Int a (f Int)
- vector :: (Vector v a, Vector w b) => IndexedLens (Layout f) (Array v f a) (Array w f b) (v a) (w b)
- values :: (Shape f, Vector v a, Vector w b) => IndexedTraversal (f Int) (Array v f a) (Array w f b) a b
- values' :: (Shape f, Vector v a, Vector v b) => IndexedTraversal (f Int) (Array v f a) (Array v f b) a b
- valuesBetween :: (Shape f, Vector v a) => f Int -> f Int -> IndexedTraversal' (f Int) (Array v f a) a
- flat :: Vector w b => Iso (Array v V1 a) (Array w V1 b) (v a) (w b)
- fromListInto :: (Shape f, Vector v a) => Layout f -> [a] -> Maybe (Array v f a)
- fromListInto_ :: (Shape f, Vector v a) => Layout f -> [a] -> Array v f a
- fromVectorInto :: (Shape f, Vector v a) => Layout f -> v a -> Maybe (Array v f a)
- fromVectorInto_ :: (Shape f, Vector v a) => Layout f -> v a -> Array v f a
- ixRow :: Vector v a => Int -> IndexedTraversal' Int (Array v V2 a) (v a)
- rows :: (Vector v a, Vector w b) => IndexedTraversal Int (Array v V2 a) (Array w V2 b) (v a) (w b)
- ixColumn :: Vector v a => Int -> IndexedTraversal' Int (Array v V2 a) (v a)
- columns :: (Vector v a, Vector w b) => IndexedTraversal Int (Array v V2 a) (Array w V2 b) (v a) (w b)
- ixPlane :: Vector v a => ALens' (V3 Int) (V2 Int) -> Int -> IndexedTraversal' Int (Array v V3 a) (Array v V2 a)
- planes :: (Vector v a, Vector w b) => ALens' (V3 Int) (V2 Int) -> IndexedTraversal Int (Array v V3 a) (Array w V3 b) (Array v V2 a) (Array w V2 b)
- flattenPlane :: (Vector v a, Vector w b) => ALens' (V3 Int) (V2 Int) -> (v a -> b) -> Array v V3 a -> Array w V2 b
- data MArray v l s a
- type BMArray = MArray MVector
- type UMArray = MArray MVector
- type SMArray = MArray MVector
- type PMArray = MArray MVector
- data Delayed f a
- delayed :: (Vector v a, Vector w b, Shape f, Shape g) => Iso (Array v f a) (Array w g b) (Delayed f a) (Delayed g b)
- seqDelayed :: (Vector v a, Vector w b, Shape f, Shape g) => Iso (Array v f a) (Array w g b) (Delayed f a) (Delayed g b)
- delay :: (Vector v a, Shape f) => Array v f a -> Delayed f a
- manifest :: (Vector v a, Shape f) => Delayed f a -> Array v f a
- seqManifest :: (Vector v a, Shape f) => Delayed f a -> Array v f a
- genDelayed :: Layout f -> (f Int -> a) -> Delayed f a
- indexDelayed :: Shape f => Delayed f a -> f Int -> a
- affirm :: (Shape f, Unbox a) => Delayed f a -> Delayed f a
- seqAffirm :: (Shape f, Unbox a) => Delayed f a -> Delayed f a
- (*^) :: (Functor f, Num a) => a -> f a -> f a
- (^*) :: (Functor f, Num a) => f a -> a -> f a
- (^/) :: (Functor f, Fractional a) => f a -> a -> f a
- class Functor f => Additive (f :: Type -> Type) where
- class Additive f => Metric (f :: Type -> Type) where
- data Focused f a
- focusOn :: f Int -> Delayed f a -> Focused f a
- unfocus :: Focused f a -> Delayed f a
- unfocused :: IndexedLens (f Int) (Focused f a) (Focused f b) (Delayed f a) (Delayed f b)
- extendFocus :: Shape f => (Focused f a -> b) -> Delayed f a -> Delayed f b
- locale :: ComonadStore s w => Lens' (w a) s
- shiftFocus :: Applicative f => f Int -> Focused f a -> Focused f a
- data Boundary
- peekB :: Shape f => Boundary -> f Int -> Focused f a -> a
- peeksB :: Shape f => Boundary -> (f Int -> f Int) -> Focused f a -> a
- peekRelativeB :: Shape f => Boundary -> f Int -> Focused f a -> a
- class Functor w => Comonad (w :: Type -> Type) where
- class Comonad w => ComonadStore s (w :: Type -> Type) | w -> s where
- data Stencil f a
- stencil :: QuasiQuoter
- mkStencil :: [(f Int, a)] -> Stencil f a
- mkStencilTH :: (ShapeLift f, Lift a) => [(f Int, a)] -> Q Exp
- stencilSum :: (Shape f, Num a) => Boundary -> Stencil f a -> Focused f a -> a
- newtype V1 a = V1 a
- data V2 a = V2 !a !a
- data V3 a = V3 !a !a !a
- data V4 a = V4 !a !a !a !a
- class R1 (t :: Type -> Type) where
- class R1 t => R2 (t :: Type -> Type) where
- class R2 t => R3 (t :: Type -> Type) where
- class R3 t => R4 (t :: Type -> Type) where
- _xz :: forall (t :: Type -> Type) a. R3 t => Lens' (t a) (V2 a)
- _yz :: forall (t :: Type -> Type) a. R3 t => Lens' (t a) (V2 a)
- _yx :: forall (t :: Type -> Type) a. R2 t => Lens' (t a) (V2 a)
- _zy :: forall (t :: Type -> Type) a. R3 t => Lens' (t a) (V2 a)
- _zx :: forall (t :: Type -> Type) a. R3 t => Lens' (t a) (V2 a)
Array types
An Array
is a vector with a shape.
Instances
Shape f => HasLayout f (Array v f a) Source # | The |
(Boxed v, Shape f) => FunctorWithIndex (f Int) (Array v f) Source # | |
(Boxed v, Shape f) => FoldableWithIndex (f Int) (Array v f) Source # | |
Defined in Data.Dense.Base ifoldMap :: Monoid m => (f Int -> a -> m) -> Array v f a -> m # ifolded :: IndexedFold (f Int) (Array v f a) a # ifoldr :: (f Int -> a -> b -> b) -> b -> Array v f a -> b # ifoldl :: (f Int -> b -> a -> b) -> b -> Array v f a -> b # ifoldr' :: (f Int -> a -> b -> b) -> b -> Array v f a -> b # ifoldl' :: (f Int -> b -> a -> b) -> b -> Array v f a -> b # | |
(Boxed v, Shape f) => TraversableWithIndex (f Int) (Array v f) Source # | |
Defined in Data.Dense.Base itraverse :: Applicative f0 => (f Int -> a -> f0 b) -> Array v f a -> f0 (Array v f b) # itraversed :: IndexedTraversal (f Int) (Array v f a) (Array v f b) a b # | |
Boxed v => Functor (Array v f) Source # | |
Boxed v => Foldable (Array v f) Source # | |
Defined in Data.Dense.Base fold :: Monoid m => Array v f m -> m # foldMap :: Monoid m => (a -> m) -> Array v f a -> m # foldMap' :: Monoid m => (a -> m) -> Array v f a -> m # foldr :: (a -> b -> b) -> b -> Array v f a -> b # foldr' :: (a -> b -> b) -> b -> Array v f a -> b # foldl :: (b -> a -> b) -> b -> Array v f a -> b # foldl' :: (b -> a -> b) -> b -> Array v f a -> b # foldr1 :: (a -> a -> a) -> Array v f a -> a # foldl1 :: (a -> a -> a) -> Array v f a -> a # toList :: Array v f a -> [a] # length :: Array v f a -> Int # elem :: Eq a => a -> Array v f a -> Bool # maximum :: Ord a => Array v f a -> a # minimum :: Ord a => Array v f a -> a # | |
Boxed v => Traversable (Array v f) Source # | |
(Boxed v, Eq1 f) => Eq1 (Array v f) Source # | |
(Boxed v, Read1 f) => Read1 (Array v f) Source # | |
Defined in Data.Dense.Base | |
(Boxed v, Shape f, Serial1 f) => Serial1 (Array v f) Source # | |
Defined in Data.Dense.Base serializeWith :: MonadPut m => (a -> m ()) -> Array v f a -> m () # deserializeWith :: MonadGet m => m a -> m (Array v f a) # | |
(Vector v a, f ~ V1) => Vector (Array v f) a Source # | 1D Arrays can be used as a generic |
Defined in Data.Dense.Base basicUnsafeFreeze :: PrimMonad m => Mutable (Array v f) (PrimState m) a -> m (Array v f a) # basicUnsafeThaw :: PrimMonad m => Array v f a -> m (Mutable (Array v f) (PrimState m) a) # basicLength :: Array v f a -> Int # basicUnsafeSlice :: Int -> Int -> Array v f a -> Array v f a # basicUnsafeIndexM :: Monad m => Array v f a -> Int -> m a # basicUnsafeCopy :: PrimMonad m => Mutable (Array v f) (PrimState m) a -> Array v f a -> m () # | |
(Vector v a, Eq1 f, Eq a) => Eq (Array v f a) Source # | |
(Typeable f, Typeable v, Typeable a, Data (f Int), Data (v a)) => Data (Array v f a) Source # | |
Defined in Data.Dense.Base gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Array v f a -> c (Array v f a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Array v f a) # toConstr :: Array v f a -> Constr # dataTypeOf :: Array v f a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Array v f a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Array v f a)) # gmapT :: (forall b. Data b => b -> b) -> Array v f a -> Array v f a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Array v f a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Array v f a -> r # gmapQ :: (forall d. Data d => d -> u) -> Array v f a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Array v f a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Array v f a -> m (Array v f a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Array v f a -> m (Array v f a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Array v f a -> m (Array v f a) # | |
(Vector v a, Read1 f, Read a) => Read (Array v f a) Source # | |
(Vector v a, Show1 f, Show a) => Show (Array v f a) Source # | |
(Vector v a, Shape f, Binary (f Int), Binary a) => Binary (Array v f a) Source # | |
(Vector v a, Shape f, Serial1 f, Serial a) => Serial (Array v f a) Source # | |
Defined in Data.Dense.Base | |
(Vector v a, Shape f, Serialize (f Int), Serialize a) => Serialize (Array v f a) Source # | |
(NFData (f Int), NFData (v a)) => NFData (Array v f a) Source # | |
Defined in Data.Dense.Base | |
(Vector v a, Foldable f, Hashable a) => Hashable (Array v f a) Source # | |
Defined in Data.Dense.Base | |
(Shape f, Vector v a) => Ixed (Array v f a) Source # | |
Defined in Data.Dense.Base | |
(Shape f, Vector v a) => AsEmpty (Array v f a) Source # | |
Defined in Data.Dense.Base | |
(Vector v a, Vector v b) => Each (Array v f a) (Array v f b) a b Source # | |
type Mutable (Array v f) Source # | |
Defined in Data.Dense.Base | |
type Index (Array v f a) Source # | |
Defined in Data.Dense.Base | |
type IxValue (Array v f a) Source # | |
Defined in Data.Dense.Base |
Indexing
type Layout f = f Int Source #
A Layout
is the full size of an array. This alias is used to help
distinguish between the layout of an array and an index (usually
just l Int
) in a type signature.
class Shape f => HasLayout f a | a -> f where Source #
Class of things that have a Layout
. This means we can use the
same functions for the various different arrays in the library.
Nothing
Instances
i ~ Int => HasLayout V0 (V0 i) Source # | |
i ~ Int => HasLayout V4 (V4 i) Source # | |
i ~ Int => HasLayout V3 (V3 i) Source # | |
i ~ Int => HasLayout V2 (V2 i) Source # | |
i ~ Int => HasLayout V1 (V1 i) Source # | |
Shape f => HasLayout f (Focused f a) Source # | The |
Shape f => HasLayout f (Delayed f a) Source # | The |
Shape f => HasLayout f (Array v f a) Source # | The |
Shape f => HasLayout f (MArray v f s a) Source # | |
class (Eq1 f, Additive f, Traversable f) => Shape f Source #
Class for types that can be converted to and from linear indexes.
Instances
Folds over indexes
indexes :: HasLayout f a => IndexedFold Int a (f Int) Source #
Indexed fold for all the indexes in the layout.
indexesBetween :: HasLayout f a => f Int -> f Int -> IndexedFold Int a (f Int) Source #
Indexed fold between the two indexes where the index is the linear index for the original layout.
indexesFrom :: HasLayout f a => f Int -> IndexedFold Int a (f Int) Source #
Indexed fold starting starting from some point, where the index is the linear index for the original layout.
Lenses
vector :: (Vector v a, Vector w b) => IndexedLens (Layout f) (Array v f a) (Array w f b) (v a) (w b) Source #
Traversals
values :: (Shape f, Vector v a, Vector w b) => IndexedTraversal (f Int) (Array v f a) (Array w f b) a b Source #
Indexed traversal over the elements of an array. The index is the current position in the array.
values' :: (Shape f, Vector v a, Vector v b) => IndexedTraversal (f Int) (Array v f a) (Array v f b) a b Source #
Same as values
but restrictive in the vector type.
valuesBetween :: (Shape f, Vector v a) => f Int -> f Int -> IndexedTraversal' (f Int) (Array v f a) a Source #
Traverse over the values
between two indexes.
Construction
Flat arrays
flat :: Vector w b => Iso (Array v V1 a) (Array w V1 b) (v a) (w b) Source #
1D arrays are just vectors. You are free to change the length of
the vector when going over
this Iso
(unlike linear
).
Note that V1
arrays are an instance of Vector
so you can use
any of the functions in Data.Vector.Generic on them without
needing to convert.
Shaped from lists
fromListInto :: (Shape f, Vector v a) => Layout f -> [a] -> Maybe (Array v f a) Source #
O(n) Convert the first n
elements of a list to an Array with the
given shape. Returns Nothing
if there are not enough elements in
the list.
fromListInto_ :: (Shape f, Vector v a) => Layout f -> [a] -> Array v f a Source #
O(n) Convert the first n
elements of a list to an Array with the
given shape. Throw an error if the list is not long enough.
Shaped from vectors
Generating
See Data.Shaped.Generic.
Functions on arrays
Empty arrays
See AsEmpty
class or Data.Shaped.Generic.
Indexing
See Ixed
class.
Modifying arrays
See Data.Shaped.Generic.
Slices
Matrix
ixRow :: Vector v a => Int -> IndexedTraversal' Int (Array v V2 a) (v a) Source #
Affine traversal over a single row in a matrix.
>>>
traverseOf_ rows print $ m & ixRow 1 . each *~ 2
[a,b,c,d] [e * 2,f * 2,g * 2,h * 2] [i,j,k,l]
The row vector should remain the same size to satisfy traversal laws but give reasonable behaviour if the size differs:
>>>
traverseOf_ rows print $ m & ixRow 1 .~ B.fromList [0,1]
[a,b,c,d] [0,1,g,h] [i,j,k,l]
>>>
traverseOf_ rows print $ m & ixRow 1 .~ B.fromList [0..100]
[a,b,c,d] [0,1,2,3] [i,j,k,l]
rows :: (Vector v a, Vector w b) => IndexedTraversal Int (Array v V2 a) (Array w V2 b) (v a) (w b) Source #
Indexed traversal over the rows of a matrix. Each row is an
efficient slice
of the original vector.
>>>
traverseOf_ rows print m
[a,b,c,d] [e,f,g,h] [i,j,k,l]
ixColumn :: Vector v a => Int -> IndexedTraversal' Int (Array v V2 a) (v a) Source #
Affine traversal over a single column in a matrix.
>>>
traverseOf_ rows print $ m & ixColumn 2 . each +~ 1
[a,b,c + 1,d] [e,f,g + 1,h] [i,j,k + 1,l]
columns :: (Vector v a, Vector w b) => IndexedTraversal Int (Array v V2 a) (Array w V2 b) (v a) (w b) Source #
Indexed traversal over the columns of a matrix. Unlike rows
, each
column is a new separate vector.
>>>
traverseOf_ columns print m
[a,e,i] [b,f,j] [c,g,k] [d,h,l]
>>>
traverseOf_ rows print $ m & columns . indices odd . each .~ 0
[a,0,c,0] [e,0,g,0] [i,0,k,0]
The vectors should be the same size to be a valid traversal. If the vectors are different sizes, the number of rows in the new array will be the length of the smallest vector.
3D
ixPlane :: Vector v a => ALens' (V3 Int) (V2 Int) -> Int -> IndexedTraversal' Int (Array v V3 a) (Array v V2 a) Source #
planes :: (Vector v a, Vector w b) => ALens' (V3 Int) (V2 Int) -> IndexedTraversal Int (Array v V3 a) (Array w V3 b) (Array v V2 a) (Array w V2 b) Source #
flattenPlane :: (Vector v a, Vector w b) => ALens' (V3 Int) (V2 Int) -> (v a -> b) -> Array v V3 a -> Array w V2 b Source #
Flatten a plane by reducing a vector in the third dimension to a single value.
Mutable
A mutable array with a shape.
Instances
Delayed
A delayed representation of an array. This useful for mapping over an array in parallel.
Instances
Shape f => HasLayout f (Delayed f a) Source # | The |
Functor (Delayed f) Source # | |
Shape f => Foldable (Delayed f) Source # |
|
Defined in Data.Dense.Base fold :: Monoid m => Delayed f m -> m # foldMap :: Monoid m => (a -> m) -> Delayed f a -> m # foldMap' :: Monoid m => (a -> m) -> Delayed f a -> m # foldr :: (a -> b -> b) -> b -> Delayed f a -> b # foldr' :: (a -> b -> b) -> b -> Delayed f a -> b # foldl :: (b -> a -> b) -> b -> Delayed f a -> b # foldl' :: (b -> a -> b) -> b -> Delayed f a -> b # foldr1 :: (a -> a -> a) -> Delayed f a -> a # foldl1 :: (a -> a -> a) -> Delayed f a -> a # toList :: Delayed f a -> [a] # length :: Delayed f a -> Int # elem :: Eq a => a -> Delayed f a -> Bool # maximum :: Ord a => Delayed f a -> a # minimum :: Ord a => Delayed f a -> a # | |
Shape f => Traversable (Delayed f) Source # | |
Shape f => Apply (Delayed f) Source # | |
Shape f => Metric (Delayed f) Source # | |
Defined in Data.Dense.Base | |
Shape f => Additive (Delayed f) Source # | |
Defined in Data.Dense.Base zero :: Num a => Delayed f a # (^+^) :: Num a => Delayed f a -> Delayed f a -> Delayed f a # (^-^) :: Num a => Delayed f a -> Delayed f a -> Delayed f a # lerp :: Num a => a -> Delayed f a -> Delayed f a -> Delayed f a # liftU2 :: (a -> a -> a) -> Delayed f a -> Delayed f a -> Delayed f a # liftI2 :: (a -> b -> c) -> Delayed f a -> Delayed f b -> Delayed f c # | |
FunctorWithIndex (f Int) (Delayed f) Source # | |
Shape f => FoldableWithIndex (f Int) (Delayed f) Source # |
|
Defined in Data.Dense.Base ifoldMap :: Monoid m => (f Int -> a -> m) -> Delayed f a -> m # ifolded :: IndexedFold (f Int) (Delayed f a) a # ifoldr :: (f Int -> a -> b -> b) -> b -> Delayed f a -> b # ifoldl :: (f Int -> b -> a -> b) -> b -> Delayed f a -> b # ifoldr' :: (f Int -> a -> b -> b) -> b -> Delayed f a -> b # ifoldl' :: (f Int -> b -> a -> b) -> b -> Delayed f a -> b # | |
Shape f => TraversableWithIndex (f Int) (Delayed f) Source # | |
Defined in Data.Dense.Base itraverse :: Applicative f0 => (f Int -> a -> f0 b) -> Delayed f a -> f0 (Delayed f b) # itraversed :: IndexedTraversal (f Int) (Delayed f a) (Delayed f b) a b # | |
(Shape f, Show1 f, Show a) => Show (Delayed f a) Source # | |
Shape f => Ixed (Delayed f a) Source # | |
Defined in Data.Dense.Base | |
Shape f => AsEmpty (Delayed f a) Source # | |
Defined in Data.Dense.Base | |
Shape f => Each (Delayed f a) (Delayed f b) a b Source # | |
type Index (Delayed f a) Source # | |
Defined in Data.Dense.Base | |
type IxValue (Delayed f a) Source # | |
Defined in Data.Dense.Base |
Generating delayed
delayed :: (Vector v a, Vector w b, Shape f, Shape g) => Iso (Array v f a) (Array w g b) (Delayed f a) (Delayed g b) Source #
Isomorphism between an array and its delayed representation. Conversion to the array is done in parallel.
seqDelayed :: (Vector v a, Vector w b, Shape f, Shape g) => Iso (Array v f a) (Array w g b) (Delayed f a) (Delayed g b) Source #
Isomorphism between an array and its delayed representation. Conversion to the array is done in parallel.
delay :: (Vector v a, Shape f) => Array v f a -> Delayed f a Source #
Turn a material array into a delayed one with the same shape.
manifest :: (Vector v a, Shape f) => Delayed f a -> Array v f a Source #
Parallel manifestation of a delayed array into a material one.
seqManifest :: (Vector v a, Shape f) => Delayed f a -> Array v f a Source #
Sequential manifestation of a delayed array.
indexDelayed :: Shape f => Delayed f a -> f Int -> a Source #
Index a delayed array, returning a IndexOutOfBounds
exception if
the index is out of range.
affirm :: (Shape f, Unbox a) => Delayed f a -> Delayed f a Source #
manifest
an array to a UArray
and delay again. See
Data.Dense.Boxed or Data.Dense.Storable to affirm
for other
types of arrays.
seqAffirm :: (Shape f, Unbox a) => Delayed f a -> Delayed f a Source #
seqManifest
an array to a UArray
and delay again. See
Data.Dense.Boxed or Data.Dense.Storable to affirm
for other
types of arrays.
Helpful reexports
(*^) :: (Functor f, Num a) => a -> f a -> f a infixl 7 #
Compute the left scalar product
>>>
2 *^ V2 3 4
V2 6 8
(^*) :: (Functor f, Num a) => f a -> a -> f a infixl 7 #
Compute the right scalar product
>>>
V2 3 4 ^* 2
V2 6 8
(^/) :: (Functor f, Fractional a) => f a -> a -> f a infixl 7 #
Compute division by a scalar on the right.
class Functor f => Additive (f :: Type -> Type) where #
A vector is an additive group with additional structure.
Nothing
The zero vector
(^+^) :: Num a => f a -> f a -> f a infixl 6 #
Compute the sum of two vectors
>>>
V2 1 2 ^+^ V2 3 4
V2 4 6
(^-^) :: Num a => f a -> f a -> f a infixl 6 #
Compute the difference between two vectors
>>>
V2 4 5 ^-^ V2 3 1
V2 1 4
lerp :: Num a => a -> f a -> f a -> f a #
Linearly interpolate between two vectors.
liftU2 :: (a -> a -> a) -> f a -> f a -> f a #
Apply a function to merge the 'non-zero' components of two vectors, unioning the rest of the values.
liftI2 :: (a -> b -> c) -> f a -> f b -> f c #
Apply a function to the components of two vectors.
- For a dense vector this is equivalent to
liftA2
. - For a sparse vector this is equivalent to
intersectionWith
.
Instances
class Additive f => Metric (f :: Type -> Type) where #
Free and sparse inner product/metric spaces.
Nothing
dot :: Num a => f a -> f a -> a #
Compute the inner product of two vectors or (equivalently)
convert a vector f a
into a covector f a -> a
.
>>>
V2 1 2 `dot` V2 3 4
11
quadrance :: Num a => f a -> a #
Compute the squared norm. The name quadrance arises from Norman J. Wildberger's rational trigonometry.
qd :: Num a => f a -> f a -> a #
Compute the quadrance of the difference
distance :: Floating a => f a -> f a -> a #
Compute the distance between two vectors in a metric space
norm :: Floating a => f a -> a #
Compute the norm of a vector in a metric space
signorm :: Floating a => f a -> f a #
Convert a non-zero vector to unit vector.
Instances
Metric [] | |
Metric Maybe | |
Metric ZipList | |
Metric Identity | |
Defined in Linear.Metric | |
Metric IntMap | |
Metric Vector | |
Metric Plucker | |
Metric Quaternion | |
Defined in Linear.Quaternion dot :: Num a => Quaternion a -> Quaternion a -> a # quadrance :: Num a => Quaternion a -> a # qd :: Num a => Quaternion a -> Quaternion a -> a # distance :: Floating a => Quaternion a -> Quaternion a -> a # norm :: Floating a => Quaternion a -> a # signorm :: Floating a => Quaternion a -> Quaternion a # | |
Metric V0 | |
Metric V4 | |
Metric V3 | |
Metric V2 | |
Metric V1 | |
Ord k => Metric (Map k) | |
(Hashable k, Eq k) => Metric (HashMap k) | |
Defined in Linear.Metric | |
Shape f => Metric (Delayed f) Source # | |
Defined in Data.Dense.Base | |
Dim n => Metric (V n) | |
(Metric f, Metric g) => Metric (Product f g) | |
(Metric f, Metric g) => Metric (Compose f g) | |
Focused
A delayed representation of an array with a focus on a single
element. This element is the target of extract
.
Instances
Shape f => HasLayout f (Focused f a) Source # | The |
Functor (Focused f) Source # | |
Shape f => Foldable (Focused f) Source # | |
Defined in Data.Dense.Base fold :: Monoid m => Focused f m -> m # foldMap :: Monoid m => (a -> m) -> Focused f a -> m # foldMap' :: Monoid m => (a -> m) -> Focused f a -> m # foldr :: (a -> b -> b) -> b -> Focused f a -> b # foldr' :: (a -> b -> b) -> b -> Focused f a -> b # foldl :: (b -> a -> b) -> b -> Focused f a -> b # foldl' :: (b -> a -> b) -> b -> Focused f a -> b # foldr1 :: (a -> a -> a) -> Focused f a -> a # foldl1 :: (a -> a -> a) -> Focused f a -> a # toList :: Focused f a -> [a] # length :: Focused f a -> Int # elem :: Eq a => a -> Focused f a -> Bool # maximum :: Ord a => Focused f a -> a # minimum :: Ord a => Focused f a -> a # | |
Shape f => Traversable (Focused f) Source # | |
Shape f => Comonad (Focused f) Source # | |
Shape f => Extend (Focused f) Source # | |
Shape f => ComonadStore (f Int) (Focused f) Source # | |
Defined in Data.Dense.Base | |
Shape f => FunctorWithIndex (f Int) (Focused f) Source # | Index relative to focus. |
Shape f => FoldableWithIndex (f Int) (Focused f) Source # | Index relative to focus. |
Defined in Data.Dense.Base ifoldMap :: Monoid m => (f Int -> a -> m) -> Focused f a -> m # ifolded :: IndexedFold (f Int) (Focused f a) a # ifoldr :: (f Int -> a -> b -> b) -> b -> Focused f a -> b # ifoldl :: (f Int -> b -> a -> b) -> b -> Focused f a -> b # ifoldr' :: (f Int -> a -> b -> b) -> b -> Focused f a -> b # ifoldl' :: (f Int -> b -> a -> b) -> b -> Focused f a -> b # | |
Shape f => TraversableWithIndex (f Int) (Focused f) Source # | Index relative to focus. |
Defined in Data.Dense.Base itraverse :: Applicative f0 => (f Int -> a -> f0 b) -> Focused f a -> f0 (Focused f b) # itraversed :: IndexedTraversal (f Int) (Focused f a) (Focused f b) a b # | |
(Shape f, Show1 f, Show a) => Show (Focused f a) Source # | |
Shape f => Ixed (Focused f a) Source # | Index relative to focus. |
Defined in Data.Dense.Base | |
type Index (Focused f a) Source # | |
Defined in Data.Dense.Base | |
type IxValue (Focused f a) Source # | |
Defined in Data.Dense.Base |
Generating focused
focusOn :: f Int -> Delayed f a -> Focused f a Source #
Focus on a particular element of a delayed array.
unfocused :: IndexedLens (f Int) (Focused f a) (Focused f b) (Delayed f a) (Delayed f b) Source #
Indexed lens onto the delayed array, indexed at the focus.
Focus location
locale :: ComonadStore s w => Lens' (w a) s Source #
Lens onto the position of a ComonadStore
.
locale
::Lens'
(Focused
l a) (lInt
)
shiftFocus :: Applicative f => f Int -> Focused f a -> Focused f a Source #
Focus on a neighbouring element, relative to the current focus.
Boundary
The boundary condition used for indexing relative elements in a
Focused
.
Clamp | clamp coordinates to the extent of the array |
Mirror | mirror coordinates beyond the array extent |
Wrap | wrap coordinates around on each dimension |
peekB :: Shape f => Boundary -> f Int -> Focused f a -> a Source #
Index a focused using a Boundary
condition.
peeksB :: Shape f => Boundary -> (f Int -> f Int) -> Focused f a -> a Source #
Index an element by applying a function the current position, using a boundary condition.
peekRelativeB :: Shape f => Boundary -> f Int -> Focused f a -> a Source #
Index an element relative to the current focus using a Boundary
condition.
Helpful reexports
class Functor w => Comonad (w :: Type -> Type) where #
There are two ways to define a comonad:
I. Provide definitions for extract
and extend
satisfying these laws:
extend
extract
=id
extract
.extend
f = fextend
f .extend
g =extend
(f .extend
g)
In this case, you may simply set fmap
= liftW
.
These laws are directly analogous to the laws for monads and perhaps can be made clearer by viewing them as laws stating that Cokleisli composition must be associative, and has extract for a unit:
f=>=
extract
= fextract
=>=
f = f (f=>=
g)=>=
h = f=>=
(g=>=
h)
II. Alternately, you may choose to provide definitions for fmap
,
extract
, and duplicate
satisfying these laws:
extract
.duplicate
=id
fmap
extract
.duplicate
=id
duplicate
.duplicate
=fmap
duplicate
.duplicate
In this case you may not rely on the ability to define fmap
in
terms of liftW
.
You may of course, choose to define both duplicate
and extend
.
In that case you must also satisfy these laws:
extend
f =fmap
f .duplicate
duplicate
=extend
idfmap
f =extend
(f .extract
)
These are the default definitions of extend
and duplicate
and
the definition of liftW
respectively.
Instances
class Comonad w => ComonadStore s (w :: Type -> Type) | w -> s where #
peeks :: (s -> s) -> w a -> a #
seeks :: (s -> s) -> w a -> w a #
experiment :: Functor f => (s -> f s) -> w a -> f a #
Instances
ComonadStore s w => ComonadStore s (Cofree w) | |
(ComonadStore s w, Monoid m) => ComonadStore s (TracedT m w) | |
Defined in Control.Comonad.Store.Class | |
Comonad w => ComonadStore s (StoreT s w) | |
ComonadStore s w => ComonadStore s (IdentityT w) | |
Defined in Control.Comonad.Store.Class | |
ComonadStore s w => ComonadStore s (EnvT e w) | |
a ~ b => ComonadStore a (Context a b) | |
Defined in Control.Lens.Internal.Context | |
(a ~ b, Conjoined p) => ComonadStore a (Pretext p a b) | |
Defined in Control.Lens.Internal.Context | |
(a ~ b, Conjoined p) => ComonadStore a (PretextT p g a b) | |
Defined in Control.Lens.Internal.Context pos :: PretextT p g a b a0 -> a # peek :: a -> PretextT p g a b a0 -> a0 # peeks :: (a -> a) -> PretextT p g a b a0 -> a0 # seek :: a -> PretextT p g a b a0 -> PretextT p g a b a0 # seeks :: (a -> a) -> PretextT p g a b a0 -> PretextT p g a b a0 # experiment :: Functor f => (a -> f a) -> PretextT p g a b a0 -> f a0 # | |
Shape f => ComonadStore (f Int) (Focused f) Source # | |
Defined in Data.Dense.Base |
Stencils
Stencils are used to fold over neighbouring array sites. To
construct a stencil use mkStencil
, mkStencilUnboxed
. For
static sized stencils you can use the quasiquoter
stencil
.
To use a stencil you can use stencilSum
or use the Foldable
and
FoldableWithIndex
instances.
Instances
Functor (Stencil f) Source # | |
Foldable (Stencil f) Source # | |
Defined in Data.Dense.Stencil fold :: Monoid m => Stencil f m -> m # foldMap :: Monoid m => (a -> m) -> Stencil f a -> m # foldMap' :: Monoid m => (a -> m) -> Stencil f a -> m # foldr :: (a -> b -> b) -> b -> Stencil f a -> b # foldr' :: (a -> b -> b) -> b -> Stencil f a -> b # foldl :: (b -> a -> b) -> b -> Stencil f a -> b # foldl' :: (b -> a -> b) -> b -> Stencil f a -> b # foldr1 :: (a -> a -> a) -> Stencil f a -> a # foldl1 :: (a -> a -> a) -> Stencil f a -> a # toList :: Stencil f a -> [a] # length :: Stencil f a -> Int # elem :: Eq a => a -> Stencil f a -> Bool # maximum :: Ord a => Stencil f a -> a # minimum :: Ord a => Stencil f a -> a # | |
FoldableWithIndex (f Int) (Stencil f) Source # | |
Defined in Data.Dense.Stencil ifoldMap :: Monoid m => (f Int -> a -> m) -> Stencil f a -> m # ifolded :: IndexedFold (f Int) (Stencil f a) a # ifoldr :: (f Int -> a -> b -> b) -> b -> Stencil f a -> b # ifoldl :: (f Int -> b -> a -> b) -> b -> Stencil f a -> b # ifoldr' :: (f Int -> a -> b -> b) -> b -> Stencil f a -> b # ifoldl' :: (f Int -> b -> a -> b) -> b -> Stencil f a -> b # | |
(Show1 f, Show a) => Show (Stencil f a) Source # | |
Constructing stencils
stencil :: QuasiQuoter Source #
QuasiQuoter for producing a static stencil definition. This is a
versatile parser for 1D, 2D and 3D stencils. The parsing is similar
to dense
but stencil
also supports _
, which means ignore this
element. Also, stencils should have an odd length in all dimensions
so there is always a center element (which is used as zero
).
Examples
- 1D stencils are of the form
[stencil
| 5 -3 1 -3 5 |] ::Num
a =>Stencil
V1
a
- 2D stencils are of the form
myStencil2 ::Num
a =>Stencil
V2
a myStencil2 = [stencil
| 0 1 0 1 0 1 0 1 0 |]
- 3D stencils have gaps between planes.
myStencil3 ::Fractional
a =>Stencil
V3
a myStencil3 :: [stencil
| 1/20 3/10 1/20 3/10 1 3/10 1/20 3/10 1/20 3/10 1 3/10 1 _ 1 3/10 1 3/10 1/20 3/10 1/20 3/10 1 3/10 1/20 3/10 1/20 |]
Variables can also be used
myStencil2' :: a -> a -> a ->Stencil
V2
a myStencil2' a b c = [stencil
| c b c b a b c b c |]
mkStencil :: [(f Int, a)] -> Stencil f a Source #
Make a stencil folding over a list.
If the list is staticlly known this should expand at compile time
via rewrite rules, similar to makeStencilTH
but less reliable. If
that does not happen the resulting could be slow. If the list is
not know at compile time, mkStencilUnboxed
can be signifcantly
faster (but isn't subject expending via rewrite rules).
mkStencilTH :: (ShapeLift f, Lift a) => [(f Int, a)] -> Q Exp Source #
Construct a Stencil
by unrolling the list at compile time. For
example
ifoldr
f b $(mkStencilTH
[(V1
(-1), 5), (V1
0, 3), (V1
1, 5)])
will be get turned into
f (V1
(-1)) 5 (f (V1
0) 3 (f (V1
1) 5 b))
at compile time. Since there are no loops and all target indexes are known at compile time, this can lead to more optimisations and faster execution times. This can lead to around a 2x speed up compared to folding over unboxed vectors.
myStencil = $(mkStencilTH
(as :: [(fInt
, a)])) ::Stencil
f a
Using stencils
stencilSum :: (Shape f, Num a) => Boundary -> Stencil f a -> Focused f a -> a Source #
Sum the elements around a Focused
using a Boundary
condition
and a Stencil
.
This is often used in conjunction with extendFocus
.
Common shapes
A 1-dimensional vector
>>>
pure 1 :: V1 Int
V1 1
>>>
V1 2 + V1 3
V1 5
>>>
V1 2 * V1 3
V1 6
>>>
sum (V1 2)
2
V1 a |
Instances
Monad V1 | |
Functor V1 | |
MonadFix V1 | |
Applicative V1 | |
Foldable V1 | |
Defined in Linear.V1 fold :: Monoid m => V1 m -> m # foldMap :: Monoid m => (a -> m) -> V1 a -> m # foldMap' :: Monoid m => (a -> m) -> V1 a -> m # foldr :: (a -> b -> b) -> b -> V1 a -> b # foldr' :: (a -> b -> b) -> b -> V1 a -> b # foldl :: (b -> a -> b) -> b -> V1 a -> b # foldl' :: (b -> a -> b) -> b -> V1 a -> b # foldr1 :: (a -> a -> a) -> V1 a -> a # foldl1 :: (a -> a -> a) -> V1 a -> a # elem :: Eq a => a -> V1 a -> Bool # maximum :: Ord a => V1 a -> a # | |
Traversable V1 | |
Distributive V1 | |
Representable V1 | |
Eq1 V1 | |
Ord1 V1 | |
Read1 V1 | |
Show1 V1 | |
MonadZip V1 | |
Serial1 V1 | |
Defined in Linear.V1 serializeWith :: MonadPut m => (a -> m ()) -> V1 a -> m () # deserializeWith :: MonadGet m => m a -> m (V1 a) # | |
Hashable1 V1 | |
Apply V1 | |
Traversable1 V1 | |
Trace V1 | |
R1 V1 | |
Finite V1 | |
Metric V1 | |
Additive V1 | |
Foldable1 V1 | |
Bind V1 | |
Shape V1 Source # | |
Defined in Data.Dense.Index shapeToIndex :: Layout V1 -> V1 Int -> Int Source # shapeFromIndex :: Layout V1 -> Int -> V1 Int Source # shapeIntersect :: Layout V1 -> Layout V1 -> Layout V1 Source # unsafeShapeStep :: Layout V1 -> V1 Int -> V1 Int Source # shapeStep :: Layout V1 -> V1 Int -> Maybe (V1 Int) Source # shapeStepBetween :: V1 Int -> Layout V1 -> V1 Int -> Maybe (V1 Int) Source # | |
ShapeLift V1 Source # | |
Lift a => Lift (V1 a :: Type) | |
Unbox a => Vector Vector (V1 a) | |
Defined in Linear.V1 basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (V1 a) -> m (Vector (V1 a)) # basicUnsafeThaw :: PrimMonad m => Vector (V1 a) -> m (Mutable Vector (PrimState m) (V1 a)) # basicLength :: Vector (V1 a) -> Int # basicUnsafeSlice :: Int -> Int -> Vector (V1 a) -> Vector (V1 a) # basicUnsafeIndexM :: Monad m => Vector (V1 a) -> Int -> m (V1 a) # basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (V1 a) -> Vector (V1 a) -> m () # | |
Num r => Algebra r (E V1) | |
Num r => Coalgebra r (E V1) | |
Unbox a => MVector MVector (V1 a) | |
Defined in Linear.V1 basicLength :: MVector s (V1 a) -> Int # basicUnsafeSlice :: Int -> Int -> MVector s (V1 a) -> MVector s (V1 a) # basicOverlaps :: MVector s (V1 a) -> MVector s (V1 a) -> Bool # basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (V1 a)) # basicInitialize :: PrimMonad m => MVector (PrimState m) (V1 a) -> m () # basicUnsafeReplicate :: PrimMonad m => Int -> V1 a -> m (MVector (PrimState m) (V1 a)) # basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (V1 a) -> Int -> m (V1 a) # basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (V1 a) -> Int -> V1 a -> m () # basicClear :: PrimMonad m => MVector (PrimState m) (V1 a) -> m () # basicSet :: PrimMonad m => MVector (PrimState m) (V1 a) -> V1 a -> m () # basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (V1 a) -> MVector (PrimState m) (V1 a) -> m () # basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (V1 a) -> MVector (PrimState m) (V1 a) -> m () # basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (V1 a) -> Int -> m (MVector (PrimState m) (V1 a)) # | |
i ~ Int => HasLayout V1 (V1 i) Source # | |
Bounded a => Bounded (V1 a) | |
Eq a => Eq (V1 a) | |
Floating a => Floating (V1 a) | |
Fractional a => Fractional (V1 a) | |
Data a => Data (V1 a) | |
Defined in Linear.V1 gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> V1 a -> c (V1 a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (V1 a) # dataTypeOf :: V1 a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (V1 a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (V1 a)) # gmapT :: (forall b. Data b => b -> b) -> V1 a -> V1 a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> V1 a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> V1 a -> r # gmapQ :: (forall d. Data d => d -> u) -> V1 a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> V1 a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> V1 a -> m (V1 a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> V1 a -> m (V1 a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> V1 a -> m (V1 a) # | |
Num a => Num (V1 a) | |
Ord a => Ord (V1 a) | |
Read a => Read (V1 a) | |
Show a => Show (V1 a) | |
Ix a => Ix (V1 a) | |
Generic (V1 a) | |
Semigroup a => Semigroup (V1 a) | |
Monoid a => Monoid (V1 a) | |
Storable a => Storable (V1 a) | |
Binary a => Binary (V1 a) | |
Serial a => Serial (V1 a) | |
Serialize a => Serialize (V1 a) | |
NFData a => NFData (V1 a) | |
Hashable a => Hashable (V1 a) | |
Unbox a => Unbox (V1 a) | |
Defined in Linear.V1 | |
Ixed (V1 a) | |
Epsilon a => Epsilon (V1 a) | |
Random a => Random (V1 a) | |
Generic1 V1 | |
FunctorWithIndex (E V1) V1 | |
FoldableWithIndex (E V1) V1 | |
TraversableWithIndex (E V1) V1 | |
Defined in Linear.V1 itraverse :: Applicative f => (E V1 -> a -> f b) -> V1 a -> f (V1 b) # itraversed :: IndexedTraversal (E V1) (V1 a) (V1 b) a b # | |
Each (V1 a) (V1 b) a b | |
Field1 (V1 a) (V1 b) a b | |
type Rep V1 | |
type Size V1 | |
newtype MVector s (V1 a) | |
type Rep (V1 a) | |
newtype Vector (V1 a) | |
type Index (V1 a) | |
type IxValue (V1 a) | |
type Rep1 V1 | |
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
V2 !a !a |
Instances
A 3-dimensional vector
V3 !a !a !a |
Instances
A 4-dimensional vector.
V4 !a !a !a !a |
Instances
Monad V4 | |
Functor V4 | |
MonadFix V4 | |
Applicative V4 | |
Foldable V4 | |
Defined in Linear.V4 fold :: Monoid m => V4 m -> m # foldMap :: Monoid m => (a -> m) -> V4 a -> m # foldMap' :: Monoid m => (a -> m) -> V4 a -> m # foldr :: (a -> b -> b) -> b -> V4 a -> b # foldr' :: (a -> b -> b) -> b -> V4 a -> b # foldl :: (b -> a -> b) -> b -> V4 a -> b # foldl' :: (b -> a -> b) -> b -> V4 a -> b # foldr1 :: (a -> a -> a) -> V4 a -> a # foldl1 :: (a -> a -> a) -> V4 a -> a # elem :: Eq a => a -> V4 a -> Bool # maximum :: Ord a => V4 a -> a # | |
Traversable V4 | |
Distributive V4 | |
Representable V4 | |
Eq1 V4 | |
Ord1 V4 | |
Read1 V4 | |
Show1 V4 | |
MonadZip V4 | |
Serial1 V4 | |
Defined in Linear.V4 serializeWith :: MonadPut m => (a -> m ()) -> V4 a -> m () # deserializeWith :: MonadGet m => m a -> m (V4 a) # | |
Hashable1 V4 | |
Apply V4 | |
Traversable1 V4 | |
Trace V4 | |
R4 V4 | |
R3 V4 | |
R2 V4 | |
R1 V4 | |
Finite V4 | |
Metric V4 | |
Additive V4 | |
Foldable1 V4 | |
Bind V4 | |
Shape V4 Source # | |
Defined in Data.Dense.Index shapeToIndex :: Layout V4 -> V4 Int -> Int Source # shapeFromIndex :: Layout V4 -> Int -> V4 Int Source # shapeIntersect :: Layout V4 -> Layout V4 -> Layout V4 Source # unsafeShapeStep :: Layout V4 -> V4 Int -> V4 Int Source # shapeStep :: Layout V4 -> V4 Int -> Maybe (V4 Int) Source # shapeStepBetween :: V4 Int -> Layout V4 -> V4 Int -> Maybe (V4 Int) Source # | |
ShapeLift V4 Source # | |
Lift a => Lift (V4 a :: Type) | |
Unbox a => Vector Vector (V4 a) | |
Defined in Linear.V4 basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (V4 a) -> m (Vector (V4 a)) # basicUnsafeThaw :: PrimMonad m => Vector (V4 a) -> m (Mutable Vector (PrimState m) (V4 a)) # basicLength :: Vector (V4 a) -> Int # basicUnsafeSlice :: Int -> Int -> Vector (V4 a) -> Vector (V4 a) # basicUnsafeIndexM :: Monad m => Vector (V4 a) -> Int -> m (V4 a) # basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (V4 a) -> Vector (V4 a) -> m () # | |
Num r => Coalgebra r (E V4) | |
Unbox a => MVector MVector (V4 a) | |
Defined in Linear.V4 basicLength :: MVector s (V4 a) -> Int # basicUnsafeSlice :: Int -> Int -> MVector s (V4 a) -> MVector s (V4 a) # basicOverlaps :: MVector s (V4 a) -> MVector s (V4 a) -> Bool # basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (V4 a)) # basicInitialize :: PrimMonad m => MVector (PrimState m) (V4 a) -> m () # basicUnsafeReplicate :: PrimMonad m => Int -> V4 a -> m (MVector (PrimState m) (V4 a)) # basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (V4 a) -> Int -> m (V4 a) # basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (V4 a) -> Int -> V4 a -> m () # basicClear :: PrimMonad m => MVector (PrimState m) (V4 a) -> m () # basicSet :: PrimMonad m => MVector (PrimState m) (V4 a) -> V4 a -> m () # basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (V4 a) -> MVector (PrimState m) (V4 a) -> m () # basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (V4 a) -> MVector (PrimState m) (V4 a) -> m () # basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (V4 a) -> Int -> m (MVector (PrimState m) (V4 a)) # | |
i ~ Int => HasLayout V4 (V4 i) Source # | |
Bounded a => Bounded (V4 a) | |
Eq a => Eq (V4 a) | |
Floating a => Floating (V4 a) | |
Fractional a => Fractional (V4 a) | |
Data a => Data (V4 a) | |
Defined in Linear.V4 gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> V4 a -> c (V4 a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (V4 a) # dataTypeOf :: V4 a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (V4 a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (V4 a)) # gmapT :: (forall b. Data b => b -> b) -> V4 a -> V4 a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> V4 a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> V4 a -> r # gmapQ :: (forall d. Data d => d -> u) -> V4 a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> V4 a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> V4 a -> m (V4 a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> V4 a -> m (V4 a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> V4 a -> m (V4 a) # | |
Num a => Num (V4 a) | |
Ord a => Ord (V4 a) | |
Read a => Read (V4 a) | |
Show a => Show (V4 a) | |
Ix a => Ix (V4 a) | |
Generic (V4 a) | |
Semigroup a => Semigroup (V4 a) | |
Monoid a => Monoid (V4 a) | |
Storable a => Storable (V4 a) | |