{-# LANGUAGE TypeOperators, TypeFamilies, UndecidableInstances
, FlexibleInstances, MultiParamTypeClasses, CPP #-}
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# OPTIONS_GHC -Wall -fno-warn-orphans #-}
module Data.Basis (HasBasis(..), linearCombo, recompose) where
import Control.Arrow (first)
import Data.Ratio
import Foreign.C.Types (CFloat, CDouble)
import Data.VectorSpace
import Data.VectorSpace.Generic
import qualified GHC.Generics as Gnrx
import GHC.Generics (Generic, (:*:)(..))
class VectorSpace v => HasBasis v where
type Basis v :: *
type Basis v = Basis (VRep v)
basisValue :: Basis v -> v
default basisValue :: (Generic v, HasBasis (VRep v), Basis (VRep v) ~ Basis v)
=> Basis v -> v
basisValue Basis v
b = forall a x. Generic a => Rep a x -> a
Gnrx.to (forall v. HasBasis v => Basis v -> v
basisValue Basis v
b :: VRep v)
decompose :: v -> [(Basis v, Scalar v)]
default decompose :: ( Generic v, HasBasis (VRep v)
, Scalar (VRep v) ~ Scalar v, Basis (VRep v) ~ Basis v )
=> v -> [(Basis v, Scalar v)]
decompose v
v = forall v. HasBasis v => v -> [(Basis v, Scalar v)]
decompose (forall a x. Generic a => a -> Rep a x
Gnrx.from v
v :: VRep v)
decompose' :: v -> (Basis v -> Scalar v)
default decompose' :: ( Generic v, HasBasis (VRep v)
, Scalar (VRep v) ~ Scalar v, Basis (VRep v) ~ Basis v )
=> v -> Basis v -> Scalar v
decompose' v
v = forall v. HasBasis v => v -> Basis v -> Scalar v
decompose' (forall a x. Generic a => a -> Rep a x
Gnrx.from v
v :: VRep v)
recompose :: HasBasis v => [(Basis v, Scalar v)] -> v
recompose :: forall v. HasBasis v => [(Basis v, Scalar v)] -> v
recompose = forall v. VectorSpace v => [(v, Scalar v)] -> v
linearCombo forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (b, d) (c, d)
first forall v. HasBasis v => Basis v -> v
basisValue)
#define ScalarTypeCon(con,t) \
instance con => HasBasis (t) where \
{ type Basis (t) = () \
; basisValue () = 1 \
; decompose s = [((),s)] \
; decompose' s = const s }
#define ScalarType(t) ScalarTypeCon((),t)
ScalarType(Float)
ScalarType(CFloat)
ScalarType(Double)
ScalarType(CDouble)
ScalarTypeCon(Integral a, Ratio a)
instance ( HasBasis u, s ~ Scalar u
, HasBasis v, s ~ Scalar v )
=> HasBasis (u,v) where
type Basis (u,v) = Basis u `Either` Basis v
basisValue :: Basis (u, v) -> (u, v)
basisValue (Left Basis u
a) = (forall v. HasBasis v => Basis v -> v
basisValue Basis u
a, forall v. AdditiveGroup v => v
zeroV)
basisValue (Right Basis v
b) = (forall v. AdditiveGroup v => v
zeroV, forall v. HasBasis v => Basis v -> v
basisValue Basis v
b)
decompose :: (u, v) -> [(Basis (u, v), Scalar (u, v))]
decompose (u
u,v
v) = forall w b. HasBasis w => (Basis w -> b) -> w -> [(b, Scalar w)]
decomp2 forall a b. a -> Either a b
Left u
u forall a. [a] -> [a] -> [a]
++ forall w b. HasBasis w => (Basis w -> b) -> w -> [(b, Scalar w)]
decomp2 forall a b. b -> Either a b
Right v
v
decompose' :: (u, v) -> Basis (u, v) -> Scalar (u, v)
decompose' (u
u,v
v) = forall v. HasBasis v => v -> Basis v -> Scalar v
decompose' u
u forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
`either` forall v. HasBasis v => v -> Basis v -> Scalar v
decompose' v
v
decomp2 :: HasBasis w => (Basis w -> b) -> w -> [(b, Scalar w)]
decomp2 :: forall w b. HasBasis w => (Basis w -> b) -> w -> [(b, Scalar w)]
decomp2 Basis w -> b
inject = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (b, d) (c, d)
first Basis w -> b
inject) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall v. HasBasis v => v -> [(Basis v, Scalar v)]
decompose
instance ( HasBasis u, s ~ Scalar u
, HasBasis v, s ~ Scalar v
, HasBasis w, s ~ Scalar w )
=> HasBasis (u,v,w) where
type Basis (u,v,w) = Basis (u,(v,w))
basisValue :: Basis (u, v, w) -> (u, v, w)
basisValue = forall a b c. (a, (b, c)) -> (a, b, c)
unnest3 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall v. HasBasis v => Basis v -> v
basisValue
decompose :: (u, v, w) -> [(Basis (u, v, w), Scalar (u, v, w))]
decompose = forall v. HasBasis v => v -> [(Basis v, Scalar v)]
decompose forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b c. (a, b, c) -> (a, (b, c))
nest3
decompose' :: (u, v, w) -> Basis (u, v, w) -> Scalar (u, v, w)
decompose' = forall v. HasBasis v => v -> Basis v -> Scalar v
decompose' forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b c. (a, b, c) -> (a, (b, c))
nest3
unnest3 :: (a,(b,c)) -> (a,b,c)
unnest3 :: forall a b c. (a, (b, c)) -> (a, b, c)
unnest3 (a
a,(b
b,c
c)) = (a
a,b
b,c
c)
nest3 :: (a,b,c) -> (a,(b,c))
nest3 :: forall a b c. (a, b, c) -> (a, (b, c))
nest3 (a
a,b
b,c
c) = (a
a,(b
b,c
c))
instance HasBasis a => HasBasis (Gnrx.Rec0 a s) where
type Basis (Gnrx.Rec0 a s) = Basis a
basisValue :: Basis (Rec0 a s) -> Rec0 a s
basisValue = forall k i c (p :: k). c -> K1 i c p
Gnrx.K1 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall v. HasBasis v => Basis v -> v
basisValue
decompose :: Rec0 a s -> [(Basis (Rec0 a s), Scalar (Rec0 a s))]
decompose = forall v. HasBasis v => v -> [(Basis v, Scalar v)]
decompose forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall k i c (p :: k). K1 i c p -> c
Gnrx.unK1
decompose' :: Rec0 a s -> Basis (Rec0 a s) -> Scalar (Rec0 a s)
decompose' = forall v. HasBasis v => v -> Basis v -> Scalar v
decompose' forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall k i c (p :: k). K1 i c p -> c
Gnrx.unK1
instance HasBasis (f p) => HasBasis (Gnrx.M1 i c f p) where
type Basis (Gnrx.M1 i c f p) = Basis (f p)
basisValue :: Basis (M1 i c f p) -> M1 i c f p
basisValue = forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
Gnrx.M1 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall v. HasBasis v => Basis v -> v
basisValue
decompose :: M1 i c f p -> [(Basis (M1 i c f p), Scalar (M1 i c f p))]
decompose = forall v. HasBasis v => v -> [(Basis v, Scalar v)]
decompose forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall k i (c :: Meta) (f :: k -> *) (p :: k). M1 i c f p -> f p
Gnrx.unM1
decompose' :: M1 i c f p -> Basis (M1 i c f p) -> Scalar (M1 i c f p)
decompose' = forall v. HasBasis v => v -> Basis v -> Scalar v
decompose' forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall k i (c :: Meta) (f :: k -> *) (p :: k). M1 i c f p -> f p
Gnrx.unM1
instance (HasBasis (f p), HasBasis (g p), Scalar (f p) ~ Scalar (g p))
=> HasBasis ((f :*: g) p) where
type Basis ((f:*:g) p) = Either (Basis (f p)) (Basis (g p))
basisValue :: Basis ((:*:) f g p) -> (:*:) f g p
basisValue (Left Basis (f p)
bf) = forall v. HasBasis v => Basis v -> v
basisValue Basis (f p)
bf forall k (f :: k -> *) (g :: k -> *) (p :: k).
f p -> g p -> (:*:) f g p
:*: forall v. AdditiveGroup v => v
zeroV
basisValue (Right Basis (g p)
bg) = forall v. AdditiveGroup v => v
zeroV forall k (f :: k -> *) (g :: k -> *) (p :: k).
f p -> g p -> (:*:) f g p
:*: forall v. HasBasis v => Basis v -> v
basisValue Basis (g p)
bg
decompose :: (:*:) f g p -> [(Basis ((:*:) f g p), Scalar ((:*:) f g p))]
decompose (f p
u:*:g p
v) = forall w b. HasBasis w => (Basis w -> b) -> w -> [(b, Scalar w)]
decomp2 forall a b. a -> Either a b
Left f p
u forall a. [a] -> [a] -> [a]
++ forall w b. HasBasis w => (Basis w -> b) -> w -> [(b, Scalar w)]
decomp2 forall a b. b -> Either a b
Right g p
v
decompose' :: (:*:) f g p -> Basis ((:*:) f g p) -> Scalar ((:*:) f g p)
decompose' (f p
u:*:g p
v) = forall v. HasBasis v => v -> Basis v -> Scalar v
decompose' f p
u forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
`either` forall v. HasBasis v => v -> Basis v -> Scalar v
decompose' g p
v