cifl-math-library-1.1.1.0: Math libraries
Safe HaskellTrustworthy
LanguageHaskell2010

Math.Matrix.QuasiQuoter

Description

This module provides QuasiQuoter syntactic sugar for matrices. based on GHC's Language.Haskell.TH quasi quoters.

To use these you should use: {-# LANGUAGE QuasiQuotes #-}

Or corresponding compiler option "-XQuasiQuotes".

The syntax is:

[mat3x4|1 2 3 4;3 4 5 6;5 6 7 8|] :: (Vector3 :*: Vector4) Integer
[double2x2|3.4 5.6;6.7 8.8|] :: (Vector2 :*: Vector2) Double

The semicolons can be replaced with new line character to produce the matrix layout in the code, e.g.:

 [mat4x4|1 1 1 1
         2 2 2 2
         3 3 3 3
         4 4 4 4|]

The code supports matrices up to 4x4 matrices. For larger matrices, you should provide a vector type, and use e.g.

mat7x3 = parseMat (const () :: Vec 7 (Vec 3 Integer) -> ())
dbl7x2 = parseDbl (const () :: Vec 13 (Vec 2 Double) -> ())
Synopsis

Documentation

notQuote :: b -> Q a Source #

mat1x1 :: QuasiQuoter Source #

Quasiquoters for various matrix sizes

mat2x1 :: QuasiQuoter Source #

Quasiquoters for various matrix sizes

mat3x1 :: QuasiQuoter Source #

Quasiquoters for various matrix sizes

mat4x1 :: QuasiQuoter Source #

Quasiquoters for various matrix sizes

mat1x2 :: QuasiQuoter Source #

Quasiquoters for various matrix sizes

mat2x2 :: QuasiQuoter Source #

Quasiquoters for various matrix sizes

mat3x2 :: QuasiQuoter Source #

Quasiquoters for various matrix sizes

mat4x2 :: QuasiQuoter Source #

Quasiquoters for various matrix sizes

mat1x3 :: QuasiQuoter Source #

Quasiquoters for various matrix sizes

mat2x3 :: QuasiQuoter Source #

Quasiquoters for various matrix sizes

mat3x3 :: QuasiQuoter Source #

Quasiquoters for various matrix sizes

mat4x3 :: QuasiQuoter Source #

Quasiquoters for various matrix sizes

mat1x4 :: QuasiQuoter Source #

Quasiquoters for various matrix sizes

mat2x4 :: QuasiQuoter Source #

Quasiquoters for various matrix sizes

mat3x4 :: QuasiQuoter Source #

Quasiquoters for various matrix sizes

mat4x4 :: QuasiQuoter Source #

Quasiquoters for various matrix sizes

parseMat :: (CoordinateSpace (Scalar (f (g a))), CoordinateSpace (f (g a)), Lift (f (g a)), Scalar (Scalar (f (g a))) ~ Integer) => (f (g a) -> ()) -> String -> Q Exp Source #

parseDbl :: (CoordinateSpace (Scalar (f (g a))), CoordinateSpace (f (g a)), Lift (f (g a)), Scalar (Scalar (f (g a))) ~ Double) => (f (g a) -> ()) -> String -> Q Exp Source #

stringLitP :: MonadFail m => Token -> m Text Source #

floatLitP :: MonadFail m => Token -> m Double Source #

numberP :: MonadFail m => Token -> m Integer Source #

parseToMatrix :: MonadFail m => (Token -> ParseM a) -> Text -> m ((List :*: List) a) Source #

parseMatrix :: (Token -> ParseM a) -> ParseM ((List :*: List) a) Source #

Orphan instances

Lift a => Lift (Vector1 a :: Type) Source # 
Instance details

Methods

lift :: Quote m => Vector1 a -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Vector1 a -> Code m (Vector1 a) #

Lift a => Lift (Vector2 a :: Type) Source # 
Instance details

Methods

lift :: Quote m => Vector2 a -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Vector2 a -> Code m (Vector2 a) #

Lift a => Lift (Vector3 a :: Type) Source # 
Instance details

Methods

lift :: Quote m => Vector3 a -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Vector3 a -> Code m (Vector3 a) #

Lift a => Lift (Vector4 a :: Type) Source # 
Instance details

Methods

lift :: Quote m => Vector4 a -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Vector4 a -> Code m (Vector4 a) #

Lift ((Vector3 :*: Vector3) Integer) Source # 
Instance details

Methods

lift :: Quote m => (Vector3 :*: Vector3) Integer -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => (Vector3 :*: Vector3) Integer -> Code m ((Vector3 :*: Vector3) Integer) #

Lift ((List :*: List) Integer) Source # 
Instance details

Methods

lift :: Quote m => (List :*: List) Integer -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => (List :*: List) Integer -> Code m ((List :*: List) Integer) #