dense-0.1.0.1: Mutable and immutable dense multidimensional arrays
Copyright(c) Christopher Chalmers
LicenseBSD3
MaintainerChristopher Chalmers
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Dense.TH

Description

Contains QuasiQuotes and TemplateHaskell utilities for creating dense arrays, stencils and fixed length vectors.

The parser for the QuasiQuotes is still a work in progress.

Synopsis

Creating dense arrays

dense :: QuasiQuoter Source #

QuasiQuoter for producing a dense arrays using a custom parser. Values are space separated, while also allowing infix expressions (like 5/7). If you want to apply a function, it should be done in brackets. Supports 1D, 2D and 3D arrays.

The number of rows/columns must be consistent thought out the array.

Examples

Expand
  • 1D arrays are of the following form form. Note these can be used as V1, V2 or V3 arrays.
[dense| 5 -3 1 -3 5 |] :: (R1 f, Vector v a, Num a) => Array v f a
  • 2D arrays are of the following form. Note these can be used as V2 or V3 arrays.
chars :: UArray V2 Char
chars :: [dense|
  'a' 'b' 'c'
  'd' 'e' 'f'
  'g' 'h' 'i'
|]
  • 3D arrays are of the following form. Note the order in which dense formats the array. The array a is such that a ! V3 x y z = "xyz"
a :: BArray V3 String
a = [dense|
  "000" "100" "200"
  "010" "110" "210"
  "020" "120" "220"

  "001" "101" "201"
  "011" "111" "211"
  "021" "121" "221"

  "002" "102" "202"
  "012" "112" "212"
  "022" "122" "222"
|]

Fixed length vector

v :: QuasiQuoter Source #

Type safe QuasiQuoter for fixed length vectors V. Values are space separated. Can be used as expressions or patterns.

[v| x y z w q r |] :: V 6 a

Note this requires DataKinds. Also requires ViewPatterns if v is used as a pattern.

Examples

Expand
>>> let a = [v| 1 2 3 4 5 |]
>>> :t a
a :: Num a => V 5 a
>>> a
V {toVector = [1,2,3,4,5]}
>>> let f [v| a b c d e |] = (a,b,c,d,e)
>>> :t f
f :: V 5 t -> (t, t, t, t, t)
>>> f a
(1,2,3,4,5)

Variables and infix expressions are also allowed. Negative values can be expressed by a leading - with a space before but no space after.

>>> let b x = [v| 1/x 2 / x (succ x)**2 x-2 x - 3 -x |]
>>> b Debug.SimpleReflect.a
V {toVector = [1 / a,2 / a,succ a**2,a - 2,a - 3,negate a]}

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

Expand
  • 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
|]

Stencils from lists

class Shape f => ShapeLift f where Source #

Class of shapes that can be lifted.

This is to prevent orphans for the Lift class.

Methods

liftShape :: Lift a => f a -> Q Exp Source #

lift for Shapes.

liftShape' :: Lift a => f a -> Q Exp Source #

Polymorphic lift for a Shapes.

Instances

Instances details
ShapeLift V4 Source # 
Instance details

Defined in Data.Dense.TH

Methods

liftShape :: Lift a => V4 a -> Q Exp Source #

liftShape' :: Lift a => V4 a -> Q Exp Source #

ShapeLift V3 Source # 
Instance details

Defined in Data.Dense.TH

Methods

liftShape :: Lift a => V3 a -> Q Exp Source #

liftShape' :: Lift a => V3 a -> Q Exp Source #

ShapeLift V2 Source # 
Instance details

Defined in Data.Dense.TH

Methods

liftShape :: Lift a => V2 a -> Q Exp Source #

liftShape' :: Lift a => V2 a -> Q Exp Source #

ShapeLift V1 Source # 
Instance details

Defined in Data.Dense.TH

Methods

liftShape :: Lift a => V1 a -> Q Exp Source #

liftShape' :: Lift a => V1 a -> Q Exp Source #

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 :: [(f Int, a)])) :: Stencil f a

mkStencilTHBy :: ShapeLift f => (a -> Q Exp) -> [(f Int, a)] -> Q Exp Source #

mkStencilTH with a custom lift function for a.