Skip to content

Commit

Permalink
added expm and logm; the justification is again that they may only be…
Browse files Browse the repository at this point in the history
… called on square matrices.
  • Loading branch information
mstksg committed May 25, 2016
1 parent 5a23359 commit cd6caa8
Show file tree
Hide file tree
Showing 2 changed files with 31 additions and 2 deletions.
11 changes: 11 additions & 0 deletions packages/base/src/Internal/Static.hs
Original file line number Diff line number Diff line change
Expand Up @@ -567,6 +567,17 @@ instance KnownNat n => Disp (C n)

--------------------------------------------------------------------------------

overMatL' :: (KnownNat m, KnownNat n)
=> (LA.Matrix -> LA.Matrix ) -> L m n -> L m n
overMatL' f = mkL . f . unwrap
{-# INLINE overMatL' #-}

overMatM' :: (KnownNat m, KnownNat n)
=> (LA.Matrix -> LA.Matrix ) -> M m n -> M m n
overMatM' f = mkM . f . unwrap
{-# INLINE overMatM' #-}


#else

module Numeric.LinearAlgebra.Static.Internal where
Expand Down
22 changes: 20 additions & 2 deletions packages/base/src/Numeric/LinearAlgebra/Static.hs
Original file line number Diff line number Diff line change
Expand Up @@ -537,6 +537,8 @@ class Domain field vec mat | mat -> vec field, vec -> mat field, field -> mat ve
zipWithVector :: forall n. KnownNat n => (field -> field -> field) -> vec n -> vec n -> vec n
det :: forall n. KnownNat n => mat n n -> field
invlndet :: forall n. KnownNat n => mat n n -> (mat n n, (field, field))
expm :: forall n. KnownNat n => mat n n -> mat n n
sqrtm :: forall n. KnownNat n => mat n n -> mat n n


instance Domain R L
Expand All @@ -552,6 +554,8 @@ instance Domain ℝ R L
zipWithVector = zipWithR
det = detL
invlndet = invlndetL
expm = expmL
sqrtm = sqrtmL

instance Domain C M
where
Expand All @@ -566,6 +570,8 @@ instance Domain ℂ C M
zipWithVector = zipWithC
det = detM
invlndet = invlndetM
expm = expmM
sqrtm = sqrtmM

--------------------------------------------------------------------------------

Expand Down Expand Up @@ -615,14 +621,20 @@ zipWithR :: KnownNat n => (ℝ -> ℝ -> ℝ) -> R n -> R n -> R n
zipWithR f (extract -> x) (extract -> y) = mkR (LA.zipVectorWith f x y)

mapL :: (KnownNat n, KnownNat m) => ( -> ) -> L n m -> L n m
mapL f (unwrap -> m) = mkL (LA.cmap f m)
mapL f = overMatL' (LA.cmap f)

detL :: KnownNat n => Sq n ->
detL = LA.det . unwrap

invlndetL :: KnownNat n => Sq n -> (L n n, (, ))
invlndetL = first mkL . LA.invlndet . unwrap

expmL :: KnownNat n => Sq n -> Sq n
expmL = overMatL' LA.expm

sqrtmL :: KnownNat n => Sq n -> Sq n
sqrtmL = overMatL' LA.sqrtm

--------------------------------------------------------------------------------

mulC :: forall m k n. (KnownNat m, KnownNat k, KnownNat n) => M m k -> M k n -> M m n
Expand Down Expand Up @@ -671,14 +683,20 @@ zipWithC :: KnownNat n => (ℂ -> ℂ -> ℂ) -> C n -> C n -> C n
zipWithC f (extract -> x) (extract -> y) = mkC (LA.zipVectorWith f x y)

mapM' :: (KnownNat n, KnownNat m) => ( -> ) -> M n m -> M n m
mapM' f (unwrap -> m) = mkM (LA.cmap f m)
mapM' f = overMatM' (LA.cmap f)

detM :: KnownNat n => M n n ->
detM = LA.det . unwrap

invlndetM :: KnownNat n => M n n -> (M n n, (, ))
invlndetM = first mkM . LA.invlndet . unwrap

expmM :: KnownNat n => M n n -> M n n
expmM = overMatM' LA.expm

sqrtmM :: KnownNat n => M n n -> M n n
sqrtmM = overMatM' LA.sqrtm


--------------------------------------------------------------------------------

Expand Down

0 comments on commit cd6caa8

Please sign in to comment.