{-# LANGUAGE CPP #-}
#if __GLASGOW_HASKELL__ >= 708

{-# LANGUAGE DataKinds #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE Rank2Types #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE DeriveGeneric #-}

{-# OPTIONS_GHC -fno-warn-missing-signatures #-}

{- |
Module      :  Internal.Static
Copyright   :  (c) Alberto Ruiz 2006-14
License     :  BSD3
Stability   :  provisional

-}

module Internal.Static where


import GHC.TypeLits
import qualified Numeric.LinearAlgebra as LA
import Numeric.LinearAlgebra hiding (konst,size,R,C)
import Internal.Vector as D hiding (R,C)
import Internal.ST
import Control.DeepSeq
import Data.Proxy(Proxy)
import Foreign.Storable(Storable)
import Text.Printf

import Data.Binary
import GHC.Generics (Generic)
import Data.Proxy (Proxy(..))

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

type  = Double
type  = Complex Double

newtype Dim (n :: Nat) t = Dim t
  deriving (Int -> Dim n t -> ShowS
[Dim n t] -> ShowS
Dim n t -> String
(Int -> Dim n t -> ShowS)
-> (Dim n t -> String) -> ([Dim n t] -> ShowS) -> Show (Dim n t)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall (n :: Nat) t. Show t => Int -> Dim n t -> ShowS
forall (n :: Nat) t. Show t => [Dim n t] -> ShowS
forall (n :: Nat) t. Show t => Dim n t -> String
showList :: [Dim n t] -> ShowS
$cshowList :: forall (n :: Nat) t. Show t => [Dim n t] -> ShowS
show :: Dim n t -> String
$cshow :: forall (n :: Nat) t. Show t => Dim n t -> String
showsPrec :: Int -> Dim n t -> ShowS
$cshowsPrec :: forall (n :: Nat) t. Show t => Int -> Dim n t -> ShowS
Show, (forall x. Dim n t -> Rep (Dim n t) x)
-> (forall x. Rep (Dim n t) x -> Dim n t) -> Generic (Dim n t)
forall x. Rep (Dim n t) x -> Dim n t
forall x. Dim n t -> Rep (Dim n t) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (n :: Nat) t x. Rep (Dim n t) x -> Dim n t
forall (n :: Nat) t x. Dim n t -> Rep (Dim n t) x
$cto :: forall (n :: Nat) t x. Rep (Dim n t) x -> Dim n t
$cfrom :: forall (n :: Nat) t x. Dim n t -> Rep (Dim n t) x
Generic)

instance (KnownNat n, Binary a) => Binary (Dim n a) where
  get :: Get (Dim n a)
get = do
    Integer
k <- Get Integer
forall t. Binary t => Get t
get
    let n :: Integer
n = Proxy n -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (Proxy n
forall k (t :: k). Proxy t
Proxy :: Proxy n)
    if Integer
n Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== Integer
k
      then a -> Dim n a
forall (n :: Nat) t. t -> Dim n t
Dim (a -> Dim n a) -> Get a -> Get (Dim n a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get a
forall t. Binary t => Get t
get
      else String -> Get (Dim n a)
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String
"Expected dimension " String -> ShowS
forall a. [a] -> [a] -> [a]
++ (Integer -> String
forall a. Show a => a -> String
show Integer
n) String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
", but found dimension " String -> ShowS
forall a. [a] -> [a] -> [a]
++ (Integer -> String
forall a. Show a => a -> String
show Integer
k))

  put :: Dim n a -> Put
put (Dim a
x) = do
    Integer -> Put
forall t. Binary t => t -> Put
put (Proxy n -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (Proxy n
forall k (t :: k). Proxy t
Proxy :: Proxy n))
    a -> Put
forall t. Binary t => t -> Put
put a
x

lift1F
  :: (c t -> c t)
  -> Dim n (c t) -> Dim n (c t)
lift1F :: (c t -> c t) -> Dim n (c t) -> Dim n (c t)
lift1F c t -> c t
f (Dim c t
v) = c t -> Dim n (c t)
forall (n :: Nat) t. t -> Dim n t
Dim (c t -> c t
f c t
v)

lift2F
  :: (c t -> c t -> c t)
  -> Dim n (c t) -> Dim n (c t) -> Dim n (c t)
lift2F :: (c t -> c t -> c t) -> Dim n (c t) -> Dim n (c t) -> Dim n (c t)
lift2F c t -> c t -> c t
f (Dim c t
u) (Dim c t
v) = c t -> Dim n (c t)
forall (n :: Nat) t. t -> Dim n t
Dim (c t -> c t -> c t
f c t
u c t
v)

instance NFData t => NFData (Dim n t) where
    rnf :: Dim n t -> ()
rnf (Dim (t -> t
forall a. NFData a => a -> a
force -> !t
_)) = ()

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

newtype R n = R (Dim n (Vector ))
  deriving (Integer -> R n
R n -> R n
R n -> R n -> R n
(R n -> R n -> R n)
-> (R n -> R n -> R n)
-> (R n -> R n -> R n)
-> (R n -> R n)
-> (R n -> R n)
-> (R n -> R n)
-> (Integer -> R n)
-> Num (R n)
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
forall (n :: Nat). Integer -> R n
forall (n :: Nat). R n -> R n
forall (n :: Nat). R n -> R n -> R n
fromInteger :: Integer -> R n
$cfromInteger :: forall (n :: Nat). Integer -> R n
signum :: R n -> R n
$csignum :: forall (n :: Nat). R n -> R n
abs :: R n -> R n
$cabs :: forall (n :: Nat). R n -> R n
negate :: R n -> R n
$cnegate :: forall (n :: Nat). R n -> R n
* :: R n -> R n -> R n
$c* :: forall (n :: Nat). R n -> R n -> R n
- :: R n -> R n -> R n
$c- :: forall (n :: Nat). R n -> R n -> R n
+ :: R n -> R n -> R n
$c+ :: forall (n :: Nat). R n -> R n -> R n
Num,Num (R n)
Num (R n)
-> (R n -> R n -> R n)
-> (R n -> R n)
-> (Rational -> R n)
-> Fractional (R n)
Rational -> R n
R n -> R n
R n -> R n -> R n
forall a.
Num a
-> (a -> a -> a) -> (a -> a) -> (Rational -> a) -> Fractional a
forall (n :: Nat). Num (R n)
forall (n :: Nat). Rational -> R n
forall (n :: Nat). R n -> R n
forall (n :: Nat). R n -> R n -> R n
fromRational :: Rational -> R n
$cfromRational :: forall (n :: Nat). Rational -> R n
recip :: R n -> R n
$crecip :: forall (n :: Nat). R n -> R n
/ :: R n -> R n -> R n
$c/ :: forall (n :: Nat). R n -> R n -> R n
$cp1Fractional :: forall (n :: Nat). Num (R n)
Fractional,Fractional (R n)
R n
Fractional (R n)
-> R n
-> (R n -> R n)
-> (R n -> R n)
-> (R n -> R n)
-> (R n -> R n -> R n)
-> (R n -> R n -> R n)
-> (R n -> R n)
-> (R n -> R n)
-> (R n -> R n)
-> (R n -> R n)
-> (R n -> R n)
-> (R n -> R n)
-> (R n -> R n)
-> (R n -> R n)
-> (R n -> R n)
-> (R n -> R n)
-> (R n -> R n)
-> (R n -> R n)
-> (R n -> R n)
-> (R n -> R n)
-> (R n -> R n)
-> (R n -> R n)
-> Floating (R n)
R n -> R n
R n -> R n -> R n
forall a.
Fractional a
-> a
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> Floating a
forall (n :: Nat). Fractional (R n)
forall (n :: Nat). R n
forall (n :: Nat). R n -> R n
forall (n :: Nat). R n -> R n -> R n
log1mexp :: R n -> R n
$clog1mexp :: forall (n :: Nat). R n -> R n
log1pexp :: R n -> R n
$clog1pexp :: forall (n :: Nat). R n -> R n
expm1 :: R n -> R n
$cexpm1 :: forall (n :: Nat). R n -> R n
log1p :: R n -> R n
$clog1p :: forall (n :: Nat). R n -> R n
atanh :: R n -> R n
$catanh :: forall (n :: Nat). R n -> R n
acosh :: R n -> R n
$cacosh :: forall (n :: Nat). R n -> R n
asinh :: R n -> R n
$casinh :: forall (n :: Nat). R n -> R n
tanh :: R n -> R n
$ctanh :: forall (n :: Nat). R n -> R n
cosh :: R n -> R n
$ccosh :: forall (n :: Nat). R n -> R n
sinh :: R n -> R n
$csinh :: forall (n :: Nat). R n -> R n
atan :: R n -> R n
$catan :: forall (n :: Nat). R n -> R n
acos :: R n -> R n
$cacos :: forall (n :: Nat). R n -> R n
asin :: R n -> R n
$casin :: forall (n :: Nat). R n -> R n
tan :: R n -> R n
$ctan :: forall (n :: Nat). R n -> R n
cos :: R n -> R n
$ccos :: forall (n :: Nat). R n -> R n
sin :: R n -> R n
$csin :: forall (n :: Nat). R n -> R n
logBase :: R n -> R n -> R n
$clogBase :: forall (n :: Nat). R n -> R n -> R n
** :: R n -> R n -> R n
$c** :: forall (n :: Nat). R n -> R n -> R n
sqrt :: R n -> R n
$csqrt :: forall (n :: Nat). R n -> R n
log :: R n -> R n
$clog :: forall (n :: Nat). R n -> R n
exp :: R n -> R n
$cexp :: forall (n :: Nat). R n -> R n
pi :: R n
$cpi :: forall (n :: Nat). R n
$cp1Floating :: forall (n :: Nat). Fractional (R n)
Floating,(forall x. R n -> Rep (R n) x)
-> (forall x. Rep (R n) x -> R n) -> Generic (R n)
forall x. Rep (R n) x -> R n
forall x. R n -> Rep (R n) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (n :: Nat) x. Rep (R n) x -> R n
forall (n :: Nat) x. R n -> Rep (R n) x
$cto :: forall (n :: Nat) x. Rep (R n) x -> R n
$cfrom :: forall (n :: Nat) x. R n -> Rep (R n) x
Generic,Get (R n)
[R n] -> Put
R n -> Put
(R n -> Put) -> Get (R n) -> ([R n] -> Put) -> Binary (R n)
forall t. (t -> Put) -> Get t -> ([t] -> Put) -> Binary t
forall (n :: Nat). KnownNat n => Get (R n)
forall (n :: Nat). KnownNat n => [R n] -> Put
forall (n :: Nat). KnownNat n => R n -> Put
putList :: [R n] -> Put
$cputList :: forall (n :: Nat). KnownNat n => [R n] -> Put
get :: Get (R n)
$cget :: forall (n :: Nat). KnownNat n => Get (R n)
put :: R n -> Put
$cput :: forall (n :: Nat). KnownNat n => R n -> Put
Binary)

newtype C n = C (Dim n (Vector ))
  deriving (Integer -> C n
C n -> C n
C n -> C n -> C n
(C n -> C n -> C n)
-> (C n -> C n -> C n)
-> (C n -> C n -> C n)
-> (C n -> C n)
-> (C n -> C n)
-> (C n -> C n)
-> (Integer -> C n)
-> Num (C n)
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
forall (n :: Nat). Integer -> C n
forall (n :: Nat). C n -> C n
forall (n :: Nat). C n -> C n -> C n
fromInteger :: Integer -> C n
$cfromInteger :: forall (n :: Nat). Integer -> C n
signum :: C n -> C n
$csignum :: forall (n :: Nat). C n -> C n
abs :: C n -> C n
$cabs :: forall (n :: Nat). C n -> C n
negate :: C n -> C n
$cnegate :: forall (n :: Nat). C n -> C n
* :: C n -> C n -> C n
$c* :: forall (n :: Nat). C n -> C n -> C n
- :: C n -> C n -> C n
$c- :: forall (n :: Nat). C n -> C n -> C n
+ :: C n -> C n -> C n
$c+ :: forall (n :: Nat). C n -> C n -> C n
Num,Num (C n)
Num (C n)
-> (C n -> C n -> C n)
-> (C n -> C n)
-> (Rational -> C n)
-> Fractional (C n)
Rational -> C n
C n -> C n
C n -> C n -> C n
forall a.
Num a
-> (a -> a -> a) -> (a -> a) -> (Rational -> a) -> Fractional a
forall (n :: Nat). Num (C n)
forall (n :: Nat). Rational -> C n
forall (n :: Nat). C n -> C n
forall (n :: Nat). C n -> C n -> C n
fromRational :: Rational -> C n
$cfromRational :: forall (n :: Nat). Rational -> C n
recip :: C n -> C n
$crecip :: forall (n :: Nat). C n -> C n
/ :: C n -> C n -> C n
$c/ :: forall (n :: Nat). C n -> C n -> C n
$cp1Fractional :: forall (n :: Nat). Num (C n)
Fractional,Fractional (C n)
C n
Fractional (C n)
-> C n
-> (C n -> C n)
-> (C n -> C n)
-> (C n -> C n)
-> (C n -> C n -> C n)
-> (C n -> C n -> C n)
-> (C n -> C n)
-> (C n -> C n)
-> (C n -> C n)
-> (C n -> C n)
-> (C n -> C n)
-> (C n -> C n)
-> (C n -> C n)
-> (C n -> C n)
-> (C n -> C n)
-> (C n -> C n)
-> (C n -> C n)
-> (C n -> C n)
-> (C n -> C n)
-> (C n -> C n)
-> (C n -> C n)
-> (C n -> C n)
-> Floating (C n)
C n -> C n
C n -> C n -> C n
forall a.
Fractional a
-> a
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> Floating a
forall (n :: Nat). Fractional (C n)
forall (n :: Nat). C n
forall (n :: Nat). C n -> C n
forall (n :: Nat). C n -> C n -> C n
log1mexp :: C n -> C n
$clog1mexp :: forall (n :: Nat). C n -> C n
log1pexp :: C n -> C n
$clog1pexp :: forall (n :: Nat). C n -> C n
expm1 :: C n -> C n
$cexpm1 :: forall (n :: Nat). C n -> C n
log1p :: C n -> C n
$clog1p :: forall (n :: Nat). C n -> C n
atanh :: C n -> C n
$catanh :: forall (n :: Nat). C n -> C n
acosh :: C n -> C n
$cacosh :: forall (n :: Nat). C n -> C n
asinh :: C n -> C n
$casinh :: forall (n :: Nat). C n -> C n
tanh :: C n -> C n
$ctanh :: forall (n :: Nat). C n -> C n
cosh :: C n -> C n
$ccosh :: forall (n :: Nat). C n -> C n
sinh :: C n -> C n
$csinh :: forall (n :: Nat). C n -> C n
atan :: C n -> C n
$catan :: forall (n :: Nat). C n -> C n
acos :: C n -> C n
$cacos :: forall (n :: Nat). C n -> C n
asin :: C n -> C n
$casin :: forall (n :: Nat). C n -> C n
tan :: C n -> C n
$ctan :: forall (n :: Nat). C n -> C n
cos :: C n -> C n
$ccos :: forall (n :: Nat). C n -> C n
sin :: C n -> C n
$csin :: forall (n :: Nat). C n -> C n
logBase :: C n -> C n -> C n
$clogBase :: forall (n :: Nat). C n -> C n -> C n
** :: C n -> C n -> C n
$c** :: forall (n :: Nat). C n -> C n -> C n
sqrt :: C n -> C n
$csqrt :: forall (n :: Nat). C n -> C n
log :: C n -> C n
$clog :: forall (n :: Nat). C n -> C n
exp :: C n -> C n
$cexp :: forall (n :: Nat). C n -> C n
pi :: C n
$cpi :: forall (n :: Nat). C n
$cp1Floating :: forall (n :: Nat). Fractional (C n)
Floating,(forall x. C n -> Rep (C n) x)
-> (forall x. Rep (C n) x -> C n) -> Generic (C n)
forall x. Rep (C n) x -> C n
forall x. C n -> Rep (C n) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (n :: Nat) x. Rep (C n) x -> C n
forall (n :: Nat) x. C n -> Rep (C n) x
$cto :: forall (n :: Nat) x. Rep (C n) x -> C n
$cfrom :: forall (n :: Nat) x. C n -> Rep (C n) x
Generic)

newtype L m n = L (Dim m (Dim n (Matrix )))
  deriving ((forall x. L m n -> Rep (L m n) x)
-> (forall x. Rep (L m n) x -> L m n) -> Generic (L m n)
forall x. Rep (L m n) x -> L m n
forall x. L m n -> Rep (L m n) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (m :: Nat) (n :: Nat) x. Rep (L m n) x -> L m n
forall (m :: Nat) (n :: Nat) x. L m n -> Rep (L m n) x
$cto :: forall (m :: Nat) (n :: Nat) x. Rep (L m n) x -> L m n
$cfrom :: forall (m :: Nat) (n :: Nat) x. L m n -> Rep (L m n) x
Generic, Get (L m n)
[L m n] -> Put
L m n -> Put
(L m n -> Put) -> Get (L m n) -> ([L m n] -> Put) -> Binary (L m n)
forall t. (t -> Put) -> Get t -> ([t] -> Put) -> Binary t
forall (m :: Nat) (n :: Nat).
(KnownNat m, KnownNat n) =>
Get (L m n)
forall (m :: Nat) (n :: Nat).
(KnownNat m, KnownNat n) =>
[L m n] -> Put
forall (m :: Nat) (n :: Nat).
(KnownNat m, KnownNat n) =>
L m n -> Put
putList :: [L m n] -> Put
$cputList :: forall (m :: Nat) (n :: Nat).
(KnownNat m, KnownNat n) =>
[L m n] -> Put
get :: Get (L m n)
$cget :: forall (m :: Nat) (n :: Nat).
(KnownNat m, KnownNat n) =>
Get (L m n)
put :: L m n -> Put
$cput :: forall (m :: Nat) (n :: Nat).
(KnownNat m, KnownNat n) =>
L m n -> Put
Binary)

newtype M m n = M (Dim m (Dim n (Matrix )))
  deriving ((forall x. M m n -> Rep (M m n) x)
-> (forall x. Rep (M m n) x -> M m n) -> Generic (M m n)
forall x. Rep (M m n) x -> M m n
forall x. M m n -> Rep (M m n) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (m :: Nat) (n :: Nat) x. Rep (M m n) x -> M m n
forall (m :: Nat) (n :: Nat) x. M m n -> Rep (M m n) x
$cto :: forall (m :: Nat) (n :: Nat) x. Rep (M m n) x -> M m n
$cfrom :: forall (m :: Nat) (n :: Nat) x. M m n -> Rep (M m n) x
Generic)

mkR :: Vector  -> R n
mkR :: Vector ℝ -> R n
mkR = Dim n (Vector ℝ) -> R n
forall (n :: Nat). Dim n (Vector ℝ) -> R n
R (Dim n (Vector ℝ) -> R n)
-> (Vector ℝ -> Dim n (Vector ℝ)) -> Vector ℝ -> R n
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Vector ℝ -> Dim n (Vector ℝ)
forall (n :: Nat) t. t -> Dim n t
Dim

mkC :: Vector  -> C n
mkC :: Vector ℂ -> C n
mkC = Dim n (Vector ℂ) -> C n
forall (n :: Nat). Dim n (Vector ℂ) -> C n
C (Dim n (Vector ℂ) -> C n)
-> (Vector ℂ -> Dim n (Vector ℂ)) -> Vector ℂ -> C n
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Vector ℂ -> Dim n (Vector ℂ)
forall (n :: Nat) t. t -> Dim n t
Dim

mkL :: Matrix  -> L m n
mkL :: Matrix ℝ -> L m n
mkL Matrix ℝ
x = Dim m (Dim n (Matrix ℝ)) -> L m n
forall (m :: Nat) (n :: Nat). Dim m (Dim n (Matrix ℝ)) -> L m n
L (Dim n (Matrix ℝ) -> Dim m (Dim n (Matrix ℝ))
forall (n :: Nat) t. t -> Dim n t
Dim (Matrix ℝ -> Dim n (Matrix ℝ)
forall (n :: Nat) t. t -> Dim n t
Dim Matrix ℝ
x))

mkM :: Matrix  -> M m n
mkM :: Matrix ℂ -> M m n
mkM Matrix ℂ
x = Dim m (Dim n (Matrix ℂ)) -> M m n
forall (m :: Nat) (n :: Nat). Dim m (Dim n (Matrix ℂ)) -> M m n
M (Dim n (Matrix ℂ) -> Dim m (Dim n (Matrix ℂ))
forall (n :: Nat) t. t -> Dim n t
Dim (Matrix ℂ -> Dim n (Matrix ℂ)
forall (n :: Nat) t. t -> Dim n t
Dim Matrix ℂ
x))

instance NFData (R n) where
    rnf :: R n -> ()
rnf (R (Dim n (Vector ℝ) -> Dim n (Vector ℝ)
forall a. NFData a => a -> a
force -> !Dim n (Vector ℝ)
_)) = ()

instance NFData (C n) where
    rnf :: C n -> ()
rnf (C (Dim n (Vector ℂ) -> Dim n (Vector ℂ)
forall a. NFData a => a -> a
force -> !Dim n (Vector ℂ)
_)) = ()

instance NFData (L n m) where
    rnf :: L n m -> ()
rnf (L (Dim n (Dim m (Matrix ℝ)) -> Dim n (Dim m (Matrix ℝ))
forall a. NFData a => a -> a
force -> !Dim n (Dim m (Matrix ℝ))
_)) = ()

instance NFData (M n m) where
    rnf :: M n m -> ()
rnf (M (Dim n (Dim m (Matrix ℂ)) -> Dim n (Dim m (Matrix ℂ))
forall a. NFData a => a -> a
force -> !Dim n (Dim m (Matrix ℂ))
_)) = ()

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

type V n t = Dim n (Vector t)

ud :: Dim n (Vector t) -> Vector t
ud :: Dim n (Vector t) -> Vector t
ud (Dim Vector t
v) = Vector t
v

mkV :: forall (n :: Nat) t . t -> Dim n t
mkV :: t -> Dim n t
mkV = t -> Dim n t
forall (n :: Nat) t. t -> Dim n t
Dim


vconcat :: forall n m t . (KnownNat n, KnownNat m, Numeric t)
    => V n t -> V m t -> V (n+m) t
(V n t -> Vector t
forall (n :: Nat) t. Dim n (Vector t) -> Vector t
ud -> Vector t
u) vconcat :: V n t -> V m t -> V (n + m) t
`vconcat` (V m t -> Vector t
forall (n :: Nat) t. Dim n (Vector t) -> Vector t
ud -> Vector t
v) = Vector t -> V (n + m) t
forall (n :: Nat) t. t -> Dim n t
mkV ([Vector t] -> Vector t
forall t. Storable t => [Vector t] -> Vector t
vjoin [Vector t
u', Vector t
v'])
  where
    du :: Int
du = Integer -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer -> Int) -> (Proxy n -> Integer) -> Proxy n -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Proxy n -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (Proxy n -> Int) -> Proxy n -> Int
forall a b. (a -> b) -> a -> b
$ (Proxy n
forall a. HasCallStack => a
undefined :: Proxy n)
    dv :: Int
dv = Integer -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer -> Int) -> (Proxy m -> Integer) -> Proxy m -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Proxy m -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (Proxy m -> Int) -> Proxy m -> Int
forall a b. (a -> b) -> a -> b
$ (Proxy m
forall a. HasCallStack => a
undefined :: Proxy m)
    u' :: Vector t
u' | Int
du Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= Int
1 Bool -> Bool -> Bool
&& Vector t -> IndexOf Vector
forall (c :: * -> *) t. Container c t => c t -> IndexOf c
LA.size Vector t
u Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1 = t -> Int -> Vector t
forall e d (c :: * -> *). Konst e d c => e -> d -> c e
LA.konst (Vector t
u Vector t -> Int -> t
forall t. Storable t => Vector t -> Int -> t
D.@> Int
0) Int
du
       | Bool
otherwise = Vector t
u
    v' :: Vector t
v' | Int
dv Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= Int
1 Bool -> Bool -> Bool
&& Vector t -> IndexOf Vector
forall (c :: * -> *) t. Container c t => c t -> IndexOf c
LA.size Vector t
v Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1 = t -> Int -> Vector t
forall e d (c :: * -> *). Konst e d c => e -> d -> c e
LA.konst (Vector t
v Vector t -> Int -> t
forall t. Storable t => Vector t -> Int -> t
D.@> Int
0) Int
dv
       | Bool
otherwise = Vector t
v


gvec2 :: Storable t => t -> t -> V 2 t
gvec2 :: t -> t -> V 2 t
gvec2 t
a t
b = Vector t -> V 2 t
forall (n :: Nat) t. t -> Dim n t
mkV (Vector t -> V 2 t) -> Vector t -> V 2 t
forall a b. (a -> b) -> a -> b
$ (forall s. ST s (STVector s t)) -> Vector t
forall t. Storable t => (forall s. ST s (STVector s t)) -> Vector t
runSTVector ((forall s. ST s (STVector s t)) -> Vector t)
-> (forall s. ST s (STVector s t)) -> Vector t
forall a b. (a -> b) -> a -> b
$ do
    STVector s t
v <- Int -> ST s (STVector s t)
forall t s. Storable t => Int -> ST s (STVector s t)
newUndefinedVector Int
2
    STVector s t -> Int -> t -> ST s ()
forall t s. Storable t => STVector s t -> Int -> t -> ST s ()
writeVector STVector s t
v Int
0 t
a
    STVector s t -> Int -> t -> ST s ()
forall t s. Storable t => STVector s t -> Int -> t -> ST s ()
writeVector STVector s t
v Int
1 t
b
    STVector s t -> ST s (STVector s t)
forall (m :: * -> *) a. Monad m => a -> m a
return STVector s t
v

gvec3 :: Storable t => t -> t -> t -> V 3 t
gvec3 :: t -> t -> t -> V 3 t
gvec3 t
a t
b t
c = Vector t -> V 3 t
forall (n :: Nat) t. t -> Dim n t
mkV (Vector t -> V 3 t) -> Vector t -> V 3 t
forall a b. (a -> b) -> a -> b
$ (forall s. ST s (STVector s t)) -> Vector t
forall t. Storable t => (forall s. ST s (STVector s t)) -> Vector t
runSTVector ((forall s. ST s (STVector s t)) -> Vector t)
-> (forall s. ST s (STVector s t)) -> Vector t
forall a b. (a -> b) -> a -> b
$ do
    STVector s t
v <- Int -> ST s (STVector s t)
forall t s. Storable t => Int -> ST s (STVector s t)
newUndefinedVector Int
3
    STVector s t -> Int -> t -> ST s ()
forall t s. Storable t => STVector s t -> Int -> t -> ST s ()
writeVector STVector s t
v Int
0 t
a
    STVector s t -> Int -> t -> ST s ()
forall t s. Storable t => STVector s t -> Int -> t -> ST s ()
writeVector STVector s t
v Int
1 t
b
    STVector s t -> Int -> t -> ST s ()
forall t s. Storable t => STVector s t -> Int -> t -> ST s ()
writeVector STVector s t
v Int
2 t
c
    STVector s t -> ST s (STVector s t)
forall (m :: * -> *) a. Monad m => a -> m a
return STVector s t
v


gvec4 :: Storable t => t -> t -> t -> t -> V 4 t
gvec4 :: t -> t -> t -> t -> V 4 t
gvec4 t
a t
b t
c t
d = Vector t -> V 4 t
forall (n :: Nat) t. t -> Dim n t
mkV (Vector t -> V 4 t) -> Vector t -> V 4 t
forall a b. (a -> b) -> a -> b
$ (forall s. ST s (STVector s t)) -> Vector t
forall t. Storable t => (forall s. ST s (STVector s t)) -> Vector t
runSTVector ((forall s. ST s (STVector s t)) -> Vector t)
-> (forall s. ST s (STVector s t)) -> Vector t
forall a b. (a -> b) -> a -> b
$ do
    STVector s t
v <- Int -> ST s (STVector s t)
forall t s. Storable t => Int -> ST s (STVector s t)
newUndefinedVector Int
4
    STVector s t -> Int -> t -> ST s ()
forall t s. Storable t => STVector s t -> Int -> t -> ST s ()
writeVector STVector s t
v Int
0 t
a
    STVector s t -> Int -> t -> ST s ()
forall t s. Storable t => STVector s t -> Int -> t -> ST s ()
writeVector STVector s t
v Int
1 t
b
    STVector s t -> Int -> t -> ST s ()
forall t s. Storable t => STVector s t -> Int -> t -> ST s ()
writeVector STVector s t
v Int
2 t
c
    STVector s t -> Int -> t -> ST s ()
forall t s. Storable t => STVector s t -> Int -> t -> ST s ()
writeVector STVector s t
v Int
3 t
d
    STVector s t -> ST s (STVector s t)
forall (m :: * -> *) a. Monad m => a -> m a
return STVector s t
v


gvect :: forall n t . (Show t, KnownNat n, Numeric t) => String -> [t] -> V n t
gvect :: String -> [t] -> V n t
gvect String
st [t]
xs'
    | Bool
ok = Vector t -> V n t
forall (n :: Nat) t. t -> Dim n t
mkV Vector t
v
    | Bool -> Bool
not ([t] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [t]
rest) Bool -> Bool -> Bool
&& [t] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null ([t] -> [t]
forall a. [a] -> [a]
tail [t]
rest) = String -> V n t
forall a. String -> a
abort ([t] -> String
forall a. Show a => a -> String
show [t]
xs')
    | Bool -> Bool
not ([t] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [t]
rest) = String -> V n t
forall a. String -> a
abort (ShowS
forall a. [a] -> [a]
init ([t] -> String
forall a. Show a => a -> String
show ([t]
xs[t] -> [t] -> [t]
forall a. [a] -> [a] -> [a]
++Int -> [t] -> [t]
forall a. Int -> [a] -> [a]
take Int
1 [t]
rest))String -> ShowS
forall a. [a] -> [a] -> [a]
++String
", ... ]")
    | Bool
otherwise = String -> V n t
forall a. String -> a
abort ([t] -> String
forall a. Show a => a -> String
show [t]
xs)
  where
    ([t]
xs,[t]
rest) = Int -> [t] -> ([t], [t])
forall a. Int -> [a] -> ([a], [a])
splitAt Int
d [t]
xs'
    ok :: Bool
ok = Vector t -> IndexOf Vector
forall (c :: * -> *) t. Container c t => c t -> IndexOf c
LA.size Vector t
v Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
d Bool -> Bool -> Bool
&& [t] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [t]
rest
    v :: Vector t
v = [t] -> Vector t
forall a. Storable a => [a] -> Vector a
LA.fromList [t]
xs
    d :: Int
d = Integer -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer -> Int) -> (Proxy n -> Integer) -> Proxy n -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Proxy n -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (Proxy n -> Int) -> Proxy n -> Int
forall a b. (a -> b) -> a -> b
$ (Proxy n
forall a. HasCallStack => a
undefined :: Proxy n)
    abort :: String -> a
abort String
info = String -> a
forall a. HasCallStack => String -> a
error (String -> a) -> String -> a
forall a b. (a -> b) -> a -> b
$ String
stString -> ShowS
forall a. [a] -> [a] -> [a]
++String
" "String -> ShowS
forall a. [a] -> [a] -> [a]
++Int -> String
forall a. Show a => a -> String
show Int
dString -> ShowS
forall a. [a] -> [a] -> [a]
++String
" can't be created from elements "String -> ShowS
forall a. [a] -> [a] -> [a]
++String
info


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

type GM m n t = Dim m (Dim n (Matrix t))


gmat :: forall m n t . (Show t, KnownNat m, KnownNat n, Numeric t) => String -> [t] -> GM m n t
gmat :: String -> [t] -> GM m n t
gmat String
st [t]
xs'
    | Bool
ok = Dim n (Matrix t) -> GM m n t
forall (n :: Nat) t. t -> Dim n t
Dim (Matrix t -> Dim n (Matrix t)
forall (n :: Nat) t. t -> Dim n t
Dim Matrix t
x)
    | Bool -> Bool
not ([t] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [t]
rest) Bool -> Bool -> Bool
&& [t] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null ([t] -> [t]
forall a. [a] -> [a]
tail [t]
rest) = String -> GM m n t
forall a. String -> a
abort ([t] -> String
forall a. Show a => a -> String
show [t]
xs')
    | Bool -> Bool
not ([t] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [t]
rest) = String -> GM m n t
forall a. String -> a
abort (ShowS
forall a. [a] -> [a]
init ([t] -> String
forall a. Show a => a -> String
show ([t]
xs[t] -> [t] -> [t]
forall a. [a] -> [a] -> [a]
++Int -> [t] -> [t]
forall a. Int -> [a] -> [a]
take Int
1 [t]
rest))String -> ShowS
forall a. [a] -> [a] -> [a]
++String
", ... ]")
    | Bool
otherwise = String -> GM m n t
forall a. String -> a
abort ([t] -> String
forall a. Show a => a -> String
show [t]
xs)
  where
    ([t]
xs,[t]
rest) = Int -> [t] -> ([t], [t])
forall a. Int -> [a] -> ([a], [a])
splitAt (Int
m'Int -> Int -> Int
forall a. Num a => a -> a -> a
*Int
n') [t]
xs'
    v :: Vector t
v = [t] -> Vector t
forall a. Storable a => [a] -> Vector a
LA.fromList [t]
xs
    x :: Matrix t
x = Int -> Vector t -> Matrix t
forall t. Storable t => Int -> Vector t -> Matrix t
reshape Int
n' Vector t
v
    ok :: Bool
ok = [t] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [t]
rest Bool -> Bool -> Bool
&& ((Int
n' Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 Bool -> Bool -> Bool
&& Vector t -> Int
forall t. Storable t => Vector t -> Int
dim Vector t
v Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0) Bool -> Bool -> Bool
|| Int
n'Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0 Bool -> Bool -> Bool
&& (Int -> Int -> Int
forall a. Integral a => a -> a -> a
rem (Vector t -> IndexOf Vector
forall (c :: * -> *) t. Container c t => c t -> IndexOf c
LA.size Vector t
v) Int
n' Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0) Bool -> Bool -> Bool
&& Matrix t -> IndexOf Matrix
forall (c :: * -> *) t. Container c t => c t -> IndexOf c
LA.size Matrix t
x (Int, Int) -> (Int, Int) -> Bool
forall a. Eq a => a -> a -> Bool
== (Int
m',Int
n'))
    m' :: Int
m' = Integer -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer -> Int) -> (Proxy m -> Integer) -> Proxy m -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Proxy m -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (Proxy m -> Int) -> Proxy m -> Int
forall a b. (a -> b) -> a -> b
$ (Proxy m
forall a. HasCallStack => a
undefined :: Proxy m) :: Int
    n' :: Int
n' = Integer -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer -> Int) -> (Proxy n -> Integer) -> Proxy n -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Proxy n -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (Proxy n -> Int) -> Proxy n -> Int
forall a b. (a -> b) -> a -> b
$ (Proxy n
forall a. HasCallStack => a
undefined :: Proxy n) :: Int
    abort :: String -> a
abort String
info = String -> a
forall a. HasCallStack => String -> a
error (String -> a) -> String -> a
forall a b. (a -> b) -> a -> b
$ String
st String -> ShowS
forall a. [a] -> [a] -> [a]
++String
" "String -> ShowS
forall a. [a] -> [a] -> [a]
++Int -> String
forall a. Show a => a -> String
show Int
m' String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
n'String -> ShowS
forall a. [a] -> [a] -> [a]
++String
" can't be created from elements " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
info

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

class Num t => Sized t s d | s -> t, s -> d
  where
    konst     ::  t   -> s
    unwrap    ::  s   -> d t
    fromList  :: [t]  -> s
    extract   ::  s   -> d t
    create    ::  d t -> Maybe s
    size      ::  s   -> IndexOf d

singleV :: c t -> Bool
singleV c t
v = c t -> IndexOf c
forall (c :: * -> *) t. Container c t => c t -> IndexOf c
LA.size c t
v IndexOf c -> IndexOf c -> Bool
forall a. Eq a => a -> a -> Bool
== IndexOf c
1
singleM :: Matrix t -> Bool
singleM Matrix t
m = Matrix t -> Int
forall t. Matrix t -> Int
rows Matrix t
m Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1 Bool -> Bool -> Bool
&& Matrix t -> Int
forall t. Matrix t -> Int
cols Matrix t
m Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1


instance KnownNat n => Sized  (C n) Vector
  where
    size :: C n -> IndexOf Vector
size C n
_ = Integer -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer -> Int) -> (Proxy n -> Integer) -> Proxy n -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Proxy n -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (Proxy n -> Int) -> Proxy n -> Int
forall a b. (a -> b) -> a -> b
$ (Proxy n
forall a. HasCallStack => a
undefined :: Proxy n)
    konst :: ℂ -> C n
konst x = Vector ℂ -> C n
forall (n :: Nat). Vector ℂ -> C n
mkC (ℂ -> Vector ℂ
forall (c :: * -> *) e. Container c e => e -> c e
LA.scalar x)
    unwrap :: C n -> Vector ℂ
unwrap (C (Dim Vector ℂ
v)) = Vector ℂ
v
    fromList :: [ℂ] -> C n
fromList [ℂ]
xs = Dim n (Vector ℂ) -> C n
forall (n :: Nat). Dim n (Vector ℂ) -> C n
C (String -> [ℂ] -> Dim n (Vector ℂ)
forall (n :: Nat) t.
(Show t, KnownNat n, Numeric t) =>
String -> [t] -> V n t
gvect String
"C" [ℂ]
xs)
    extract :: C n -> Vector ℂ
extract s :: C n
s@(C n -> Vector ℂ
forall t s (d :: * -> *). Sized t s d => s -> d t
unwrap -> Vector ℂ
v)
      | Vector ℂ -> Bool
forall (c :: * -> *) t.
(Eq (IndexOf c), Container c t, Num (IndexOf c)) =>
c t -> Bool
singleV Vector ℂ
v = ℂ -> Int -> Vector ℂ
forall e d (c :: * -> *). Konst e d c => e -> d -> c e
LA.konst (Vector ℂ
vVector ℂ -> Int -> ℂ
forall c t. Indexable c t => c -> Int -> t
!Int
0) (C n -> IndexOf Vector
forall t s (d :: * -> *). Sized t s d => s -> IndexOf d
size C n
s)
      | Bool
otherwise = Vector ℂ
v
    create :: Vector ℂ -> Maybe (C n)
create Vector ℂ
v
        | Vector ℂ -> IndexOf Vector
forall (c :: * -> *) t. Container c t => c t -> IndexOf c
LA.size Vector ℂ
v Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== C n -> IndexOf Vector
forall t s (d :: * -> *). Sized t s d => s -> IndexOf d
size C n
r = C n -> Maybe (C n)
forall a. a -> Maybe a
Just C n
r
        | Bool
otherwise = Maybe (C n)
forall a. Maybe a
Nothing
      where
        r :: C n
r = Vector ℂ -> C n
forall (n :: Nat). Vector ℂ -> C n
mkC Vector ℂ
v :: C n


instance KnownNat n => Sized  (R n) Vector
  where
    size :: R n -> IndexOf Vector
size R n
_ = Integer -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer -> Int) -> (Proxy n -> Integer) -> Proxy n -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Proxy n -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (Proxy n -> Int) -> Proxy n -> Int
forall a b. (a -> b) -> a -> b
$ (Proxy n
forall a. HasCallStack => a
undefined :: Proxy n)
    konst :: ℝ -> R n
konst x = Vector ℝ -> R n
forall (n :: Nat). Vector ℝ -> R n
mkR (ℝ -> Vector ℝ
forall (c :: * -> *) e. Container c e => e -> c e
LA.scalar x)
    unwrap :: R n -> Vector ℝ
unwrap (R (Dim Vector ℝ
v)) = Vector ℝ
v
    fromList :: [ℝ] -> R n
fromList [ℝ]
xs = Dim n (Vector ℝ) -> R n
forall (n :: Nat). Dim n (Vector ℝ) -> R n
R (String -> [ℝ] -> Dim n (Vector ℝ)
forall (n :: Nat) t.
(Show t, KnownNat n, Numeric t) =>
String -> [t] -> V n t
gvect String
"R" [ℝ]
xs)
    extract :: R n -> Vector ℝ
extract s :: R n
s@(R n -> Vector ℝ
forall t s (d :: * -> *). Sized t s d => s -> d t
unwrap -> Vector ℝ
v)
      | Vector ℝ -> Bool
forall (c :: * -> *) t.
(Eq (IndexOf c), Container c t, Num (IndexOf c)) =>
c t -> Bool
singleV Vector ℝ
v = ℝ -> Int -> Vector ℝ
forall e d (c :: * -> *). Konst e d c => e -> d -> c e
LA.konst (Vector ℝ
vVector ℝ -> Int -> ℝ
forall c t. Indexable c t => c -> Int -> t
!Int
0) (R n -> IndexOf Vector
forall t s (d :: * -> *). Sized t s d => s -> IndexOf d
size R n
s)
      | Bool
otherwise = Vector ℝ
v
    create :: Vector ℝ -> Maybe (R n)
create Vector ℝ
v
        | Vector ℝ -> IndexOf Vector
forall (c :: * -> *) t. Container c t => c t -> IndexOf c
LA.size Vector ℝ
v Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== R n -> IndexOf Vector
forall t s (d :: * -> *). Sized t s d => s -> IndexOf d
size R n
r = R n -> Maybe (R n)
forall a. a -> Maybe a
Just R n
r
        | Bool
otherwise = Maybe (R n)
forall a. Maybe a
Nothing
      where
        r :: R n
r = Vector ℝ -> R n
forall (n :: Nat). Vector ℝ -> R n
mkR Vector ℝ
v :: R n



instance (KnownNat m, KnownNat n) => Sized  (L m n) Matrix
  where
    size :: L m n -> IndexOf Matrix
size L m n
_ = ((Integer -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer -> Int) -> (Proxy m -> Integer) -> Proxy m -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Proxy m -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal) (Proxy m
forall a. HasCallStack => a
undefined :: Proxy m)
             ,(Integer -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer -> Int) -> (Proxy n -> Integer) -> Proxy n -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Proxy n -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal) (Proxy n
forall a. HasCallStack => a
undefined :: Proxy n))
    konst :: ℝ -> L m n
konst x = Matrix ℝ -> L m n
forall (m :: Nat) (n :: Nat). Matrix ℝ -> L m n
mkL (ℝ -> Matrix ℝ
forall (c :: * -> *) e. Container c e => e -> c e
LA.scalar x)
    fromList :: [ℝ] -> L m n
fromList [ℝ]
xs = Dim m (Dim n (Matrix ℝ)) -> L m n
forall (m :: Nat) (n :: Nat). Dim m (Dim n (Matrix ℝ)) -> L m n
L (String -> [ℝ] -> Dim m (Dim n (Matrix ℝ))
forall (m :: Nat) (n :: Nat) t.
(Show t, KnownNat m, KnownNat n, Numeric t) =>
String -> [t] -> GM m n t
gmat String
"L" [ℝ]
xs)
    unwrap :: L m n -> Matrix ℝ
unwrap (L (Dim (Dim Matrix ℝ
m))) = Matrix ℝ
m
    extract :: L m n -> Matrix ℝ
extract (L m n -> Maybe (ℝ, Vector ℝ, (Int, Int))
forall (m :: Nat) (n :: Nat).
(KnownNat m, KnownNat n) =>
L m n -> Maybe (ℝ, Vector ℝ, (Int, Int))
isDiag -> Just (z,Vector ℝ
y,(Int
m',Int
n'))) = ℝ -> Vector ℝ -> Int -> Int -> Matrix ℝ
forall t. Storable t => t -> Vector t -> Int -> Int -> Matrix t
diagRect z Vector ℝ
y Int
m' Int
n'
    extract s :: L m n
s@(L m n -> Matrix ℝ
forall t s (d :: * -> *). Sized t s d => s -> d t
unwrap -> Matrix ℝ
a)
        | Matrix ℝ -> Bool
forall t. Matrix t -> Bool
singleM Matrix ℝ
a = ℝ -> (Int, Int) -> Matrix ℝ
forall e d (c :: * -> *). Konst e d c => e -> d -> c e
LA.konst (Matrix ℝ
a Matrix ℝ -> IndexOf Matrix -> ℝ
forall (c :: * -> *) e. Container c e => c e -> IndexOf c -> e
`atIndex` (Int
0,Int
0)) (L m n -> IndexOf Matrix
forall t s (d :: * -> *). Sized t s d => s -> IndexOf d
size L m n
s)
        | Bool
otherwise = Matrix ℝ
a
    create :: Matrix ℝ -> Maybe (L m n)
create Matrix ℝ
x
        | Matrix ℝ -> IndexOf Matrix
forall (c :: * -> *) t. Container c t => c t -> IndexOf c
LA.size Matrix ℝ
x (Int, Int) -> (Int, Int) -> Bool
forall a. Eq a => a -> a -> Bool
== L m n -> IndexOf Matrix
forall t s (d :: * -> *). Sized t s d => s -> IndexOf d
size L m n
r = L m n -> Maybe (L m n)
forall a. a -> Maybe a
Just L m n
r
        | Bool
otherwise = Maybe (L m n)
forall a. Maybe a
Nothing
      where
        r :: L m n
r = Matrix ℝ -> L m n
forall (m :: Nat) (n :: Nat). Matrix ℝ -> L m n
mkL Matrix ℝ
x :: L m n


instance (KnownNat m, KnownNat n) => Sized  (M m n) Matrix
  where
    size :: M m n -> IndexOf Matrix
size M m n
_ = ((Integer -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer -> Int) -> (Proxy m -> Integer) -> Proxy m -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Proxy m -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal) (Proxy m
forall a. HasCallStack => a
undefined :: Proxy m)
             ,(Integer -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer -> Int) -> (Proxy n -> Integer) -> Proxy n -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Proxy n -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal) (Proxy n
forall a. HasCallStack => a
undefined :: Proxy n))
    konst :: ℂ -> M m n
konst x = Matrix ℂ -> M m n
forall (m :: Nat) (n :: Nat). Matrix ℂ -> M m n
mkM (ℂ -> Matrix ℂ
forall (c :: * -> *) e. Container c e => e -> c e
LA.scalar x)
    fromList :: [ℂ] -> M m n
fromList [ℂ]
xs = Dim m (Dim n (Matrix ℂ)) -> M m n
forall (m :: Nat) (n :: Nat). Dim m (Dim n (Matrix ℂ)) -> M m n
M (String -> [ℂ] -> Dim m (Dim n (Matrix ℂ))
forall (m :: Nat) (n :: Nat) t.
(Show t, KnownNat m, KnownNat n, Numeric t) =>
String -> [t] -> GM m n t
gmat String
"M" [ℂ]
xs)
    unwrap :: M m n -> Matrix ℂ
unwrap (M (Dim (Dim Matrix ℂ
m))) = Matrix ℂ
m
    extract :: M m n -> Matrix ℂ
extract (M m n -> Maybe (ℂ, Vector ℂ, (Int, Int))
forall (m :: Nat) (n :: Nat).
(KnownNat m, KnownNat n) =>
M m n -> Maybe (ℂ, Vector ℂ, (Int, Int))
isDiagC -> Just (z,Vector ℂ
y,(Int
m',Int
n'))) = ℂ -> Vector ℂ -> Int -> Int -> Matrix ℂ
forall t. Storable t => t -> Vector t -> Int -> Int -> Matrix t
diagRect z Vector ℂ
y Int
m' Int
n'
    extract s :: M m n
s@(M m n -> Matrix ℂ
forall t s (d :: * -> *). Sized t s d => s -> d t
unwrap -> Matrix ℂ
a)
        | Matrix ℂ -> Bool
forall t. Matrix t -> Bool
singleM Matrix ℂ
a = ℂ -> (Int, Int) -> Matrix ℂ
forall e d (c :: * -> *). Konst e d c => e -> d -> c e
LA.konst (Matrix ℂ
a Matrix ℂ -> IndexOf Matrix -> ℂ
forall (c :: * -> *) e. Container c e => c e -> IndexOf c -> e
`atIndex` (Int
0,Int
0)) (M m n -> IndexOf Matrix
forall t s (d :: * -> *). Sized t s d => s -> IndexOf d
size M m n
s)
        | Bool
otherwise = Matrix ℂ
a
    create :: Matrix ℂ -> Maybe (M m n)
create Matrix ℂ
x
        | Matrix ℂ -> IndexOf Matrix
forall (c :: * -> *) t. Container c t => c t -> IndexOf c
LA.size Matrix ℂ
x (Int, Int) -> (Int, Int) -> Bool
forall a. Eq a => a -> a -> Bool
== M m n -> IndexOf Matrix
forall t s (d :: * -> *). Sized t s d => s -> IndexOf d
size M m n
r = M m n -> Maybe (M m n)
forall a. a -> Maybe a
Just M m n
r
        | Bool
otherwise = Maybe (M m n)
forall a. Maybe a
Nothing
      where
        r :: M m n
r = Matrix ℂ -> M m n
forall (m :: Nat) (n :: Nat). Matrix ℂ -> M m n
mkM Matrix ℂ
x :: M m n

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

instance (KnownNat n, KnownNat m) => Transposable (L m n) (L n m)
  where
    tr :: L m n -> L n m
tr a :: L m n
a@(L m n -> Maybe (ℝ, Vector ℝ, (Int, Int))
forall (m :: Nat) (n :: Nat).
(KnownNat m, KnownNat n) =>
L m n -> Maybe (ℝ, Vector ℝ, (Int, Int))
isDiag -> Just (ℝ, Vector ℝ, (Int, Int))
_) = Matrix ℝ -> L n m
forall (m :: Nat) (n :: Nat). Matrix ℝ -> L m n
mkL (L m n -> Matrix ℝ
forall t s (d :: * -> *). Sized t s d => s -> d t
extract L m n
a)
    tr (L m n -> Matrix ℝ
forall t s (d :: * -> *). Sized t s d => s -> d t
extract -> Matrix ℝ
a) = Matrix ℝ -> L n m
forall (m :: Nat) (n :: Nat). Matrix ℝ -> L m n
mkL (Matrix ℝ -> Matrix ℝ
forall m mt. Transposable m mt => m -> mt
tr Matrix ℝ
a)
    tr' :: L m n -> L n m
tr' = L m n -> L n m
forall m mt. Transposable m mt => m -> mt
tr

instance (KnownNat n, KnownNat m) => Transposable (M m n) (M n m)
  where
    tr :: M m n -> M n m
tr a :: M m n
a@(M m n -> Maybe (ℂ, Vector ℂ, (Int, Int))
forall (m :: Nat) (n :: Nat).
(KnownNat m, KnownNat n) =>
M m n -> Maybe (ℂ, Vector ℂ, (Int, Int))
isDiagC -> Just (ℂ, Vector ℂ, (Int, Int))
_) = Matrix ℂ -> M n m
forall (m :: Nat) (n :: Nat). Matrix ℂ -> M m n
mkM (M m n -> Matrix ℂ
forall t s (d :: * -> *). Sized t s d => s -> d t
extract M m n
a)
    tr (M m n -> Matrix ℂ
forall t s (d :: * -> *). Sized t s d => s -> d t
extract -> Matrix ℂ
a) = Matrix ℂ -> M n m
forall (m :: Nat) (n :: Nat). Matrix ℂ -> M m n
mkM (Matrix ℂ -> Matrix ℂ
forall m mt. Transposable m mt => m -> mt
tr Matrix ℂ
a)
    tr' :: M m n -> M n m
tr' a :: M m n
a@(M m n -> Maybe (ℂ, Vector ℂ, (Int, Int))
forall (m :: Nat) (n :: Nat).
(KnownNat m, KnownNat n) =>
M m n -> Maybe (ℂ, Vector ℂ, (Int, Int))
isDiagC -> Just (ℂ, Vector ℂ, (Int, Int))
_) = Matrix ℂ -> M n m
forall (m :: Nat) (n :: Nat). Matrix ℂ -> M m n
mkM (M m n -> Matrix ℂ
forall t s (d :: * -> *). Sized t s d => s -> d t
extract M m n
a)
    tr' (M m n -> Matrix ℂ
forall t s (d :: * -> *). Sized t s d => s -> d t
extract -> Matrix ℂ
a) = Matrix ℂ -> M n m
forall (m :: Nat) (n :: Nat). Matrix ℂ -> M m n
mkM (Matrix ℂ -> Matrix ℂ
forall m mt. Transposable m mt => m -> mt
tr' Matrix ℂ
a)

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

isDiag :: forall m n . (KnownNat m, KnownNat n) => L m n -> Maybe (, Vector , (Int,Int))
isDiag :: L m n -> Maybe (ℝ, Vector ℝ, (Int, Int))
isDiag (L Dim m (Dim n (Matrix ℝ))
x) = Dim m (Dim n (Matrix ℝ)) -> Maybe (ℝ, Vector ℝ, (Int, Int))
forall (m :: Nat) (n :: Nat) t.
(Numeric t, KnownNat m, KnownNat n) =>
GM m n t -> Maybe (t, Vector t, (Int, Int))
isDiagg Dim m (Dim n (Matrix ℝ))
x

isDiagC :: forall m n . (KnownNat m, KnownNat n) => M m n -> Maybe (, Vector , (Int,Int))
isDiagC :: M m n -> Maybe (ℂ, Vector ℂ, (Int, Int))
isDiagC (M Dim m (Dim n (Matrix ℂ))
x) = Dim m (Dim n (Matrix ℂ)) -> Maybe (ℂ, Vector ℂ, (Int, Int))
forall (m :: Nat) (n :: Nat) t.
(Numeric t, KnownNat m, KnownNat n) =>
GM m n t -> Maybe (t, Vector t, (Int, Int))
isDiagg Dim m (Dim n (Matrix ℂ))
x


isDiagg :: forall m n t . (Numeric t, KnownNat m, KnownNat n) => GM m n t -> Maybe (t, Vector t, (Int,Int))
isDiagg :: GM m n t -> Maybe (t, Vector t, (Int, Int))
isDiagg (Dim (Dim Matrix t
x))
    | Matrix t -> Bool
forall t. Matrix t -> Bool
singleM Matrix t
x = Maybe (t, Vector t, (Int, Int))
forall a. Maybe a
Nothing
    | Matrix t -> Int
forall t. Matrix t -> Int
rows Matrix t
x Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1 Bool -> Bool -> Bool
&& Int
m' Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
1 Bool -> Bool -> Bool
|| Matrix t -> Int
forall t. Matrix t -> Int
cols Matrix t
x Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1 Bool -> Bool -> Bool
&& Int
n' Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
1 = (t, Vector t, (Int, Int)) -> Maybe (t, Vector t, (Int, Int))
forall a. a -> Maybe a
Just (t
z,Vector t
yz,(Int
m',Int
n'))
    | Bool
otherwise = Maybe (t, Vector t, (Int, Int))
forall a. Maybe a
Nothing
  where
    m' :: Int
m' = Integer -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer -> Int) -> (Proxy m -> Integer) -> Proxy m -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Proxy m -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (Proxy m -> Int) -> Proxy m -> Int
forall a b. (a -> b) -> a -> b
$ (Proxy m
forall a. HasCallStack => a
undefined :: Proxy m) :: Int
    n' :: Int
n' = Integer -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer -> Int) -> (Proxy n -> Integer) -> Proxy n -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Proxy n -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (Proxy n -> Int) -> Proxy n -> Int
forall a b. (a -> b) -> a -> b
$ (Proxy n
forall a. HasCallStack => a
undefined :: Proxy n) :: Int
    v :: Vector t
v = Matrix t -> Vector t
forall t. Element t => Matrix t -> Vector t
flatten Matrix t
x
    z :: t
z = Vector t
v Vector t -> IndexOf Vector -> t
forall (c :: * -> *) e. Container c e => c e -> IndexOf c -> e
`atIndex` IndexOf Vector
0
    y :: Vector t
y = Int -> Int -> Vector t -> Vector t
forall t. Storable t => Int -> Int -> Vector t -> Vector t
subVector Int
1 (Vector t -> IndexOf Vector
forall (c :: * -> *) t. Container c t => c t -> IndexOf c
LA.size Vector t
vInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1) Vector t
v
    ny :: IndexOf Vector
ny = Vector t -> IndexOf Vector
forall (c :: * -> *) t. Container c t => c t -> IndexOf c
LA.size Vector t
y
    zeros :: Vector t
zeros = t -> Int -> Vector t
forall e d (c :: * -> *). Konst e d c => e -> d -> c e
LA.konst t
0 (Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
0 (Int -> Int -> Int
forall a. Ord a => a -> a -> a
min Int
m' Int
n' Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
ny))
    yz :: Vector t
yz = [Vector t] -> Vector t
forall t. Storable t => [Vector t] -> Vector t
vjoin [Vector t
y,Vector t
zeros]

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

instance KnownNat n => Show (R n)
  where
    show :: R n -> String
show s :: R n
s@(R (Dim Vector ℝ
v))
      | Vector ℝ -> Bool
forall (c :: * -> *) t.
(Eq (IndexOf c), Container c t, Num (IndexOf c)) =>
c t -> Bool
singleV Vector ℝ
v = String
"(" String -> ShowS
forall a. [a] -> [a] -> [a]
++ ℝ -> String
forall a. Show a => a -> String
show (Vector ℝ
vVector ℝ -> Int -> ℝ
forall c t. Indexable c t => c -> Int -> t
!Int
0) String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" :: R " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
d String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
")"
      | Bool
otherwise = String
"(vector " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Vector ℝ -> String
forall a. Show a => a -> String
show Vector ℝ
v String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" :: R " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
d String -> ShowS
forall a. [a] -> [a] -> [a]
++String
")"
      where
        d :: IndexOf Vector
d = R n -> IndexOf Vector
forall t s (d :: * -> *). Sized t s d => s -> IndexOf d
size R n
s

instance KnownNat n => Show (C n)
  where
    show :: C n -> String
show s :: C n
s@(C (Dim Vector ℂ
v))
      | Vector ℂ -> Bool
forall (c :: * -> *) t.
(Eq (IndexOf c), Container c t, Num (IndexOf c)) =>
c t -> Bool
singleV Vector ℂ
v = String
"(" String -> ShowS
forall a. [a] -> [a] -> [a]
++ ℂ -> String
forall a. Show a => a -> String
show (Vector ℂ
vVector ℂ -> Int -> ℂ
forall c t. Indexable c t => c -> Int -> t
!Int
0) String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" :: C " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
d String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
")"
      | Bool
otherwise = String
"(vector " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Vector ℂ -> String
forall a. Show a => a -> String
show Vector ℂ
v String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" :: C " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
d String -> ShowS
forall a. [a] -> [a] -> [a]
++String
")"
      where
        d :: IndexOf Vector
d = C n -> IndexOf Vector
forall t s (d :: * -> *). Sized t s d => s -> IndexOf d
size C n
s

instance (KnownNat m, KnownNat n) => Show (L m n)
  where
    show :: L m n -> String
show (L m n -> Maybe (ℝ, Vector ℝ, (Int, Int))
forall (m :: Nat) (n :: Nat).
(KnownNat m, KnownNat n) =>
L m n -> Maybe (ℝ, Vector ℝ, (Int, Int))
isDiag -> Just (z,Vector ℝ
y,(Int
m',Int
n'))) = String -> String -> String -> Int -> Int -> String
forall r. PrintfType r => String -> r
printf String
"(diag %s %s :: L %d %d)" (ℝ -> String
forall a. Show a => a -> String
show z) (Vector ℝ -> String
forall a. Show a => a -> String
show Vector ℝ
y) Int
m' Int
n'
    show s :: L m n
s@(L (Dim (Dim Matrix ℝ
x)))
       | Matrix ℝ -> Bool
forall t. Matrix t -> Bool
singleM Matrix ℝ
x = String -> String -> Int -> Int -> String
forall r. PrintfType r => String -> r
printf String
"(%s :: L %d %d)" (ℝ -> String
forall a. Show a => a -> String
show (Matrix ℝ
x Matrix ℝ -> IndexOf Matrix -> ℝ
forall (c :: * -> *) e. Container c e => c e -> IndexOf c -> e
`atIndex` (Int
0,Int
0))) Int
m' Int
n'
       | Bool
otherwise = String
"(matrix" String -> ShowS
forall a. [a] -> [a] -> [a]
++ (Char -> Bool) -> ShowS
forall a. (a -> Bool) -> [a] -> [a]
dropWhile (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/=Char
'\n') (Matrix ℝ -> String
forall a. Show a => a -> String
show Matrix ℝ
x) String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" :: L " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
m' String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
n' String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
")"
      where
        (Int
m',Int
n') = L m n -> IndexOf Matrix
forall t s (d :: * -> *). Sized t s d => s -> IndexOf d
size L m n
s

instance (KnownNat m, KnownNat n) => Show (M m n)
  where
    show :: M m n -> String
show (M m n -> Maybe (ℂ, Vector ℂ, (Int, Int))
forall (m :: Nat) (n :: Nat).
(KnownNat m, KnownNat n) =>
M m n -> Maybe (ℂ, Vector ℂ, (Int, Int))
isDiagC -> Just (z,Vector ℂ
y,(Int
m',Int
n'))) = String -> String -> String -> Int -> Int -> String
forall r. PrintfType r => String -> r
printf String
"(diag %s %s :: M %d %d)" (ℂ -> String
forall a. Show a => a -> String
show z) (Vector ℂ -> String
forall a. Show a => a -> String
show Vector ℂ
y) Int
m' Int
n'
    show s :: M m n
s@(M (Dim (Dim Matrix ℂ
x)))
       | Matrix ℂ -> Bool
forall t. Matrix t -> Bool
singleM Matrix ℂ
x = String -> String -> Int -> Int -> String
forall r. PrintfType r => String -> r
printf String
"(%s :: M %d %d)" (ℂ -> String
forall a. Show a => a -> String
show (Matrix ℂ
x Matrix ℂ -> IndexOf Matrix -> ℂ
forall (c :: * -> *) e. Container c e => c e -> IndexOf c -> e
`atIndex` (Int
0,Int
0))) Int
m' Int
n'
       | Bool
otherwise = String
"(matrix" String -> ShowS
forall a. [a] -> [a] -> [a]
++ (Char -> Bool) -> ShowS
forall a. (a -> Bool) -> [a] -> [a]
dropWhile (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/=Char
'\n') (Matrix ℂ -> String
forall a. Show a => a -> String
show Matrix ℂ
x) String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" :: M " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
m' String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
n' String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
")"
      where
        (Int
m',Int
n') = M m n -> IndexOf Matrix
forall t s (d :: * -> *). Sized t s d => s -> IndexOf d
size M m n
s

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

instance (Num (Vector t), Numeric t )=> Num (Dim n (Vector t))
  where
    + :: Dim n (Vector t) -> Dim n (Vector t) -> Dim n (Vector t)
(+) = (Vector t -> Vector t -> Vector t)
-> Dim n (Vector t) -> Dim n (Vector t) -> Dim n (Vector t)
forall (c :: * -> *) t (n :: Nat).
(c t -> c t -> c t) -> Dim n (c t) -> Dim n (c t) -> Dim n (c t)
lift2F Vector t -> Vector t -> Vector t
forall a. Num a => a -> a -> a
(+)
    * :: Dim n (Vector t) -> Dim n (Vector t) -> Dim n (Vector t)
(*) = (Vector t -> Vector t -> Vector t)
-> Dim n (Vector t) -> Dim n (Vector t) -> Dim n (Vector t)
forall (c :: * -> *) t (n :: Nat).
(c t -> c t -> c t) -> Dim n (c t) -> Dim n (c t) -> Dim n (c t)
lift2F Vector t -> Vector t -> Vector t
forall a. Num a => a -> a -> a
(*)
    (-) = (Vector t -> Vector t -> Vector t)
-> Dim n (Vector t) -> Dim n (Vector t) -> Dim n (Vector t)
forall (c :: * -> *) t (n :: Nat).
(c t -> c t -> c t) -> Dim n (c t) -> Dim n (c t) -> Dim n (c t)
lift2F (-)
    abs :: Dim n (Vector t) -> Dim n (Vector t)
abs = (Vector t -> Vector t) -> Dim n (Vector t) -> Dim n (Vector t)
forall (c :: * -> *) t (n :: Nat).
(c t -> c t) -> Dim n (c t) -> Dim n (c t)
lift1F Vector t -> Vector t
forall a. Num a => a -> a
abs
    signum :: Dim n (Vector t) -> Dim n (Vector t)
signum = (Vector t -> Vector t) -> Dim n (Vector t) -> Dim n (Vector t)
forall (c :: * -> *) t (n :: Nat).
(c t -> c t) -> Dim n (c t) -> Dim n (c t)
lift1F Vector t -> Vector t
forall a. Num a => a -> a
signum
    negate :: Dim n (Vector t) -> Dim n (Vector t)
negate = (Vector t -> Vector t) -> Dim n (Vector t) -> Dim n (Vector t)
forall (c :: * -> *) t (n :: Nat).
(c t -> c t) -> Dim n (c t) -> Dim n (c t)
lift1F Vector t -> Vector t
forall a. Num a => a -> a
negate
    fromInteger :: Integer -> Dim n (Vector t)
fromInteger Integer
x = Vector t -> Dim n (Vector t)
forall (n :: Nat) t. t -> Dim n t
Dim (Integer -> Vector t
forall a. Num a => Integer -> a
fromInteger Integer
x)

instance (Num (Vector t), Fractional t, Numeric t) => Fractional (Dim n (Vector t))
  where
    fromRational :: Rational -> Dim n (Vector t)
fromRational Rational
x = Vector t -> Dim n (Vector t)
forall (n :: Nat) t. t -> Dim n t
Dim (Rational -> Vector t
forall a. Fractional a => Rational -> a
fromRational Rational
x)
    / :: Dim n (Vector t) -> Dim n (Vector t) -> Dim n (Vector t)
(/) = (Vector t -> Vector t -> Vector t)
-> Dim n (Vector t) -> Dim n (Vector t) -> Dim n (Vector t)
forall (c :: * -> *) t (n :: Nat).
(c t -> c t -> c t) -> Dim n (c t) -> Dim n (c t) -> Dim n (c t)
lift2F Vector t -> Vector t -> Vector t
forall a. Fractional a => a -> a -> a
(/)

instance (Fractional t, Floating (Vector t), Numeric t) => Floating (Dim n (Vector t)) where
    sin :: Dim n (Vector t) -> Dim n (Vector t)
sin   = (Vector t -> Vector t) -> Dim n (Vector t) -> Dim n (Vector t)
forall (c :: * -> *) t (n :: Nat).
(c t -> c t) -> Dim n (c t) -> Dim n (c t)
lift1F Vector t -> Vector t
forall a. Floating a => a -> a
sin
    cos :: Dim n (Vector t) -> Dim n (Vector t)
cos   = (Vector t -> Vector t) -> Dim n (Vector t) -> Dim n (Vector t)
forall (c :: * -> *) t (n :: Nat).
(c t -> c t) -> Dim n (c t) -> Dim n (c t)
lift1F Vector t -> Vector t
forall a. Floating a => a -> a
cos
    tan :: Dim n (Vector t) -> Dim n (Vector t)
tan   = (Vector t -> Vector t) -> Dim n (Vector t) -> Dim n (Vector t)
forall (c :: * -> *) t (n :: Nat).
(c t -> c t) -> Dim n (c t) -> Dim n (c t)
lift1F Vector t -> Vector t
forall a. Floating a => a -> a
tan
    asin :: Dim n (Vector t) -> Dim n (Vector t)
asin  = (Vector t -> Vector t) -> Dim n (Vector t) -> Dim n (Vector t)
forall (c :: * -> *) t (n :: Nat).
(c t -> c t) -> Dim n (c t) -> Dim n (c t)
lift1F Vector t -> Vector t
forall a. Floating a => a -> a
asin
    acos :: Dim n (Vector t) -> Dim n (Vector t)
acos  = (Vector t -> Vector t) -> Dim n (Vector t) -> Dim n (Vector t)
forall (c :: * -> *) t (n :: Nat).
(c t -> c t) -> Dim n (c t) -> Dim n (c t)
lift1F Vector t -> Vector t
forall a. Floating a => a -> a
acos
    atan :: Dim n (Vector t) -> Dim n (Vector t)
atan  = (Vector t -> Vector t) -> Dim n (Vector t) -> Dim n (Vector t)
forall (c :: * -> *) t (n :: Nat).
(c t -> c t) -> Dim n (c t) -> Dim n (c t)
lift1F Vector t -> Vector t
forall a. Floating a => a -> a
atan
    sinh :: Dim n (Vector t) -> Dim n (Vector t)
sinh  = (Vector t -> Vector t) -> Dim n (Vector t) -> Dim n (Vector t)
forall (c :: * -> *) t (n :: Nat).
(c t -> c t) -> Dim n (c t) -> Dim n (c t)
lift1F Vector t -> Vector t
forall a. Floating a => a -> a
sinh
    cosh :: Dim n (Vector t) -> Dim n (Vector t)
cosh  = (Vector t -> Vector t) -> Dim n (Vector t) -> Dim n (Vector t)
forall (c :: * -> *) t (n :: Nat).
(c t -> c t) -> Dim n (c t) -> Dim n (c t)
lift1F Vector t -> Vector t
forall a. Floating a => a -> a
cosh
    tanh :: Dim n (Vector t) -> Dim n (Vector t)
tanh  = (Vector t -> Vector t) -> Dim n (Vector t) -> Dim n (Vector t)
forall (c :: * -> *) t (n :: Nat).
(c t -> c t) -> Dim n (c t) -> Dim n (c t)
lift1F Vector t -> Vector t
forall a. Floating a => a -> a
tanh
    asinh :: Dim n (Vector t) -> Dim n (Vector t)
asinh = (Vector t -> Vector t) -> Dim n (Vector t) -> Dim n (Vector t)
forall (c :: * -> *) t (n :: Nat).
(c t -> c t) -> Dim n (c t) -> Dim n (c t)
lift1F Vector t -> Vector t
forall a. Floating a => a -> a
asinh
    acosh :: Dim n (Vector t) -> Dim n (Vector t)
acosh = (Vector t -> Vector t) -> Dim n (Vector t) -> Dim n (Vector t)
forall (c :: * -> *) t (n :: Nat).
(c t -> c t) -> Dim n (c t) -> Dim n (c t)
lift1F Vector t -> Vector t
forall a. Floating a => a -> a
acosh
    atanh :: Dim n (Vector t) -> Dim n (Vector t)
atanh = (Vector t -> Vector t) -> Dim n (Vector t) -> Dim n (Vector t)
forall (c :: * -> *) t (n :: Nat).
(c t -> c t) -> Dim n (c t) -> Dim n (c t)
lift1F Vector t -> Vector t
forall a. Floating a => a -> a
atanh
    exp :: Dim n (Vector t) -> Dim n (Vector t)
exp   = (Vector t -> Vector t) -> Dim n (Vector t) -> Dim n (Vector t)
forall (c :: * -> *) t (n :: Nat).
(c t -> c t) -> Dim n (c t) -> Dim n (c t)
lift1F Vector t -> Vector t
forall a. Floating a => a -> a
exp
    log :: Dim n (Vector t) -> Dim n (Vector t)
log   = (Vector t -> Vector t) -> Dim n (Vector t) -> Dim n (Vector t)
forall (c :: * -> *) t (n :: Nat).
(c t -> c t) -> Dim n (c t) -> Dim n (c t)
lift1F Vector t -> Vector t
forall a. Floating a => a -> a
log
    sqrt :: Dim n (Vector t) -> Dim n (Vector t)
sqrt  = (Vector t -> Vector t) -> Dim n (Vector t) -> Dim n (Vector t)
forall (c :: * -> *) t (n :: Nat).
(c t -> c t) -> Dim n (c t) -> Dim n (c t)
lift1F Vector t -> Vector t
forall a. Floating a => a -> a
sqrt
    ** :: Dim n (Vector t) -> Dim n (Vector t) -> Dim n (Vector t)
(**)  = (Vector t -> Vector t -> Vector t)
-> Dim n (Vector t) -> Dim n (Vector t) -> Dim n (Vector t)
forall (c :: * -> *) t (n :: Nat).
(c t -> c t -> c t) -> Dim n (c t) -> Dim n (c t) -> Dim n (c t)
lift2F Vector t -> Vector t -> Vector t
forall a. Floating a => a -> a -> a
(**)
    pi :: Dim n (Vector t)
pi    = Vector t -> Dim n (Vector t)
forall (n :: Nat) t. t -> Dim n t
Dim Vector t
forall a. Floating a => a
pi


instance (Num (Vector t), Numeric t) => Num (Dim m (Dim n (Matrix t)))
  where
    + :: Dim m (Dim n (Matrix t))
-> Dim m (Dim n (Matrix t)) -> Dim m (Dim n (Matrix t))
(+) = ((Dim n (Matrix t) -> Dim n (Matrix t) -> Dim n (Matrix t))
-> Dim m (Dim n (Matrix t))
-> Dim m (Dim n (Matrix t))
-> Dim m (Dim n (Matrix t))
forall (c :: * -> *) t (n :: Nat).
(c t -> c t -> c t) -> Dim n (c t) -> Dim n (c t) -> Dim n (c t)
lift2F ((Dim n (Matrix t) -> Dim n (Matrix t) -> Dim n (Matrix t))
 -> Dim m (Dim n (Matrix t))
 -> Dim m (Dim n (Matrix t))
 -> Dim m (Dim n (Matrix t)))
-> ((Matrix t -> Matrix t -> Matrix t)
    -> Dim n (Matrix t) -> Dim n (Matrix t) -> Dim n (Matrix t))
-> (Matrix t -> Matrix t -> Matrix t)
-> Dim m (Dim n (Matrix t))
-> Dim m (Dim n (Matrix t))
-> Dim m (Dim n (Matrix t))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Matrix t -> Matrix t -> Matrix t)
-> Dim n (Matrix t) -> Dim n (Matrix t) -> Dim n (Matrix t)
forall (c :: * -> *) t (n :: Nat).
(c t -> c t -> c t) -> Dim n (c t) -> Dim n (c t) -> Dim n (c t)
lift2F) Matrix t -> Matrix t -> Matrix t
forall a. Num a => a -> a -> a
(+)
    * :: Dim m (Dim n (Matrix t))
-> Dim m (Dim n (Matrix t)) -> Dim m (Dim n (Matrix t))
(*) = ((Dim n (Matrix t) -> Dim n (Matrix t) -> Dim n (Matrix t))
-> Dim m (Dim n (Matrix t))
-> Dim m (Dim n (Matrix t))
-> Dim m (Dim n (Matrix t))
forall (c :: * -> *) t (n :: Nat).
(c t -> c t -> c t) -> Dim n (c t) -> Dim n (c t) -> Dim n (c t)
lift2F ((Dim n (Matrix t) -> Dim n (Matrix t) -> Dim n (Matrix t))
 -> Dim m (Dim n (Matrix t))
 -> Dim m (Dim n (Matrix t))
 -> Dim m (Dim n (Matrix t)))
-> ((Matrix t -> Matrix t -> Matrix t)
    -> Dim n (Matrix t) -> Dim n (Matrix t) -> Dim n (Matrix t))
-> (Matrix t -> Matrix t -> Matrix t)
-> Dim m (Dim n (Matrix t))
-> Dim m (Dim n (Matrix t))
-> Dim m (Dim n (Matrix t))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Matrix t -> Matrix t -> Matrix t)
-> Dim n (Matrix t) -> Dim n (Matrix t) -> Dim n (Matrix t)
forall (c :: * -> *) t (n :: Nat).
(c t -> c t -> c t) -> Dim n (c t) -> Dim n (c t) -> Dim n (c t)
lift2F) Matrix t -> Matrix t -> Matrix t
forall a. Num a => a -> a -> a
(*)
    (-) = ((Dim n (Matrix t) -> Dim n (Matrix t) -> Dim n (Matrix t))
-> Dim m (Dim n (Matrix t))
-> Dim m (Dim n (Matrix t))
-> Dim m (Dim n (Matrix t))
forall (c :: * -> *) t (n :: Nat).
(c t -> c t -> c t) -> Dim n (c t) -> Dim n (c t) -> Dim n (c t)
lift2F ((Dim n (Matrix t) -> Dim n (Matrix t) -> Dim n (Matrix t))
 -> Dim m (Dim n (Matrix t))
 -> Dim m (Dim n (Matrix t))
 -> Dim m (Dim n (Matrix t)))
-> ((Matrix t -> Matrix t -> Matrix t)
    -> Dim n (Matrix t) -> Dim n (Matrix t) -> Dim n (Matrix t))
-> (Matrix t -> Matrix t -> Matrix t)
-> Dim m (Dim n (Matrix t))
-> Dim m (Dim n (Matrix t))
-> Dim m (Dim n (Matrix t))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Matrix t -> Matrix t -> Matrix t)
-> Dim n (Matrix t) -> Dim n (Matrix t) -> Dim n (Matrix t)
forall (c :: * -> *) t (n :: Nat).
(c t -> c t -> c t) -> Dim n (c t) -> Dim n (c t) -> Dim n (c t)
lift2F) (-)
    abs :: Dim m (Dim n (Matrix t)) -> Dim m (Dim n (Matrix t))
abs = ((Dim n (Matrix t) -> Dim n (Matrix t))
-> Dim m (Dim n (Matrix t)) -> Dim m (Dim n (Matrix t))
forall (c :: * -> *) t (n :: Nat).
(c t -> c t) -> Dim n (c t) -> Dim n (c t)
lift1F ((Dim n (Matrix t) -> Dim n (Matrix t))
 -> Dim m (Dim n (Matrix t)) -> Dim m (Dim n (Matrix t)))
-> ((Matrix t -> Matrix t) -> Dim n (Matrix t) -> Dim n (Matrix t))
-> (Matrix t -> Matrix t)
-> Dim m (Dim n (Matrix t))
-> Dim m (Dim n (Matrix t))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Matrix t -> Matrix t) -> Dim n (Matrix t) -> Dim n (Matrix t)
forall (c :: * -> *) t (n :: Nat).
(c t -> c t) -> Dim n (c t) -> Dim n (c t)
lift1F) Matrix t -> Matrix t
forall a. Num a => a -> a
abs
    signum :: Dim m (Dim n (Matrix t)) -> Dim m (Dim n (Matrix t))
signum = ((Dim n (Matrix t) -> Dim n (Matrix t))
-> Dim m (Dim n (Matrix t)) -> Dim m (Dim n (Matrix t))
forall (c :: * -> *) t (n :: Nat).
(c t -> c t) -> Dim n (c t) -> Dim n (c t)
lift1F ((Dim n (Matrix t) -> Dim n (Matrix t))
 -> Dim m (Dim n (Matrix t)) -> Dim m (Dim n (Matrix t)))
-> ((Matrix t -> Matrix t) -> Dim n (Matrix t) -> Dim n (Matrix t))
-> (Matrix t -> Matrix t)
-> Dim m (Dim n (Matrix t))
-> Dim m (Dim n (Matrix t))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Matrix t -> Matrix t) -> Dim n (Matrix t) -> Dim n (Matrix t)
forall (c :: * -> *) t (n :: Nat).
(c t -> c t) -> Dim n (c t) -> Dim n (c t)
lift1F) Matrix t -> Matrix t
forall a. Num a => a -> a
signum
    negate :: Dim m (Dim n (Matrix t)) -> Dim m (Dim n (Matrix t))
negate = ((Dim n (Matrix t) -> Dim n (Matrix t))
-> Dim m (Dim n (Matrix t)) -> Dim m (Dim n (Matrix t))
forall (c :: * -> *) t (n :: Nat).
(c t -> c t) -> Dim n (c t) -> Dim n (c t)
lift1F ((Dim n (Matrix t) -> Dim n (Matrix t))
 -> Dim m (Dim n (Matrix t)) -> Dim m (Dim n (Matrix t)))
-> ((Matrix t -> Matrix t) -> Dim n (Matrix t) -> Dim n (Matrix t))
-> (Matrix t -> Matrix t)
-> Dim m (Dim n (Matrix t))
-> Dim m (Dim n (Matrix t))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Matrix t -> Matrix t) -> Dim n (Matrix t) -> Dim n (Matrix t)
forall (c :: * -> *) t (n :: Nat).
(c t -> c t) -> Dim n (c t) -> Dim n (c t)
lift1F) Matrix t -> Matrix t
forall a. Num a => a -> a
negate
    fromInteger :: Integer -> Dim m (Dim n (Matrix t))
fromInteger Integer
x = Dim n (Matrix t) -> Dim m (Dim n (Matrix t))
forall (n :: Nat) t. t -> Dim n t
Dim (Matrix t -> Dim n (Matrix t)
forall (n :: Nat) t. t -> Dim n t
Dim (Integer -> Matrix t
forall a. Num a => Integer -> a
fromInteger Integer
x))

instance (Num (Vector t), Fractional t, Numeric t) => Fractional (Dim m (Dim n (Matrix t)))
  where
    fromRational :: Rational -> Dim m (Dim n (Matrix t))
fromRational Rational
x = Dim n (Matrix t) -> Dim m (Dim n (Matrix t))
forall (n :: Nat) t. t -> Dim n t
Dim (Matrix t -> Dim n (Matrix t)
forall (n :: Nat) t. t -> Dim n t
Dim (Rational -> Matrix t
forall a. Fractional a => Rational -> a
fromRational Rational
x))
    / :: Dim m (Dim n (Matrix t))
-> Dim m (Dim n (Matrix t)) -> Dim m (Dim n (Matrix t))
(/) = ((Dim n (Matrix t) -> Dim n (Matrix t) -> Dim n (Matrix t))
-> Dim m (Dim n (Matrix t))
-> Dim m (Dim n (Matrix t))
-> Dim m (Dim n (Matrix t))
forall (c :: * -> *) t (n :: Nat).
(c t -> c t -> c t) -> Dim n (c t) -> Dim n (c t) -> Dim n (c t)
lift2F((Dim n (Matrix t) -> Dim n (Matrix t) -> Dim n (Matrix t))
 -> Dim m (Dim n (Matrix t))
 -> Dim m (Dim n (Matrix t))
 -> Dim m (Dim n (Matrix t)))
-> ((Matrix t -> Matrix t -> Matrix t)
    -> Dim n (Matrix t) -> Dim n (Matrix t) -> Dim n (Matrix t))
-> (Matrix t -> Matrix t -> Matrix t)
-> Dim m (Dim n (Matrix t))
-> Dim m (Dim n (Matrix t))
-> Dim m (Dim n (Matrix t))
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Matrix t -> Matrix t -> Matrix t)
-> Dim n (Matrix t) -> Dim n (Matrix t) -> Dim n (Matrix t)
forall (c :: * -> *) t (n :: Nat).
(c t -> c t -> c t) -> Dim n (c t) -> Dim n (c t) -> Dim n (c t)
lift2F) Matrix t -> Matrix t -> Matrix t
forall a. Fractional a => a -> a -> a
(/)

instance (Floating (Vector t), Floating t, Numeric t) => Floating (Dim m (Dim n (Matrix t))) where
    sin :: Dim m (Dim n (Matrix t)) -> Dim m (Dim n (Matrix t))
sin   = ((Dim n (Matrix t) -> Dim n (Matrix t))
-> Dim m (Dim n (Matrix t)) -> Dim m (Dim n (Matrix t))
forall (c :: * -> *) t (n :: Nat).
(c t -> c t) -> Dim n (c t) -> Dim n (c t)
lift1F ((Dim n (Matrix t) -> Dim n (Matrix t))
 -> Dim m (Dim n (Matrix t)) -> Dim m (Dim n (Matrix t)))
-> ((Matrix t -> Matrix t) -> Dim n (Matrix t) -> Dim n (Matrix t))
-> (Matrix t -> Matrix t)
-> Dim m (Dim n (Matrix t))
-> Dim m (Dim n (Matrix t))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Matrix t -> Matrix t) -> Dim n (Matrix t) -> Dim n (Matrix t)
forall (c :: * -> *) t (n :: Nat).
(c t -> c t) -> Dim n (c t) -> Dim n (c t)
lift1F) Matrix t -> Matrix t
forall a. Floating a => a -> a
sin
    cos :: Dim m (Dim n (Matrix t)) -> Dim m (Dim n (Matrix t))
cos   = ((Dim n (Matrix t) -> Dim n (Matrix t))
-> Dim m (Dim n (Matrix t)) -> Dim m (Dim n (Matrix t))
forall (c :: * -> *) t (n :: Nat).
(c t -> c t) -> Dim n (c t) -> Dim n (c t)
lift1F ((Dim n (Matrix t) -> Dim n (Matrix t))
 -> Dim m (Dim n (Matrix t)) -> Dim m (Dim n (Matrix t)))
-> ((Matrix t -> Matrix t) -> Dim n (Matrix t) -> Dim n (Matrix t))
-> (Matrix t -> Matrix t)
-> Dim m (Dim n (Matrix t))
-> Dim m (Dim n (Matrix t))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Matrix t -> Matrix t) -> Dim n (Matrix t) -> Dim n (Matrix t)
forall (c :: * -> *) t (n :: Nat).
(c t -> c t) -> Dim n (c t) -> Dim n (c t)
lift1F) Matrix t -> Matrix t
forall a. Floating a => a -> a
cos
    tan :: Dim m (Dim n (Matrix t)) -> Dim m (Dim n (Matrix t))
tan   = ((Dim n (Matrix t) -> Dim n (Matrix t))
-> Dim m (Dim n (Matrix t)) -> Dim m (Dim n (Matrix t))
forall (c :: * -> *) t (n :: Nat).
(c t -> c t) -> Dim n (c t) -> Dim n (c t)
lift1F ((Dim n (Matrix t) -> Dim n (Matrix t))
 -> Dim m (Dim n (Matrix t)) -> Dim m (Dim n (Matrix t)))
-> ((Matrix t -> Matrix t) -> Dim n (Matrix t) -> Dim n (Matrix t))
-> (Matrix t -> Matrix t)
-> Dim m (Dim n (Matrix t))
-> Dim m (Dim n (Matrix t))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Matrix t -> Matrix t) -> Dim n (Matrix t) -> Dim n (Matrix t)
forall (c :: * -> *) t (n :: Nat).
(c t -> c t) -> Dim n (c t) -> Dim n (c t)
lift1F) Matrix t -> Matrix t
forall a. Floating a => a -> a
tan
    asin :: Dim m (Dim n (Matrix t)) -> Dim m (Dim n (Matrix t))
asin  = ((Dim n (Matrix t) -> Dim n (Matrix t))
-> Dim m (Dim n (Matrix t)) -> Dim m (Dim n (Matrix t))
forall (c :: * -> *) t (n :: Nat).
(c t -> c t) -> Dim n (c t) -> Dim n (c t)
lift1F ((Dim n (Matrix t) -> Dim n (Matrix t))
 -> Dim m (Dim n (Matrix t)) -> Dim m (Dim n (Matrix t)))
-> ((Matrix t -> Matrix t) -> Dim n (Matrix t) -> Dim n (Matrix t))
-> (Matrix t -> Matrix t)
-> Dim m (Dim n (Matrix t))
-> Dim m (Dim n (Matrix t))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Matrix t -> Matrix t) -> Dim n (Matrix t) -> Dim n (Matrix t)
forall (c :: * -> *) t (n :: Nat).
(c t -> c t) -> Dim n (c t) -> Dim n (c t)
lift1F) Matrix t -> Matrix t
forall a. Floating a => a -> a
asin
    acos :: Dim m (Dim n (Matrix t)) -> Dim m (Dim n (Matrix t))
acos  = ((Dim n (Matrix t) -> Dim n (Matrix t))
-> Dim m (Dim n (Matrix t)) -> Dim m (Dim n (Matrix t))
forall (c :: * -> *) t (n :: Nat).
(c t -> c t) -> Dim n (c t) -> Dim n (c t)
lift1F ((Dim n (Matrix t) -> Dim n (Matrix t))
 -> Dim m (Dim n (Matrix t)) -> Dim m (Dim n (Matrix t)))
-> ((Matrix t -> Matrix t) -> Dim n (Matrix t) -> Dim n (Matrix t))
-> (Matrix t -> Matrix t)
-> Dim m (Dim n (Matrix t))
-> Dim m (Dim n (Matrix t))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Matrix t -> Matrix t) -> Dim n (Matrix t) -> Dim n (Matrix t)
forall (c :: * -> *) t (n :: Nat).
(c t -> c t) -> Dim n (c t) -> Dim n (c t)
lift1F) Matrix t -> Matrix t
forall a. Floating a => a -> a
acos
    atan :: Dim m (Dim n (Matrix t)) -> Dim m (Dim n (Matrix t))
atan  = ((Dim n (Matrix t) -> Dim n (Matrix t))
-> Dim m (Dim n (Matrix t)) -> Dim m (Dim n (Matrix t))
forall (c :: * -> *) t (n :: Nat).
(c t -> c t) -> Dim n (c t) -> Dim n (c t)
lift1F ((Dim n (Matrix t) -> Dim n (Matrix t))
 -> Dim m (Dim n (Matrix t)) -> Dim m (Dim n (Matrix t)))
-> ((Matrix t -> Matrix t) -> Dim n (Matrix t) -> Dim n (Matrix t))
-> (Matrix t -> Matrix t)
-> Dim m (Dim n (Matrix t))
-> Dim m (Dim n (Matrix t))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Matrix t -> Matrix t) -> Dim n (Matrix t) -> Dim n (Matrix t)
forall (c :: * -> *) t (n :: Nat).
(c t -> c t) -> Dim n (c t) -> Dim n (c t)
lift1F) Matrix t -> Matrix t
forall a. Floating a => a -> a
atan
    sinh :: Dim m (Dim n (Matrix t)) -> Dim m (Dim n (Matrix t))
sinh  = ((Dim n (Matrix t) -> Dim n (Matrix t))
-> Dim m (Dim n (Matrix t)) -> Dim m (Dim n (Matrix t))
forall (c :: * -> *) t (n :: Nat).
(c t -> c t) -> Dim n (c t) -> Dim n (c t)
lift1F ((Dim n (Matrix t) -> Dim n (Matrix t))
 -> Dim m (Dim n (Matrix t)) -> Dim m (Dim n (Matrix t)))
-> ((Matrix t -> Matrix t) -> Dim n (Matrix t) -> Dim n (Matrix t))
-> (Matrix t -> Matrix t)
-> Dim m (Dim n (Matrix t))
-> Dim m (Dim n (Matrix t))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Matrix t -> Matrix t) -> Dim n (Matrix t) -> Dim n (Matrix t)
forall (c :: * -> *) t (n :: Nat).
(c t -> c t) -> Dim n (c t) -> Dim n (c t)
lift1F) Matrix t -> Matrix t
forall a. Floating a => a -> a
sinh
    cosh :: Dim m (Dim n (Matrix t)) -> Dim m (Dim n (Matrix t))
cosh  = ((Dim n (Matrix t) -> Dim n (Matrix t))
-> Dim m (Dim n (Matrix t)) -> Dim m (Dim n (Matrix t))
forall (c :: * -> *) t (n :: Nat).
(c t -> c t) -> Dim n (c t) -> Dim n (c t)
lift1F ((Dim n (Matrix t) -> Dim n (Matrix t))
 -> Dim m (Dim n (Matrix t)) -> Dim m (Dim n (Matrix t)))
-> ((Matrix t -> Matrix t) -> Dim n (Matrix t) -> Dim n (Matrix t))
-> (Matrix t -> Matrix t)
-> Dim m (Dim n (Matrix t))
-> Dim m (Dim n (Matrix t))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Matrix t -> Matrix t) -> Dim n (Matrix t) -> Dim n (Matrix t)
forall (c :: * -> *) t (n :: Nat).
(c t -> c t) -> Dim n (c t) -> Dim n (c t)
lift1F) Matrix t -> Matrix t
forall a. Floating a => a -> a
cosh
    tanh :: Dim m (Dim n (Matrix t)) -> Dim m (Dim n (Matrix t))
tanh  = ((Dim n (Matrix t) -> Dim n (Matrix t))
-> Dim m (Dim n (Matrix t)) -> Dim m (Dim n (Matrix t))
forall (c :: * -> *) t (n :: Nat).
(c t -> c t) -> Dim n (c t) -> Dim n (c t)
lift1F ((Dim n (Matrix t) -> Dim n (Matrix t))
 -> Dim m (Dim n (Matrix t)) -> Dim m (Dim n (Matrix t)))
-> ((Matrix t -> Matrix t) -> Dim n (Matrix t) -> Dim n (Matrix t))
-> (Matrix t -> Matrix t)
-> Dim m (Dim n (Matrix t))
-> Dim m (Dim n (Matrix t))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Matrix t -> Matrix t) -> Dim n (Matrix t) -> Dim n (Matrix t)
forall (c :: * -> *) t (n :: Nat).
(c t -> c t) -> Dim n (c t) -> Dim n (c t)
lift1F) Matrix t -> Matrix t
forall a. Floating a => a -> a
tanh
    asinh :: Dim m (Dim n (Matrix t)) -> Dim m (Dim n (Matrix t))
asinh = ((Dim n (Matrix t) -> Dim n (Matrix t))
-> Dim m (Dim n (Matrix t)) -> Dim m (Dim n (Matrix t))
forall (c :: * -> *) t (n :: Nat).
(c t -> c t) -> Dim n (c t) -> Dim n (c t)
lift1F ((Dim n (Matrix t) -> Dim n (Matrix t))
 -> Dim m (Dim n (Matrix t)) -> Dim m (Dim n (Matrix t)))
-> ((Matrix t -> Matrix t) -> Dim n (Matrix t) -> Dim n (Matrix t))
-> (Matrix t -> Matrix t)
-> Dim m (Dim n (Matrix t))
-> Dim m (Dim n (Matrix t))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Matrix t -> Matrix t) -> Dim n (Matrix t) -> Dim n (Matrix t)
forall (c :: * -> *) t (n :: Nat).
(c t -> c t) -> Dim n (c t) -> Dim n (c t)
lift1F) Matrix t -> Matrix t
forall a. Floating a => a -> a
asinh
    acosh :: Dim m (Dim n (Matrix t)) -> Dim m (Dim n (Matrix t))
acosh = ((Dim n (Matrix t) -> Dim n (Matrix t))
-> Dim m (Dim n (Matrix t)) -> Dim m (Dim n (Matrix t))
forall (c :: * -> *) t (n :: Nat).
(c t -> c t) -> Dim n (c t) -> Dim n (c t)
lift1F ((Dim n (Matrix t) -> Dim n (Matrix t))
 -> Dim m (Dim n (Matrix t)) -> Dim m (Dim n (Matrix t)))
-> ((Matrix t -> Matrix t) -> Dim n (Matrix t) -> Dim n (Matrix t))
-> (Matrix t -> Matrix t)
-> Dim m (Dim n (Matrix t))
-> Dim m (Dim n (Matrix t))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Matrix t -> Matrix t) -> Dim n (Matrix t) -> Dim n (Matrix t)
forall (c :: * -> *) t (n :: Nat).
(c t -> c t) -> Dim n (c t) -> Dim n (c t)
lift1F) Matrix t -> Matrix t
forall a. Floating a => a -> a
acosh
    atanh :: Dim m (Dim n (Matrix t)) -> Dim m (Dim n (Matrix t))
atanh = ((Dim n (Matrix t) -> Dim n (Matrix t))
-> Dim m (Dim n (Matrix t)) -> Dim m (Dim n (Matrix t))
forall (c :: * -> *) t (n :: Nat).
(c t -> c t) -> Dim n (c t) -> Dim n (c t)
lift1F ((Dim n (Matrix t) -> Dim n (Matrix t))
 -> Dim m (Dim n (Matrix t)) -> Dim m (Dim n (Matrix t)))
-> ((Matrix t -> Matrix t) -> Dim n (Matrix t) -> Dim n (Matrix t))
-> (Matrix t -> Matrix t)
-> Dim m (Dim n (Matrix t))
-> Dim m (Dim n (Matrix t))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Matrix t -> Matrix t) -> Dim n (Matrix t) -> Dim n (Matrix t)
forall (c :: * -> *) t (n :: Nat).
(c t -> c t) -> Dim n (c t) -> Dim n (c t)
lift1F) Matrix t -> Matrix t
forall a. Floating a => a -> a
atanh
    exp :: Dim m (Dim n (Matrix t)) -> Dim m (Dim n (Matrix t))
exp   = ((Dim n (Matrix t) -> Dim n (Matrix t))
-> Dim m (Dim n (Matrix t)) -> Dim m (Dim n (Matrix t))
forall (c :: * -> *) t (n :: Nat).
(c t -> c t) -> Dim n (c t) -> Dim n (c t)
lift1F ((Dim n (Matrix t) -> Dim n (Matrix t))
 -> Dim m (Dim n (Matrix t)) -> Dim m (Dim n (Matrix t)))
-> ((Matrix t -> Matrix t) -> Dim n (Matrix t) -> Dim n (Matrix t))
-> (Matrix t -> Matrix t)
-> Dim m (Dim n (Matrix t))
-> Dim m (Dim n (Matrix t))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Matrix t -> Matrix t) -> Dim n (Matrix t) -> Dim n (Matrix t)
forall (c :: * -> *) t (n :: Nat).
(c t -> c t) -> Dim n (c t) -> Dim n (c t)
lift1F) Matrix t -> Matrix t
forall a. Floating a => a -> a
exp
    log :: Dim m (Dim n (Matrix t)) -> Dim m (Dim n (Matrix t))
log   = ((Dim n (Matrix t) -> Dim n (Matrix t))
-> Dim m (Dim n (Matrix t)) -> Dim m (Dim n (Matrix t))
forall (c :: * -> *) t (n :: Nat).
(c t -> c t) -> Dim n (c t) -> Dim n (c t)
lift1F ((Dim n (Matrix t) -> Dim n (Matrix t))
 -> Dim m (Dim n (Matrix t)) -> Dim m (Dim n (Matrix t)))
-> ((Matrix t -> Matrix t) -> Dim n (Matrix t) -> Dim n (Matrix t))
-> (Matrix t -> Matrix t)
-> Dim m (Dim n (Matrix t))
-> Dim m (Dim n (Matrix t))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Matrix t -> Matrix t) -> Dim n (Matrix t) -> Dim n (Matrix t)
forall (c :: * -> *) t (n :: Nat).
(c t -> c t) -> Dim n (c t) -> Dim n (c t)
lift1F) Matrix t -> Matrix t
forall a. Floating a => a -> a
log
    sqrt :: Dim m (Dim n (Matrix t)) -> Dim m (Dim n (Matrix t))
sqrt  = ((Dim n (Matrix t) -> Dim n (Matrix t))
-> Dim m (Dim n (Matrix t)) -> Dim m (Dim n (Matrix t))
forall (c :: * -> *) t (n :: Nat).
(c t -> c t) -> Dim n (c t) -> Dim n (c t)
lift1F ((Dim n (Matrix t) -> Dim n (Matrix t))
 -> Dim m (Dim n (Matrix t)) -> Dim m (Dim n (Matrix t)))
-> ((Matrix t -> Matrix t) -> Dim n (Matrix t) -> Dim n (Matrix t))
-> (Matrix t -> Matrix t)
-> Dim m (Dim n (Matrix t))
-> Dim m (Dim n (Matrix t))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Matrix t -> Matrix t) -> Dim n (Matrix t) -> Dim n (Matrix t)
forall (c :: * -> *) t (n :: Nat).
(c t -> c t) -> Dim n (c t) -> Dim n (c t)
lift1F) Matrix t -> Matrix t
forall a. Floating a => a -> a
sqrt
    ** :: Dim m (Dim n (Matrix t))
-> Dim m (Dim n (Matrix t)) -> Dim m (Dim n (Matrix t))
(**)  = ((Dim n (Matrix t) -> Dim n (Matrix t) -> Dim n (Matrix t))
-> Dim m (Dim n (Matrix t))
-> Dim m (Dim n (Matrix t))
-> Dim m (Dim n (Matrix t))
forall (c :: * -> *) t (n :: Nat).
(c t -> c t -> c t) -> Dim n (c t) -> Dim n (c t) -> Dim n (c t)
lift2F ((Dim n (Matrix t) -> Dim n (Matrix t) -> Dim n (Matrix t))
 -> Dim m (Dim n (Matrix t))
 -> Dim m (Dim n (Matrix t))
 -> Dim m (Dim n (Matrix t)))
-> ((Matrix t -> Matrix t -> Matrix t)
    -> Dim n (Matrix t) -> Dim n (Matrix t) -> Dim n (Matrix t))
-> (Matrix t -> Matrix t -> Matrix t)
-> Dim m (Dim n (Matrix t))
-> Dim m (Dim n (Matrix t))
-> Dim m (Dim n (Matrix t))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Matrix t -> Matrix t -> Matrix t)
-> Dim n (Matrix t) -> Dim n (Matrix t) -> Dim n (Matrix t)
forall (c :: * -> *) t (n :: Nat).
(c t -> c t -> c t) -> Dim n (c t) -> Dim n (c t) -> Dim n (c t)
lift2F) Matrix t -> Matrix t -> Matrix t
forall a. Floating a => a -> a -> a
(**)
    pi :: Dim m (Dim n (Matrix t))
pi    = Dim n (Matrix t) -> Dim m (Dim n (Matrix t))
forall (n :: Nat) t. t -> Dim n t
Dim (Matrix t -> Dim n (Matrix t)
forall (n :: Nat) t. t -> Dim n t
Dim Matrix t
forall a. Floating a => a
pi)

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


adaptDiag :: (L m n -> L m n -> p) -> L m n -> L m n -> p
adaptDiag L m n -> L m n -> p
f a :: L m n
a@(L m n -> Maybe (ℝ, Vector ℝ, (Int, Int))
forall (m :: Nat) (n :: Nat).
(KnownNat m, KnownNat n) =>
L m n -> Maybe (ℝ, Vector ℝ, (Int, Int))
isDiag -> Just (ℝ, Vector ℝ, (Int, Int))
_) L m n
b | L m n -> Bool
forall (n :: Nat) (m :: Nat).
(KnownNat n, KnownNat m) =>
L m n -> Bool
isFull L m n
b = L m n -> L m n -> p
f (Matrix ℝ -> L m n
forall (m :: Nat) (n :: Nat). Matrix ℝ -> L m n
mkL (L m n -> Matrix ℝ
forall t s (d :: * -> *). Sized t s d => s -> d t
extract L m n
a)) L m n
b
adaptDiag L m n -> L m n -> p
f L m n
a b :: L m n
b@(L m n -> Maybe (ℝ, Vector ℝ, (Int, Int))
forall (m :: Nat) (n :: Nat).
(KnownNat m, KnownNat n) =>
L m n -> Maybe (ℝ, Vector ℝ, (Int, Int))
isDiag -> Just (ℝ, Vector ℝ, (Int, Int))
_) | L m n -> Bool
forall (n :: Nat) (m :: Nat).
(KnownNat n, KnownNat m) =>
L m n -> Bool
isFull L m n
a = L m n -> L m n -> p
f L m n
a (Matrix ℝ -> L m n
forall (m :: Nat) (n :: Nat). Matrix ℝ -> L m n
mkL (L m n -> Matrix ℝ
forall t s (d :: * -> *). Sized t s d => s -> d t
extract L m n
b))
adaptDiag L m n -> L m n -> p
f L m n
a L m n
b = L m n -> L m n -> p
f L m n
a L m n
b

isFull :: L m n -> Bool
isFull L m n
m = L m n -> Maybe (ℝ, Vector ℝ, (Int, Int))
forall (m :: Nat) (n :: Nat).
(KnownNat m, KnownNat n) =>
L m n -> Maybe (ℝ, Vector ℝ, (Int, Int))
isDiag L m n
m Maybe (ℝ, Vector ℝ, (Int, Int))
-> Maybe (ℝ, Vector ℝ, (Int, Int)) -> Bool
forall a. Eq a => a -> a -> Bool
== Maybe (ℝ, Vector ℝ, (Int, Int))
forall a. Maybe a
Nothing Bool -> Bool -> Bool
&& Bool -> Bool
not (Matrix ℝ -> Bool
forall t. Matrix t -> Bool
singleM (L m n -> Matrix ℝ
forall t s (d :: * -> *). Sized t s d => s -> d t
unwrap L m n
m))


lift1L :: (Dim m (Dim n (Matrix ℝ)) -> Dim m (Dim n (Matrix ℝ)))
-> L m n -> L m n
lift1L Dim m (Dim n (Matrix ℝ)) -> Dim m (Dim n (Matrix ℝ))
f (L Dim m (Dim n (Matrix ℝ))
v) = Dim m (Dim n (Matrix ℝ)) -> L m n
forall (m :: Nat) (n :: Nat). Dim m (Dim n (Matrix ℝ)) -> L m n
L (Dim m (Dim n (Matrix ℝ)) -> Dim m (Dim n (Matrix ℝ))
f Dim m (Dim n (Matrix ℝ))
v)
lift2L :: (Dim m (Dim n (Matrix ℝ))
 -> Dim m (Dim n (Matrix ℝ)) -> Dim m (Dim n (Matrix ℝ)))
-> L m n -> L m n -> L m n
lift2L Dim m (Dim n (Matrix ℝ))
-> Dim m (Dim n (Matrix ℝ)) -> Dim m (Dim n (Matrix ℝ))
f (L Dim m (Dim n (Matrix ℝ))
a) (L Dim m (Dim n (Matrix ℝ))
b) = Dim m (Dim n (Matrix ℝ)) -> L m n
forall (m :: Nat) (n :: Nat). Dim m (Dim n (Matrix ℝ)) -> L m n
L (Dim m (Dim n (Matrix ℝ))
-> Dim m (Dim n (Matrix ℝ)) -> Dim m (Dim n (Matrix ℝ))
f Dim m (Dim n (Matrix ℝ))
a Dim m (Dim n (Matrix ℝ))
b)
lift2LD :: (Dim m (Dim n (Matrix ℝ))
 -> Dim m (Dim n (Matrix ℝ)) -> Dim m (Dim n (Matrix ℝ)))
-> L m n -> L m n -> L m n
lift2LD Dim m (Dim n (Matrix ℝ))
-> Dim m (Dim n (Matrix ℝ)) -> Dim m (Dim n (Matrix ℝ))
f = (L m n -> L m n -> L m n) -> L m n -> L m n -> L m n
forall (m :: Nat) (n :: Nat) (n :: Nat) (m :: Nat) p.
(KnownNat m, KnownNat n, KnownNat n, KnownNat m) =>
(L m n -> L m n -> p) -> L m n -> L m n -> p
adaptDiag ((Dim m (Dim n (Matrix ℝ))
 -> Dim m (Dim n (Matrix ℝ)) -> Dim m (Dim n (Matrix ℝ)))
-> L m n -> L m n -> L m n
forall (m :: Nat) (n :: Nat) (m :: Nat) (n :: Nat) (m :: Nat)
       (n :: Nat).
(Dim m (Dim n (Matrix ℝ))
 -> Dim m (Dim n (Matrix ℝ)) -> Dim m (Dim n (Matrix ℝ)))
-> L m n -> L m n -> L m n
lift2L Dim m (Dim n (Matrix ℝ))
-> Dim m (Dim n (Matrix ℝ)) -> Dim m (Dim n (Matrix ℝ))
f)


instance (KnownNat n, KnownNat m) =>  Num (L n m)
  where
    + :: L n m -> L n m -> L n m
(+) = (Dim n (Dim m (Matrix ℝ))
 -> Dim n (Dim m (Matrix ℝ)) -> Dim n (Dim m (Matrix ℝ)))
-> L n m -> L n m -> L n m
forall (m :: Nat) (n :: Nat) (n :: Nat) (m :: Nat) (m :: Nat)
       (n :: Nat).
(KnownNat m, KnownNat n, KnownNat n, KnownNat m) =>
(Dim m (Dim n (Matrix ℝ))
 -> Dim m (Dim n (Matrix ℝ)) -> Dim m (Dim n (Matrix ℝ)))
-> L m n -> L m n -> L m n
lift2LD Dim n (Dim m (Matrix ℝ))
-> Dim n (Dim m (Matrix ℝ)) -> Dim n (Dim m (Matrix ℝ))
forall a. Num a => a -> a -> a
(+)
    * :: L n m -> L n m -> L n m
(*) = (Dim n (Dim m (Matrix ℝ))
 -> Dim n (Dim m (Matrix ℝ)) -> Dim n (Dim m (Matrix ℝ)))
-> L n m -> L n m -> L n m
forall (m :: Nat) (n :: Nat) (n :: Nat) (m :: Nat) (m :: Nat)
       (n :: Nat).
(KnownNat m, KnownNat n, KnownNat n, KnownNat m) =>
(Dim m (Dim n (Matrix ℝ))
 -> Dim m (Dim n (Matrix ℝ)) -> Dim m (Dim n (Matrix ℝ)))
-> L m n -> L m n -> L m n
lift2LD Dim n (Dim m (Matrix ℝ))
-> Dim n (Dim m (Matrix ℝ)) -> Dim n (Dim m (Matrix ℝ))
forall a. Num a => a -> a -> a
(*)
    (-) = (Dim n (Dim m (Matrix ℝ))
 -> Dim n (Dim m (Matrix ℝ)) -> Dim n (Dim m (Matrix ℝ)))
-> L n m -> L n m -> L n m
forall (m :: Nat) (n :: Nat) (n :: Nat) (m :: Nat) (m :: Nat)
       (n :: Nat).
(KnownNat m, KnownNat n, KnownNat n, KnownNat m) =>
(Dim m (Dim n (Matrix ℝ))
 -> Dim m (Dim n (Matrix ℝ)) -> Dim m (Dim n (Matrix ℝ)))
-> L m n -> L m n -> L m n
lift2LD (-)
    abs :: L n m -> L n m
abs = (Dim n (Dim m (Matrix ℝ)) -> Dim n (Dim m (Matrix ℝ)))
-> L n m -> L n m
forall (m :: Nat) (n :: Nat) (m :: Nat) (n :: Nat).
(Dim m (Dim n (Matrix ℝ)) -> Dim m (Dim n (Matrix ℝ)))
-> L m n -> L m n
lift1L Dim n (Dim m (Matrix ℝ)) -> Dim n (Dim m (Matrix ℝ))
forall a. Num a => a -> a
abs
    signum :: L n m -> L n m
signum = (Dim n (Dim m (Matrix ℝ)) -> Dim n (Dim m (Matrix ℝ)))
-> L n m -> L n m
forall (m :: Nat) (n :: Nat) (m :: Nat) (n :: Nat).
(Dim m (Dim n (Matrix ℝ)) -> Dim m (Dim n (Matrix ℝ)))
-> L m n -> L m n
lift1L Dim n (Dim m (Matrix ℝ)) -> Dim n (Dim m (Matrix ℝ))
forall a. Num a => a -> a
signum
    negate :: L n m -> L n m
negate = (Dim n (Dim m (Matrix ℝ)) -> Dim n (Dim m (Matrix ℝ)))
-> L n m -> L n m
forall (m :: Nat) (n :: Nat) (m :: Nat) (n :: Nat).
(Dim m (Dim n (Matrix ℝ)) -> Dim m (Dim n (Matrix ℝ)))
-> L m n -> L m n
lift1L Dim n (Dim m (Matrix ℝ)) -> Dim n (Dim m (Matrix ℝ))
forall a. Num a => a -> a
negate
    fromInteger :: Integer -> L n m
fromInteger = Dim n (Dim m (Matrix ℝ)) -> L n m
forall (m :: Nat) (n :: Nat). Dim m (Dim n (Matrix ℝ)) -> L m n
L (Dim n (Dim m (Matrix ℝ)) -> L n m)
-> (Integer -> Dim n (Dim m (Matrix ℝ))) -> Integer -> L n m
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Dim m (Matrix ℝ) -> Dim n (Dim m (Matrix ℝ))
forall (n :: Nat) t. t -> Dim n t
Dim (Dim m (Matrix ℝ) -> Dim n (Dim m (Matrix ℝ)))
-> (Integer -> Dim m (Matrix ℝ))
-> Integer
-> Dim n (Dim m (Matrix ℝ))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Matrix ℝ -> Dim m (Matrix ℝ)
forall (n :: Nat) t. t -> Dim n t
Dim (Matrix ℝ -> Dim m (Matrix ℝ))
-> (Integer -> Matrix ℝ) -> Integer -> Dim m (Matrix ℝ)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Matrix ℝ
forall a. Num a => Integer -> a
fromInteger

instance (KnownNat n, KnownNat m) => Fractional (L n m)
  where
    fromRational :: Rational -> L n m
fromRational = Dim n (Dim m (Matrix ℝ)) -> L n m
forall (m :: Nat) (n :: Nat). Dim m (Dim n (Matrix ℝ)) -> L m n
L (Dim n (Dim m (Matrix ℝ)) -> L n m)
-> (Rational -> Dim n (Dim m (Matrix ℝ))) -> Rational -> L n m
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Dim m (Matrix ℝ) -> Dim n (Dim m (Matrix ℝ))
forall (n :: Nat) t. t -> Dim n t
Dim (Dim m (Matrix ℝ) -> Dim n (Dim m (Matrix ℝ)))
-> (Rational -> Dim m (Matrix ℝ))
-> Rational
-> Dim n (Dim m (Matrix ℝ))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Matrix ℝ -> Dim m (Matrix ℝ)
forall (n :: Nat) t. t -> Dim n t
Dim (Matrix ℝ -> Dim m (Matrix ℝ))
-> (Rational -> Matrix ℝ) -> Rational -> Dim m (Matrix ℝ)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Rational -> Matrix ℝ
forall a. Fractional a => Rational -> a
fromRational
    / :: L n m -> L n m -> L n m
(/) = (Dim n (Dim m (Matrix ℝ))
 -> Dim n (Dim m (Matrix ℝ)) -> Dim n (Dim m (Matrix ℝ)))
-> L n m -> L n m -> L n m
forall (m :: Nat) (n :: Nat) (n :: Nat) (m :: Nat) (m :: Nat)
       (n :: Nat).
(KnownNat m, KnownNat n, KnownNat n, KnownNat m) =>
(Dim m (Dim n (Matrix ℝ))
 -> Dim m (Dim n (Matrix ℝ)) -> Dim m (Dim n (Matrix ℝ)))
-> L m n -> L m n -> L m n
lift2LD Dim n (Dim m (Matrix ℝ))
-> Dim n (Dim m (Matrix ℝ)) -> Dim n (Dim m (Matrix ℝ))
forall a. Fractional a => a -> a -> a
(/)

instance (KnownNat n, KnownNat m) => Floating (L n m) where
    sin :: L n m -> L n m
sin   = (Dim n (Dim m (Matrix ℝ)) -> Dim n (Dim m (Matrix ℝ)))
-> L n m -> L n m
forall (m :: Nat) (n :: Nat) (m :: Nat) (n :: Nat).
(Dim m (Dim n (Matrix ℝ)) -> Dim m (Dim n (Matrix ℝ)))
-> L m n -> L m n
lift1L Dim n (Dim m (Matrix ℝ)) -> Dim n (Dim m (Matrix ℝ))
forall a. Floating a => a -> a
sin
    cos :: L n m -> L n m
cos   = (Dim n (Dim m (Matrix ℝ)) -> Dim n (Dim m (Matrix ℝ)))
-> L n m -> L n m
forall (m :: Nat) (n :: Nat) (m :: Nat) (n :: Nat).
(Dim m (Dim n (Matrix ℝ)) -> Dim m (Dim n (Matrix ℝ)))
-> L m n -> L m n
lift1L Dim n (Dim m (Matrix ℝ)) -> Dim n (Dim m (Matrix ℝ))
forall a. Floating a => a -> a
cos
    tan :: L n m -> L n m
tan   = (Dim n (Dim m (Matrix ℝ)) -> Dim n (Dim m (Matrix ℝ)))
-> L n m -> L n m
forall (m :: Nat) (n :: Nat) (m :: Nat) (n :: Nat).
(Dim m (Dim n (Matrix ℝ)) -> Dim m (Dim n (Matrix ℝ)))
-> L m n -> L m n
lift1L Dim n (Dim m (Matrix ℝ)) -> Dim n (Dim m (Matrix ℝ))
forall a. Floating a => a -> a
tan
    asin :: L n m -> L n m
asin  = (Dim n (Dim m (Matrix ℝ)) -> Dim n (Dim m (Matrix ℝ)))
-> L n m -> L n m
forall (m :: Nat) (n :: Nat) (m :: Nat) (n :: Nat).
(Dim m (Dim n (Matrix ℝ)) -> Dim m (Dim n (Matrix ℝ)))
-> L m n -> L m n
lift1L Dim n (Dim m (Matrix ℝ)) -> Dim n (Dim m (Matrix ℝ))
forall a. Floating a => a -> a
asin
    acos :: L n m -> L n m
acos  = (Dim n (Dim m (Matrix ℝ)) -> Dim n (Dim m (Matrix ℝ)))
-> L n m -> L n m
forall (m :: Nat) (n :: Nat) (m :: Nat) (n :: Nat).
(Dim m (Dim n (Matrix ℝ)) -> Dim m (Dim n (Matrix ℝ)))
-> L m n -> L m n
lift1L Dim n (Dim m (Matrix ℝ)) -> Dim n (Dim m (Matrix ℝ))
forall a. Floating a => a -> a
acos
    atan :: L n m -> L n m
atan  = (Dim n (Dim m (Matrix ℝ)) -> Dim n (Dim m (Matrix ℝ)))
-> L n m -> L n m
forall (m :: Nat) (n :: Nat) (m :: Nat) (n :: Nat).
(Dim m (Dim n (Matrix ℝ)) -> Dim m (Dim n (Matrix ℝ)))
-> L m n -> L m n
lift1L Dim n (Dim m (Matrix ℝ)) -> Dim n (Dim m (Matrix ℝ))
forall a. Floating a => a -> a
atan
    sinh :: L n m -> L n m
sinh  = (Dim n (Dim m (Matrix ℝ)) -> Dim n (Dim m (Matrix ℝ)))
-> L n m -> L n m
forall (m :: Nat) (n :: Nat) (m :: Nat) (n :: Nat).
(Dim m (Dim n (Matrix ℝ)) -> Dim m (Dim n (Matrix ℝ)))
-> L m n -> L m n
lift1L Dim n (Dim m (Matrix ℝ)) -> Dim n (Dim m (Matrix ℝ))
forall a. Floating a => a -> a
sinh
    cosh :: L n m -> L n m
cosh  = (Dim n (Dim m (Matrix ℝ)) -> Dim n (Dim m (Matrix ℝ)))
-> L n m -> L n m
forall (m :: Nat) (n :: Nat) (m :: Nat) (n :: Nat).
(Dim m (Dim n (Matrix ℝ)) -> Dim m (Dim n (Matrix ℝ)))
-> L m n -> L m n
lift1L Dim n (Dim m (Matrix ℝ)) -> Dim n (Dim m (Matrix ℝ))
forall a. Floating a => a -> a
cosh
    tanh :: L n m -> L n m
tanh  = (Dim n (Dim m (Matrix ℝ)) -> Dim n (Dim m (Matrix ℝ)))
-> L n m -> L n m
forall (m :: Nat) (n :: Nat) (m :: Nat) (n :: Nat).
(Dim m (Dim n (Matrix ℝ)) -> Dim m (Dim n (Matrix ℝ)))
-> L m n -> L m n
lift1L Dim n (Dim m (Matrix ℝ)) -> Dim n (Dim m (Matrix ℝ))
forall a. Floating a => a -> a
tanh
    asinh :: L n m -> L n m
asinh = (Dim n (Dim m (Matrix ℝ)) -> Dim n (Dim m (Matrix ℝ)))
-> L n m -> L n m
forall (m :: Nat) (n :: Nat) (m :: Nat) (n :: Nat).
(Dim m (Dim n (Matrix ℝ)) -> Dim m (Dim n (Matrix ℝ)))
-> L m n -> L m n
lift1L Dim n (Dim m (Matrix ℝ)) -> Dim n (Dim m (Matrix ℝ))
forall a. Floating a => a -> a
asinh
    acosh :: L n m -> L n m
acosh = (Dim n (Dim m (Matrix ℝ)) -> Dim n (Dim m (Matrix ℝ)))
-> L n m -> L n m
forall (m :: Nat) (n :: Nat) (m :: Nat) (n :: Nat).
(Dim m (Dim n (Matrix ℝ)) -> Dim m (Dim n (Matrix ℝ)))
-> L m n -> L m n
lift1L Dim n (Dim m (Matrix ℝ)) -> Dim n (Dim m (Matrix ℝ))
forall a. Floating a => a -> a
acosh
    atanh :: L n m -> L n m
atanh = (Dim n (Dim m (Matrix ℝ)) -> Dim n (Dim m (Matrix ℝ)))
-> L n m -> L n m
forall (m :: Nat) (n :: Nat) (m :: Nat) (n :: Nat).
(Dim m (Dim n (Matrix ℝ)) -> Dim m (Dim n (Matrix ℝ)))
-> L m n -> L m n
lift1L Dim n (Dim m (Matrix ℝ)) -> Dim n (Dim m (Matrix ℝ))
forall a. Floating a => a -> a
atanh
    exp :: L n m -> L n m
exp   = (Dim n (Dim m (Matrix ℝ)) -> Dim n (Dim m (Matrix ℝ)))
-> L n m -> L n m
forall (m :: Nat) (n :: Nat) (m :: Nat) (n :: Nat).
(Dim m (Dim n (Matrix ℝ)) -> Dim m (Dim n (Matrix ℝ)))
-> L m n -> L m n
lift1L Dim n (Dim m (Matrix ℝ)) -> Dim n (Dim m (Matrix ℝ))
forall a. Floating a => a -> a
exp
    log :: L n m -> L n m
log   = (Dim n (Dim m (Matrix ℝ)) -> Dim n (Dim m (Matrix ℝ)))
-> L n m -> L n m
forall (m :: Nat) (n :: Nat) (m :: Nat) (n :: Nat).
(Dim m (Dim n (Matrix ℝ)) -> Dim m (Dim n (Matrix ℝ)))
-> L m n -> L m n
lift1L Dim n (Dim m (Matrix ℝ)) -> Dim n (Dim m (Matrix ℝ))
forall a. Floating a => a -> a
log
    sqrt :: L n m -> L n m
sqrt  = (Dim n (Dim m (Matrix ℝ)) -> Dim n (Dim m (Matrix ℝ)))
-> L n m -> L n m
forall (m :: Nat) (n :: Nat) (m :: Nat) (n :: Nat).
(Dim m (Dim n (Matrix ℝ)) -> Dim m (Dim n (Matrix ℝ)))
-> L m n -> L m n
lift1L Dim n (Dim m (Matrix ℝ)) -> Dim n (Dim m (Matrix ℝ))
forall a. Floating a => a -> a
sqrt
    ** :: L n m -> L n m -> L n m
(**)  = (Dim n (Dim m (Matrix ℝ))
 -> Dim n (Dim m (Matrix ℝ)) -> Dim n (Dim m (Matrix ℝ)))
-> L n m -> L n m -> L n m
forall (m :: Nat) (n :: Nat) (n :: Nat) (m :: Nat) (m :: Nat)
       (n :: Nat).
(KnownNat m, KnownNat n, KnownNat n, KnownNat m) =>
(Dim m (Dim n (Matrix ℝ))
 -> Dim m (Dim n (Matrix ℝ)) -> Dim m (Dim n (Matrix ℝ)))
-> L m n -> L m n -> L m n
lift2LD Dim n (Dim m (Matrix ℝ))
-> Dim n (Dim m (Matrix ℝ)) -> Dim n (Dim m (Matrix ℝ))
forall a. Floating a => a -> a -> a
(**)
    pi :: L n m
pi    = ℝ -> L n m
forall t s (d :: * -> *). Sized t s d => t -> s
konst ℝ
forall a. Floating a => a
pi

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

adaptDiagC :: (M m n -> M m n -> p) -> M m n -> M m n -> p
adaptDiagC M m n -> M m n -> p
f a :: M m n
a@(M m n -> Maybe (ℂ, Vector ℂ, (Int, Int))
forall (m :: Nat) (n :: Nat).
(KnownNat m, KnownNat n) =>
M m n -> Maybe (ℂ, Vector ℂ, (Int, Int))
isDiagC -> Just (ℂ, Vector ℂ, (Int, Int))
_) M m n
b | M m n -> Bool
forall (n :: Nat) (m :: Nat).
(KnownNat n, KnownNat m) =>
M m n -> Bool
isFullC M m n
b = M m n -> M m n -> p
f (Matrix ℂ -> M m n
forall (m :: Nat) (n :: Nat). Matrix ℂ -> M m n
mkM (M m n -> Matrix ℂ
forall t s (d :: * -> *). Sized t s d => s -> d t
extract M m n
a)) M m n
b
adaptDiagC M m n -> M m n -> p
f M m n
a b :: M m n
b@(M m n -> Maybe (ℂ, Vector ℂ, (Int, Int))
forall (m :: Nat) (n :: Nat).
(KnownNat m, KnownNat n) =>
M m n -> Maybe (ℂ, Vector ℂ, (Int, Int))
isDiagC -> Just (ℂ, Vector ℂ, (Int, Int))
_) | M m n -> Bool
forall (n :: Nat) (m :: Nat).
(KnownNat n, KnownNat m) =>
M m n -> Bool
isFullC M m n
a = M m n -> M m n -> p
f M m n
a (Matrix ℂ -> M m n
forall (m :: Nat) (n :: Nat). Matrix ℂ -> M m n
mkM (M m n -> Matrix ℂ
forall t s (d :: * -> *). Sized t s d => s -> d t
extract M m n
b))
adaptDiagC M m n -> M m n -> p
f M m n
a M m n
b = M m n -> M m n -> p
f M m n
a M m n
b

isFullC :: M m n -> Bool
isFullC M m n
m = M m n -> Maybe (ℂ, Vector ℂ, (Int, Int))
forall (m :: Nat) (n :: Nat).
(KnownNat m, KnownNat n) =>
M m n -> Maybe (ℂ, Vector ℂ, (Int, Int))
isDiagC M m n
m Maybe (ℂ, Vector ℂ, (Int, Int))
-> Maybe (ℂ, Vector ℂ, (Int, Int)) -> Bool
forall a. Eq a => a -> a -> Bool
== Maybe (ℂ, Vector ℂ, (Int, Int))
forall a. Maybe a
Nothing Bool -> Bool -> Bool
&& Bool -> Bool
not (Matrix ℂ -> Bool
forall t. Matrix t -> Bool
singleM (M m n -> Matrix ℂ
forall t s (d :: * -> *). Sized t s d => s -> d t
unwrap M m n
m))

lift1M :: (Dim m (Dim n (Matrix ℂ)) -> Dim m (Dim n (Matrix ℂ)))
-> M m n -> M m n
lift1M Dim m (Dim n (Matrix ℂ)) -> Dim m (Dim n (Matrix ℂ))
f (M Dim m (Dim n (Matrix ℂ))
v) = Dim m (Dim n (Matrix ℂ)) -> M m n
forall (m :: Nat) (n :: Nat). Dim m (Dim n (Matrix ℂ)) -> M m n
M (Dim m (Dim n (Matrix ℂ)) -> Dim m (Dim n (Matrix ℂ))
f Dim m (Dim n (Matrix ℂ))
v)
lift2M :: (Dim m (Dim n (Matrix ℂ))
 -> Dim m (Dim n (Matrix ℂ)) -> Dim m (Dim n (Matrix ℂ)))
-> M m n -> M m n -> M m n
lift2M Dim m (Dim n (Matrix ℂ))
-> Dim m (Dim n (Matrix ℂ)) -> Dim m (Dim n (Matrix ℂ))
f (M Dim m (Dim n (Matrix ℂ))
a) (M Dim m (Dim n (Matrix ℂ))
b) = Dim m (Dim n (Matrix ℂ)) -> M m n
forall (m :: Nat) (n :: Nat). Dim m (Dim n (Matrix ℂ)) -> M m n
M (Dim m (Dim n (Matrix ℂ))
-> Dim m (Dim n (Matrix ℂ)) -> Dim m (Dim n (Matrix ℂ))
f Dim m (Dim n (Matrix ℂ))
a Dim m (Dim n (Matrix ℂ))
b)
lift2MD :: (Dim m (Dim n (Matrix ℂ))
 -> Dim m (Dim n (Matrix ℂ)) -> Dim m (Dim n (Matrix ℂ)))
-> M m n -> M m n -> M m n
lift2MD Dim m (Dim n (Matrix ℂ))
-> Dim m (Dim n (Matrix ℂ)) -> Dim m (Dim n (Matrix ℂ))
f = (M m n -> M m n -> M m n) -> M m n -> M m n -> M m n
forall (m :: Nat) (n :: Nat) (n :: Nat) (m :: Nat) p.
(KnownNat m, KnownNat n, KnownNat n, KnownNat m) =>
(M m n -> M m n -> p) -> M m n -> M m n -> p
adaptDiagC ((Dim m (Dim n (Matrix ℂ))
 -> Dim m (Dim n (Matrix ℂ)) -> Dim m (Dim n (Matrix ℂ)))
-> M m n -> M m n -> M m n
forall (m :: Nat) (n :: Nat) (m :: Nat) (n :: Nat) (m :: Nat)
       (n :: Nat).
(Dim m (Dim n (Matrix ℂ))
 -> Dim m (Dim n (Matrix ℂ)) -> Dim m (Dim n (Matrix ℂ)))
-> M m n -> M m n -> M m n
lift2M Dim m (Dim n (Matrix ℂ))
-> Dim m (Dim n (Matrix ℂ)) -> Dim m (Dim n (Matrix ℂ))
f)

instance (KnownNat n, KnownNat m) =>  Num (M n m)
  where
    + :: M n m -> M n m -> M n m
(+) = (Dim n (Dim m (Matrix ℂ))
 -> Dim n (Dim m (Matrix ℂ)) -> Dim n (Dim m (Matrix ℂ)))
-> M n m -> M n m -> M n m
forall (m :: Nat) (n :: Nat) (n :: Nat) (m :: Nat) (m :: Nat)
       (n :: Nat).
(KnownNat m, KnownNat n, KnownNat n, KnownNat m) =>
(Dim m (Dim n (Matrix ℂ))
 -> Dim m (Dim n (Matrix ℂ)) -> Dim m (Dim n (Matrix ℂ)))
-> M m n -> M m n -> M m n
lift2MD Dim n (Dim m (Matrix ℂ))
-> Dim n (Dim m (Matrix ℂ)) -> Dim n (Dim m (Matrix ℂ))
forall a. Num a => a -> a -> a
(+)
    * :: M n m -> M n m -> M n m
(*) = (Dim n (Dim m (Matrix ℂ))
 -> Dim n (Dim m (Matrix ℂ)) -> Dim n (Dim m (Matrix ℂ)))
-> M n m -> M n m -> M n m
forall (m :: Nat) (n :: Nat) (n :: Nat) (m :: Nat) (m :: Nat)
       (n :: Nat).
(KnownNat m, KnownNat n, KnownNat n, KnownNat m) =>
(Dim m (Dim n (Matrix ℂ))
 -> Dim m (Dim n (Matrix ℂ)) -> Dim m (Dim n (Matrix ℂ)))
-> M m n -> M m n -> M m n
lift2MD Dim n (Dim m (Matrix ℂ))
-> Dim n (Dim m (Matrix ℂ)) -> Dim n (Dim m (Matrix ℂ))
forall a. Num a => a -> a -> a
(*)
    (-) = (Dim n (Dim m (Matrix ℂ))
 -> Dim n (Dim m (Matrix ℂ)) -> Dim n (Dim m (Matrix ℂ)))
-> M n m -> M n m -> M n m
forall (m :: Nat) (n :: Nat) (n :: Nat) (m :: Nat) (m :: Nat)
       (n :: Nat).
(KnownNat m, KnownNat n, KnownNat n, KnownNat m) =>
(Dim m (Dim n (Matrix ℂ))
 -> Dim m (Dim n (Matrix ℂ)) -> Dim m (Dim n (Matrix ℂ)))
-> M m n -> M m n -> M m n
lift2MD (-)
    abs :: M n m -> M n m
abs = (Dim n (Dim m (Matrix ℂ)) -> Dim n (Dim m (Matrix ℂ)))
-> M n m -> M n m
forall (m :: Nat) (n :: Nat) (m :: Nat) (n :: Nat).
(Dim m (Dim n (Matrix ℂ)) -> Dim m (Dim n (Matrix ℂ)))
-> M m n -> M m n
lift1M Dim n (Dim m (Matrix ℂ)) -> Dim n (Dim m (Matrix ℂ))
forall a. Num a => a -> a
abs
    signum :: M n m -> M n m
signum = (Dim n (Dim m (Matrix ℂ)) -> Dim n (Dim m (Matrix ℂ)))
-> M n m -> M n m
forall (m :: Nat) (n :: Nat) (m :: Nat) (n :: Nat).
(Dim m (Dim n (Matrix ℂ)) -> Dim m (Dim n (Matrix ℂ)))
-> M m n -> M m n
lift1M Dim n (Dim m (Matrix ℂ)) -> Dim n (Dim m (Matrix ℂ))
forall a. Num a => a -> a
signum
    negate :: M n m -> M n m
negate = (Dim n (Dim m (Matrix ℂ)) -> Dim n (Dim m (Matrix ℂ)))
-> M n m -> M n m
forall (m :: Nat) (n :: Nat) (m :: Nat) (n :: Nat).
(Dim m (Dim n (Matrix ℂ)) -> Dim m (Dim n (Matrix ℂ)))
-> M m n -> M m n
lift1M Dim n (Dim m (Matrix ℂ)) -> Dim n (Dim m (Matrix ℂ))
forall a. Num a => a -> a
negate
    fromInteger :: Integer -> M n m
fromInteger = Dim n (Dim m (Matrix ℂ)) -> M n m
forall (m :: Nat) (n :: Nat). Dim m (Dim n (Matrix ℂ)) -> M m n
M (Dim n (Dim m (Matrix ℂ)) -> M n m)
-> (Integer -> Dim n (Dim m (Matrix ℂ))) -> Integer -> M n m
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Dim m (Matrix ℂ) -> Dim n (Dim m (Matrix ℂ))
forall (n :: Nat) t. t -> Dim n t
Dim (Dim m (Matrix ℂ) -> Dim n (Dim m (Matrix ℂ)))
-> (Integer -> Dim m (Matrix ℂ))
-> Integer
-> Dim n (Dim m (Matrix ℂ))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Matrix ℂ -> Dim m (Matrix ℂ)
forall (n :: Nat) t. t -> Dim n t
Dim (Matrix ℂ -> Dim m (Matrix ℂ))
-> (Integer -> Matrix ℂ) -> Integer -> Dim m (Matrix ℂ)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Matrix ℂ
forall a. Num a => Integer -> a
fromInteger

instance (KnownNat n, KnownNat m) => Fractional (M n m)
  where
    fromRational :: Rational -> M n m
fromRational = Dim n (Dim m (Matrix ℂ)) -> M n m
forall (m :: Nat) (n :: Nat). Dim m (Dim n (Matrix ℂ)) -> M m n
M (Dim n (Dim m (Matrix ℂ)) -> M n m)
-> (Rational -> Dim n (Dim m (Matrix ℂ))) -> Rational -> M n m
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Dim m (Matrix ℂ) -> Dim n (Dim m (Matrix ℂ))
forall (n :: Nat) t. t -> Dim n t
Dim (Dim m (Matrix ℂ) -> Dim n (Dim m (Matrix ℂ)))
-> (Rational -> Dim m (Matrix ℂ))
-> Rational
-> Dim n (Dim m (Matrix ℂ))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Matrix ℂ -> Dim m (Matrix ℂ)
forall (n :: Nat) t. t -> Dim n t
Dim (Matrix ℂ -> Dim m (Matrix ℂ))
-> (Rational -> Matrix ℂ) -> Rational -> Dim m (Matrix ℂ)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Rational -> Matrix ℂ
forall a. Fractional a => Rational -> a
fromRational
    / :: M n m -> M n m -> M n m
(/) = (Dim n (Dim m (Matrix ℂ))
 -> Dim n (Dim m (Matrix ℂ)) -> Dim n (Dim m (Matrix ℂ)))
-> M n m -> M n m -> M n m
forall (m :: Nat) (n :: Nat) (n :: Nat) (m :: Nat) (m :: Nat)
       (n :: Nat).
(KnownNat m, KnownNat n, KnownNat n, KnownNat m) =>
(Dim m (Dim n (Matrix ℂ))
 -> Dim m (Dim n (Matrix ℂ)) -> Dim m (Dim n (Matrix ℂ)))
-> M m n -> M m n -> M m n
lift2MD Dim n (Dim m (Matrix ℂ))
-> Dim n (Dim m (Matrix ℂ)) -> Dim n (Dim m (Matrix ℂ))
forall a. Fractional a => a -> a -> a
(/)

instance (KnownNat n, KnownNat m) => Floating (M n m) where
    sin :: M n m -> M n m
sin   = (Dim n (Dim m (Matrix ℂ)) -> Dim n (Dim m (Matrix ℂ)))
-> M n m -> M n m
forall (m :: Nat) (n :: Nat) (m :: Nat) (n :: Nat).
(Dim m (Dim n (Matrix ℂ)) -> Dim m (Dim n (Matrix ℂ)))
-> M m n -> M m n
lift1M Dim n (Dim m (Matrix ℂ)) -> Dim n (Dim m (Matrix ℂ))
forall a. Floating a => a -> a
sin
    cos :: M n m -> M n m
cos   = (Dim n (Dim m (Matrix ℂ)) -> Dim n (Dim m (Matrix ℂ)))
-> M n m -> M n m
forall (m :: Nat) (n :: Nat) (m :: Nat) (n :: Nat).
(Dim m (Dim n (Matrix ℂ)) -> Dim m (Dim n (Matrix ℂ)))
-> M m n -> M m n
lift1M Dim n (Dim m (Matrix ℂ)) -> Dim n (Dim m (Matrix ℂ))
forall a. Floating a => a -> a
cos
    tan :: M n m -> M n m
tan   = (Dim n (Dim m (Matrix ℂ)) -> Dim n (Dim m (Matrix ℂ)))
-> M n m -> M n m
forall (m :: Nat) (n :: Nat) (m :: Nat) (n :: Nat).
(Dim m (Dim n (Matrix ℂ)) -> Dim m (Dim n (Matrix ℂ)))
-> M m n -> M m n
lift1M Dim n (Dim m (Matrix ℂ)) -> Dim n (Dim m (Matrix ℂ))
forall a. Floating a => a -> a
tan
    asin :: M n m -> M n m
asin  = (Dim n (Dim m (Matrix ℂ)) -> Dim n (Dim m (Matrix ℂ)))
-> M n m -> M n m
forall (m :: Nat) (n :: Nat) (m :: Nat) (n :: Nat).
(Dim m (Dim n (Matrix ℂ)) -> Dim m (Dim n (Matrix ℂ)))
-> M m n -> M m n
lift1M Dim n (Dim m (Matrix ℂ)) -> Dim n (Dim m (Matrix ℂ))
forall a. Floating a => a -> a
asin
    acos :: M n m -> M n m
acos  = (Dim n (Dim m (Matrix ℂ)) -> Dim n (Dim m (Matrix ℂ)))
-> M n m -> M n m
forall (m :: Nat) (n :: Nat) (m :: Nat) (n :: Nat).
(Dim m (Dim n (Matrix ℂ)) -> Dim m (Dim n (Matrix ℂ)))
-> M m n -> M m n
lift1M Dim n (Dim m (Matrix ℂ)) -> Dim n (Dim m (Matrix ℂ))
forall a. Floating a => a -> a
acos
    atan :: M n m -> M n m
atan  = (Dim n (Dim m (Matrix ℂ)) -> Dim n (Dim m (Matrix ℂ)))
-> M n m -> M n m
forall (m :: Nat) (n :: Nat) (m :: Nat) (n :: Nat).
(Dim m (Dim n (Matrix ℂ)) -> Dim m (Dim n (Matrix ℂ)))
-> M m n -> M m n
lift1M Dim n (Dim m (Matrix ℂ)) -> Dim n (Dim m (Matrix ℂ))
forall a. Floating a => a -> a
atan
    sinh :: M n m -> M n m
sinh  = (Dim n (Dim m (Matrix ℂ)) -> Dim n (Dim m (Matrix ℂ)))
-> M n m -> M n m
forall (m :: Nat) (n :: Nat) (m :: Nat) (n :: Nat).
(Dim m (Dim n (Matrix ℂ)) -> Dim m (Dim n (Matrix ℂ)))
-> M m n -> M m n
lift1M Dim n (Dim m (Matrix ℂ)) -> Dim n (Dim m (Matrix ℂ))
forall a. Floating a => a -> a
sinh
    cosh :: M n m -> M n m
cosh  = (Dim n (Dim m (Matrix ℂ)) -> Dim n (Dim m (Matrix ℂ)))
-> M n m -> M n m
forall (m :: Nat) (n :: Nat) (m :: Nat) (n :: Nat).
(Dim m (Dim n (Matrix ℂ)) -> Dim m (Dim n (Matrix ℂ)))
-> M m n -> M m n
lift1M Dim n (Dim m (Matrix ℂ)) -> Dim n (Dim m (Matrix ℂ))
forall a. Floating a => a -> a
cosh
    tanh :: M n m -> M n m
tanh  = (Dim n (Dim m (Matrix ℂ)) -> Dim n (Dim m (Matrix ℂ)))
-> M n m -> M n m
forall (m :: Nat) (n :: Nat) (m :: Nat) (n :: Nat).
(Dim m (Dim n (Matrix ℂ)) -> Dim m (Dim n (Matrix ℂ)))
-> M m n -> M m n
lift1M Dim n (Dim m (Matrix ℂ)) -> Dim n (Dim m (Matrix ℂ))
forall a. Floating a => a -> a
tanh
    asinh :: M n m -> M n m
asinh = (Dim n (Dim m (Matrix ℂ)) -> Dim n (Dim m (Matrix ℂ)))
-> M n m -> M n m
forall (m :: Nat) (n :: Nat) (m :: Nat) (n :: Nat).
(Dim m (Dim n (Matrix ℂ)) -> Dim m (Dim n (Matrix ℂ)))
-> M m n -> M m n
lift1M Dim n (Dim m (Matrix ℂ)) -> Dim n (Dim m (Matrix ℂ))
forall a. Floating a => a -> a
asinh
    acosh :: M n m -> M n m
acosh = (Dim n (Dim m (Matrix ℂ)) -> Dim n (Dim m (Matrix ℂ)))
-> M n m -> M n m
forall (m :: Nat) (n :: Nat) (m :: Nat) (n :: Nat).
(Dim m (Dim n (Matrix ℂ)) -> Dim m (Dim n (Matrix ℂ)))
-> M m n -> M m n
lift1M Dim n (Dim m (Matrix ℂ)) -> Dim n (Dim m (Matrix ℂ))
forall a. Floating a => a -> a
acosh
    atanh :: M n m -> M n m
atanh = (Dim n (Dim m (Matrix ℂ)) -> Dim n (Dim m (Matrix ℂ)))
-> M n m -> M n m
forall (m :: Nat) (n :: Nat) (m :: Nat) (n :: Nat).
(Dim m (Dim n (Matrix ℂ)) -> Dim m (Dim n (Matrix ℂ)))
-> M m n -> M m n
lift1M Dim n (Dim m (Matrix ℂ)) -> Dim n (Dim m (Matrix ℂ))
forall a. Floating a => a -> a
atanh
    exp :: M n m -> M n m
exp   = (Dim n (Dim m (Matrix ℂ)) -> Dim n (Dim m (Matrix ℂ)))
-> M n m -> M n m
forall (m :: Nat) (n :: Nat) (m :: Nat) (n :: Nat).
(Dim m (Dim n (Matrix ℂ)) -> Dim m (Dim n (Matrix ℂ)))
-> M m n -> M m n
lift1M Dim n (Dim m (Matrix ℂ)) -> Dim n (Dim m (Matrix ℂ))
forall a. Floating a => a -> a
exp
    log :: M n m -> M n m
log   = (Dim n (Dim m (Matrix ℂ)) -> Dim n (Dim m (Matrix ℂ)))
-> M n m -> M n m
forall (m :: Nat) (n :: Nat) (m :: Nat) (n :: Nat).
(Dim m (Dim n (Matrix ℂ)) -> Dim m (Dim n (Matrix ℂ)))
-> M m n -> M m n
lift1M Dim n (Dim m (Matrix ℂ)) -> Dim n (Dim m (Matrix ℂ))
forall a. Floating a => a -> a
log
    sqrt :: M n m -> M n m
sqrt  = (Dim n (Dim m (Matrix ℂ)) -> Dim n (Dim m (Matrix ℂ)))
-> M n m -> M n m
forall (m :: Nat) (n :: Nat) (m :: Nat) (n :: Nat).
(Dim m (Dim n (Matrix ℂ)) -> Dim m (Dim n (Matrix ℂ)))
-> M m n -> M m n
lift1M Dim n (Dim m (Matrix ℂ)) -> Dim n (Dim m (Matrix ℂ))
forall a. Floating a => a -> a
sqrt
    ** :: M n m -> M n m -> M n m
(**)  = (Dim n (Dim m (Matrix ℂ))
 -> Dim n (Dim m (Matrix ℂ)) -> Dim n (Dim m (Matrix ℂ)))
-> M n m -> M n m -> M n m
forall (m :: Nat) (n :: Nat) (n :: Nat) (m :: Nat) (m :: Nat)
       (n :: Nat).
(KnownNat m, KnownNat n, KnownNat n, KnownNat m) =>
(Dim m (Dim n (Matrix ℂ))
 -> Dim m (Dim n (Matrix ℂ)) -> Dim m (Dim n (Matrix ℂ)))
-> M m n -> M m n -> M m n
lift2MD Dim n (Dim m (Matrix ℂ))
-> Dim n (Dim m (Matrix ℂ)) -> Dim n (Dim m (Matrix ℂ))
forall a. Floating a => a -> a -> a
(**)
    pi :: M n m
pi    = Dim n (Dim m (Matrix ℂ)) -> M n m
forall (m :: Nat) (n :: Nat). Dim m (Dim n (Matrix ℂ)) -> M m n
M Dim n (Dim m (Matrix ℂ))
forall a. Floating a => a
pi

instance Additive (R n) where
    add :: R n -> R n -> R n
add = R n -> R n -> R n
forall a. Num a => a -> a -> a
(+)

instance Additive (C n) where
    add :: C n -> C n -> C n
add = C n -> C n -> C n
forall a. Num a => a -> a -> a
(+)

instance (KnownNat m, KnownNat n) => Additive (L m n) where
    add :: L m n -> L m n -> L m n
add = L m n -> L m n -> L m n
forall a. Num a => a -> a -> a
(+)

instance (KnownNat m, KnownNat n) => Additive (M m n) where
    add :: M m n -> M m n -> M m n
add = M m n -> M m n -> M m n
forall a. Num a => a -> a -> a
(+)

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


class Disp t
  where
    disp :: Int -> t -> IO ()


instance (KnownNat m, KnownNat n) => Disp (L m n)
  where
    disp :: Int -> L m n -> IO ()
disp Int
n L m n
x = do
        let a :: Matrix ℝ
a = L m n -> Matrix ℝ
forall t s (d :: * -> *). Sized t s d => s -> d t
extract L m n
x
        let su :: String
su = Int -> Matrix ℝ -> String
LA.dispf Int
n Matrix ℝ
a
        String -> Int -> Int -> IO ()
forall r. PrintfType r => String -> r
printf String
"L %d %d" (Matrix ℝ -> Int
forall t. Matrix t -> Int
rows Matrix ℝ
a) (Matrix ℝ -> Int
forall t. Matrix t -> Int
cols Matrix ℝ
a) IO () -> IO () -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> String -> IO ()
putStr ((Char -> Bool) -> ShowS
forall a. (a -> Bool) -> [a] -> [a]
dropWhile (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/=Char
'\n') ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ String
su)

instance (KnownNat m, KnownNat n) => Disp (M m n)
  where
    disp :: Int -> M m n -> IO ()
disp Int
n M m n
x = do
        let a :: Matrix ℂ
a = M m n -> Matrix ℂ
forall t s (d :: * -> *). Sized t s d => s -> d t
extract M m n
x
        let su :: String
su = Int -> Matrix ℂ -> String
LA.dispcf Int
n Matrix ℂ
a
        String -> Int -> Int -> IO ()
forall r. PrintfType r => String -> r
printf String
"M %d %d" (Matrix ℂ -> Int
forall t. Matrix t -> Int
rows Matrix ℂ
a) (Matrix ℂ -> Int
forall t. Matrix t -> Int
cols Matrix ℂ
a) IO () -> IO () -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> String -> IO ()
putStr ((Char -> Bool) -> ShowS
forall a. (a -> Bool) -> [a] -> [a]
dropWhile (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/=Char
'\n') ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ String
su)


instance KnownNat n => Disp (R n)
  where
    disp :: Int -> R n -> IO ()
disp Int
n R n
v = do
        let su :: String
su = Int -> Matrix ℝ -> String
LA.dispf Int
n (Vector ℝ -> Matrix ℝ
forall a. Storable a => Vector a -> Matrix a
asRow (Vector ℝ -> Matrix ℝ) -> Vector ℝ -> Matrix ℝ
forall a b. (a -> b) -> a -> b
$ R n -> Vector ℝ
forall t s (d :: * -> *). Sized t s d => s -> d t
extract R n
v)
        String -> IO ()
putStr String
"R " IO () -> IO () -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> String -> IO ()
putStr (ShowS
forall a. [a] -> [a]
tail ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> ShowS
forall a. (a -> Bool) -> [a] -> [a]
dropWhile (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/=Char
'x') ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ String
su)

instance KnownNat n => Disp (C n)
  where
    disp :: Int -> C n -> IO ()
disp Int
n C n
v = do
        let su :: String
su = Int -> Matrix ℂ -> String
LA.dispcf Int
n (Vector ℂ -> Matrix ℂ
forall a. Storable a => Vector a -> Matrix a
asRow (Vector ℂ -> Matrix ℂ) -> Vector ℂ -> Matrix ℂ
forall a b. (a -> b) -> a -> b
$ C n -> Vector ℂ
forall t s (d :: * -> *). Sized t s d => s -> d t
extract C n
v)
        String -> IO ()
putStr String
"C " IO () -> IO () -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> String -> IO ()
putStr (ShowS
forall a. [a] -> [a]
tail ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> ShowS
forall a. (a -> Bool) -> [a] -> [a]
dropWhile (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/=Char
'x') ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ String
su)

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

overMatL' :: (KnownNat m, KnownNat n)
          => (LA.Matrix  -> LA.Matrix ) -> L m n -> L m n
overMatL' :: (Matrix ℝ -> Matrix ℝ) -> L m n -> L m n
overMatL' Matrix ℝ -> Matrix ℝ
f = Matrix ℝ -> L m n
forall (m :: Nat) (n :: Nat). Matrix ℝ -> L m n
mkL (Matrix ℝ -> L m n) -> (L m n -> Matrix ℝ) -> L m n -> L m n
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Matrix ℝ -> Matrix ℝ
f (Matrix ℝ -> Matrix ℝ) -> (L m n -> Matrix ℝ) -> L m n -> Matrix ℝ
forall b c a. (b -> c) -> (a -> b) -> a -> c
. L m n -> Matrix ℝ
forall t s (d :: * -> *). Sized t s d => s -> d t
unwrap
{-# INLINE overMatL' #-}

overMatM' :: (KnownNat m, KnownNat n)
          => (LA.Matrix  -> LA.Matrix ) -> M m n -> M m n
overMatM' :: (Matrix ℂ -> Matrix ℂ) -> M m n -> M m n
overMatM' Matrix ℂ -> Matrix ℂ
f = Matrix ℂ -> M m n
forall (m :: Nat) (n :: Nat). Matrix ℂ -> M m n
mkM (Matrix ℂ -> M m n) -> (M m n -> Matrix ℂ) -> M m n -> M m n
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Matrix ℂ -> Matrix ℂ
f (Matrix ℂ -> Matrix ℂ) -> (M m n -> Matrix ℂ) -> M m n -> Matrix ℂ
forall b c a. (b -> c) -> (a -> b) -> a -> c
. M m n -> Matrix ℂ
forall t s (d :: * -> *). Sized t s d => s -> d t
unwrap
{-# INLINE overMatM' #-}


#else

module Numeric.LinearAlgebra.Static.Internal where

#endif