dense-0.1.0.0: Mutable and immutable dense multidimensional arrays

Copyright(c) Christopher Chalmers
LicenseBSD3
MaintainerChristopher Chalmers
Stabilityprovisional
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Dense.Stencil

Contents

Description

Stencils can be used to sum (or any fold) over neighbouring sites to the current position on a Focused.

Synopsis

The Stencil type

newtype Stencil f a Source #

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.

Constructors

Stencil (forall b. (f Int -> a -> b -> b) -> b -> b) 

Instances

Functor (Stencil f) Source # 

Methods

fmap :: (a -> b) -> Stencil f a -> Stencil f b #

(<$) :: a -> Stencil f b -> Stencil f a #

Foldable (Stencil f) Source # 

Methods

fold :: Monoid m => Stencil f m -> 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] #

null :: Stencil f a -> Bool #

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 #

sum :: Num a => Stencil f a -> a #

product :: Num a => Stencil f a -> a #

FoldableWithIndex (f Int) (Stencil f) Source # 

Methods

ifoldMap :: Monoid m => (f Int -> a -> m) -> Stencil f a -> m #

ifolded :: (Indexable (f Int) p, Contravariant f, Applicative f) => p a (f a) -> Stencil f a -> f (Stencil f 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 # 

Methods

showsPrec :: Int -> Stencil f a -> ShowS #

show :: Stencil f a -> String #

showList :: [Stencil f a] -> ShowS #

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).

mkStencilUnboxed :: (Unbox (f Int), Unbox a) => [(f Int, a)] -> Stencil f a Source #

Make a stencil folding over an unboxed vector from the list.

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.