hmatrix-static-0.3: hmatrix with vector and matrix sizes encoded in typesSource codeContentsIndex
Data.Packed.Static.Syntax
Portabilityportable
Stabilityexperimental
MaintainerReiner Pope <reiner.pope@gmail.com>
Contents
Matrix views
Vector views
Description

QuasiQuoting for matrices and vectors.

BIG WARNING: the expression quasiquoters for matrices and vectors are broken for infix expressions. All operators will be assumed to be left infix with infix level 9. To avoid unexpected parses, fully parenthesise all infix expressions.

Synopsis
mat :: QuasiQuoter
matU :: QuasiQuoter
vec :: QuasiQuoter
vecU :: QuasiQuoter
data MatView n t
viewMat :: Element t => Matrix (m, n) t -> MatView (m, n) t
data VecView n t
viewVec :: Storable t => Vector n t -> VecView n t
Documentation
mat :: QuasiQuoterSource

The matrix quasiquoter for expressions and patterns.

  • Elements on the same row are separated by commas; rows themselves are separated by semicolons. All whitespace is optional
  • The expression quasiquoter allows arbitrary Haskell expressions as its elements; the pattern quasiquoter requires that each element is a variable.
  • Using the quasiquoter for patterns requires that you use the viewMat view pattern first (this is a workaround since Template Haskell doesn't yet support view patterns).

For example,

 example1 :: (Element t) => Matrix (D2,D3) t -> Matrix (D2,D2) t
 example1 (viewMat -> [$mat|a, b, c;
                            d, e, f|]) = [$mat|a+b,   b+c;
                                               sin c, f  |]
matU :: QuasiQuoterSource

Quasiquoter for matrices of Unknown size. We should just use [$matU|<text>|] as shorthand for forgetShapeU [$mat|<text>|].

No pattern quasiquoter exists, and I currently have no plans to introduce one.

vec :: QuasiQuoterSource

The vector quasiquoter for expressions and patterns. This is very similar to the mat quasiquoter.

  • Elements are separated by commas; whitespace is ignored.
  • The expression quasiquoter allows arbitrary Haskell expressions for each element; the pattern quasiquoter requires that each element is a variable pattern.
  • The pattern quasiquoter must be preceeded by a the viewVec view pattern.

For example,

 example2 :: (Storable t, Num t) => Vector D2 t -> Vector D3 t
 example2 (viewVec -> [$vec|a, b|]) = [$vec|a*b, 5, 7|]
vecU :: QuasiQuoterSource
Quasiquoter for vectors of unknown lengths. Like matU, [$vecU|<text>|] is just shorthand for forgetShapeU [$vec|<text>|].
Matrix views
data MatView n t Source
Required for the mat pattern quasiquoter. See mat.
viewMat :: Element t => Matrix (m, n) t -> MatView (m, n) tSource
Required for the mat pattern quasiquoter. See mat.
Vector views
data VecView n t Source
Required for the vec quasiquoter. See vec.
viewVec :: Storable t => Vector n t -> VecView n tSource
Required for the vec quasiquoter. See vec.
Produced by Haddock version 2.4.2