summaryrefslogtreecommitdiff
path: root/packages
diff options
context:
space:
mode:
authorAlberto Ruiz <aruiz@um.es>2014-06-16 18:24:56 +0200
committerAlberto Ruiz <aruiz@um.es>2014-06-16 18:24:56 +0200
commit315b1cd732eb4ef7ae511a537a496d1f17ae017f (patch)
tree0fb9a52dac6304c50a7e2cc4a26d0b81e7ed9f8d /packages
parent25973e7498af7649c614b6f05c6c3b8cc3f24637 (diff)
Floating instances
Diffstat (limited to 'packages')
-rw-r--r--packages/base/src/Numeric/LinearAlgebra/Static/Internal.hs83
1 files changed, 80 insertions, 3 deletions
diff --git a/packages/base/src/Numeric/LinearAlgebra/Static/Internal.hs b/packages/base/src/Numeric/LinearAlgebra/Static/Internal.hs
index b13c264..7968d77 100644
--- a/packages/base/src/Numeric/LinearAlgebra/Static/Internal.hs
+++ b/packages/base/src/Numeric/LinearAlgebra/Static/Internal.hs
@@ -27,7 +27,8 @@ module Numeric.LinearAlgebra.Static.Internal where
27 27
28 28
29import GHC.TypeLits 29import GHC.TypeLits
30import Numeric.LinearAlgebra.HMatrix as LA 30import qualified Numeric.LinearAlgebra.HMatrix as LA
31import Numeric.LinearAlgebra.HMatrix hiding (konst)
31import Data.Packed as D 32import Data.Packed as D
32import Data.Packed.ST 33import Data.Packed.ST
33import Data.Proxy(Proxy) 34import Data.Proxy(Proxy)
@@ -52,10 +53,10 @@ lift2F f (Dim u) (Dim v) = Dim (f u v)
52-------------------------------------------------------------------------------- 53--------------------------------------------------------------------------------
53 54
54newtype R n = R (Dim n (Vector ℝ)) 55newtype R n = R (Dim n (Vector ℝ))
55 deriving (Num,Fractional) 56 deriving (Num,Fractional,Floating)
56 57
57newtype C n = C (Dim n (Vector ℂ)) 58newtype C n = C (Dim n (Vector ℂ))
58 deriving (Num,Fractional) 59 deriving (Num,Fractional,Floating)
59 60
60newtype L m n = L (Dim m (Dim n (Matrix ℝ))) 61newtype L m n = L (Dim m (Dim n (Matrix ℝ)))
61 62
@@ -313,6 +314,25 @@ instance (Num (Vector t), Num (Matrix t), Numeric t) => Fractional (Dim n (Vecto
313 fromRational x = Dim (fromRational x) 314 fromRational x = Dim (fromRational x)
314 (/) = lift2F (/) 315 (/) = lift2F (/)
315 316
317instance (Floating (Vector t), Numeric t) => Floating (Dim n (Vector t)) where
318 sin = lift1F sin
319 cos = lift1F cos
320 tan = lift1F tan
321 asin = lift1F asin
322 acos = lift1F acos
323 atan = lift1F atan
324 sinh = lift1F sinh
325 cosh = lift1F cosh
326 tanh = lift1F tanh
327 asinh = lift1F asinh
328 acosh = lift1F acosh
329 atanh = lift1F atanh
330 exp = lift1F exp
331 log = lift1F log
332 sqrt = lift1F sqrt
333 (**) = lift2F (**)
334 pi = Dim pi
335
316 336
317instance (Num (Matrix t), Numeric t) => Num (Dim m (Dim n (Matrix t))) 337instance (Num (Matrix t), Numeric t) => Num (Dim m (Dim n (Matrix t)))
318 where 338 where
@@ -329,6 +349,25 @@ instance (Num (Vector t), Num (Matrix t), Numeric t) => Fractional (Dim m (Dim n
329 fromRational x = Dim (Dim (fromRational x)) 349 fromRational x = Dim (Dim (fromRational x))
330 (/) = (lift2F.lift2F) (/) 350 (/) = (lift2F.lift2F) (/)
331 351
352instance (Num (Vector t), Floating (Matrix t), Numeric t) => Floating (Dim m (Dim n (Matrix t))) where
353 sin = (lift1F . lift1F) sin
354 cos = (lift1F . lift1F) cos
355 tan = (lift1F . lift1F) tan
356 asin = (lift1F . lift1F) asin
357 acos = (lift1F . lift1F) acos
358 atan = (lift1F . lift1F) atan
359 sinh = (lift1F . lift1F) sinh
360 cosh = (lift1F . lift1F) cosh
361 tanh = (lift1F . lift1F) tanh
362 asinh = (lift1F . lift1F) asinh
363 acosh = (lift1F . lift1F) acosh
364 atanh = (lift1F . lift1F) atanh
365 exp = (lift1F . lift1F) exp
366 log = (lift1F . lift1F) log
367 sqrt = (lift1F . lift1F) sqrt
368 (**) = (lift2F . lift2F) (**)
369 pi = Dim (Dim pi)
370
332-------------------------------------------------------------------------------- 371--------------------------------------------------------------------------------
333 372
334 373
@@ -359,6 +398,25 @@ instance (KnownNat n, KnownNat m) => Fractional (L n m)
359 fromRational = L . Dim . Dim . fromRational 398 fromRational = L . Dim . Dim . fromRational
360 (/) = lift2LD (/) 399 (/) = lift2LD (/)
361 400
401instance (KnownNat n, KnownNat m) => Floating (L n m) where
402 sin = lift1L sin
403 cos = lift1L cos
404 tan = lift1L tan
405 asin = lift1L asin
406 acos = lift1L acos
407 atan = lift1L atan
408 sinh = lift1L sinh
409 cosh = lift1L cosh
410 tanh = lift1L tanh
411 asinh = lift1L asinh
412 acosh = lift1L acosh
413 atanh = lift1L atanh
414 exp = lift1L exp
415 log = lift1L log
416 sqrt = lift1L sqrt
417 (**) = lift2LD (**)
418 pi = konst pi
419
362-------------------------------------------------------------------------------- 420--------------------------------------------------------------------------------
363 421
364adaptDiagC f a@(isDiagC -> Just _) b | isFullC b = f (mkM (extract a)) b 422adaptDiagC f a@(isDiagC -> Just _) b | isFullC b = f (mkM (extract a)) b
@@ -386,6 +444,25 @@ instance (KnownNat n, KnownNat m) => Fractional (M n m)
386 fromRational = M . Dim . Dim . fromRational 444 fromRational = M . Dim . Dim . fromRational
387 (/) = lift2MD (/) 445 (/) = lift2MD (/)
388 446
447instance (KnownNat n, KnownNat m) => Floating (M n m) where
448 sin = lift1M sin
449 cos = lift1M cos
450 tan = lift1M tan
451 asin = lift1M asin
452 acos = lift1M acos
453 atan = lift1M atan
454 sinh = lift1M sinh
455 cosh = lift1M cosh
456 tanh = lift1M tanh
457 asinh = lift1M asinh
458 acosh = lift1M acosh
459 atanh = lift1M atanh
460 exp = lift1M exp
461 log = lift1M log
462 sqrt = lift1M sqrt
463 (**) = lift2MD (**)
464 pi = M pi
465
389-------------------------------------------------------------------------------- 466--------------------------------------------------------------------------------
390 467
391 468