{-# LANGUAGE CPP #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE ImportQualifiedPost #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE StandaloneKindSignatures #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_HADDOCK not-home #-}
module Data.Array.Nested.Shaped.Base where
import Prelude hiding (mappend, mconcat)
import Control.DeepSeq (NFData(..))
import Control.Monad.ST
import Data.Bifunctor (first)
import Data.Coerce (coerce)
import Data.Kind (Type)
import Data.List.NonEmpty (NonEmpty)
import Data.Proxy
import Data.Type.Equality
import Foreign.Storable (Storable)
import GHC.Float qualified (expm1, log1mexp, log1p, log1pexp)
import GHC.Generics (Generic)
import GHC.TypeLits
import Data.Array.Nested.Lemmas
import Data.Array.Nested.Mixed
import Data.Array.Nested.Mixed.Shape
import Data.Array.Nested.Shaped.Shape
import Data.Array.Nested.Types
import Data.Array.Strided.Arith
import Data.Array.XArray (XArray)
type Shaped :: [Nat] -> Type -> Type
newtype Shaped sh a = Shaped (Mixed (MapJust sh) a)
#ifdef OXAR_DEFAULT_SHOW_INSTANCES
deriving instance Show (Mixed (MapJust sh) a) => Show (Shaped sh a)
#endif
deriving instance Eq (Mixed (MapJust sh) a) => Eq (Shaped sh a)
deriving instance Ord (Mixed (MapJust sh) a) => Ord (Shaped sh a)
#ifndef OXAR_DEFAULT_SHOW_INSTANCES
instance (Show a, Elt a) => Show (Shaped n a) where
showsPrec :: Int -> Shaped n a -> ShowS
showsPrec Int
d arr :: Shaped n a
arr@(Shaped Mixed (MapJust n) a
marr) =
let sh :: String
sh = [Int] -> String
forall a. Show a => a -> String
show (ShS n -> [Int]
forall (sh :: [Nat]). ShS sh -> [Int]
shsToList (Shaped n a -> ShS n
forall (sh :: [Nat]) a. Elt a => Shaped sh a -> ShS sh
sshape Shaped n a
arr))
in String -> String -> Int -> Mixed (MapJust n) a -> ShowS
forall a (sh :: [Maybe Nat]).
(Show a, Elt a) =>
String -> String -> Int -> Mixed sh a -> ShowS
showsMixedArray (String
"sfromListLinear " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
sh) (String
"sreplicate " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
sh) Int
d Mixed (MapJust n) a
marr
#endif
instance Elt a => NFData (Shaped sh a) where
rnf :: Shaped sh a -> ()
rnf (Shaped Mixed (MapJust sh) a
arr) = Mixed (MapJust sh) a -> ()
forall a. NFData a => a -> ()
rnf Mixed (MapJust sh) a
arr
newtype instance Mixed sh (Shaped sh' a) = M_Shaped (Mixed sh (Mixed (MapJust sh') a))
deriving ((forall x.
Mixed sh (Shaped sh' a) -> Rep (Mixed sh (Shaped sh' a)) x)
-> (forall x.
Rep (Mixed sh (Shaped sh' a)) x -> Mixed sh (Shaped sh' a))
-> Generic (Mixed sh (Shaped sh' a))
forall (sh :: [Maybe Nat]) (sh' :: [Nat]) a x.
Rep (Mixed sh (Shaped sh' a)) x -> Mixed sh (Shaped sh' a)
forall (sh :: [Maybe Nat]) (sh' :: [Nat]) a x.
Mixed sh (Shaped sh' a) -> Rep (Mixed sh (Shaped sh' a)) x
forall x.
Rep (Mixed sh (Shaped sh' a)) x -> Mixed sh (Shaped sh' a)
forall x.
Mixed sh (Shaped sh' a) -> Rep (Mixed sh (Shaped sh' a)) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall (sh :: [Maybe Nat]) (sh' :: [Nat]) a x.
Mixed sh (Shaped sh' a) -> Rep (Mixed sh (Shaped sh' a)) x
from :: forall x.
Mixed sh (Shaped sh' a) -> Rep (Mixed sh (Shaped sh' a)) x
$cto :: forall (sh :: [Maybe Nat]) (sh' :: [Nat]) a x.
Rep (Mixed sh (Shaped sh' a)) x -> Mixed sh (Shaped sh' a)
to :: forall x.
Rep (Mixed sh (Shaped sh' a)) x -> Mixed sh (Shaped sh' a)
Generic)
#ifdef OXAR_DEFAULT_SHOW_INSTANCES
deriving instance Show (Mixed sh (Mixed (MapJust sh') a)) => Show (Mixed sh (Shaped sh' a))
#endif
deriving instance Eq (Mixed sh (Mixed (MapJust sh') a)) => Eq (Mixed sh (Shaped sh' a))
newtype instance MixedVecs s sh (Shaped sh' a) = MV_Shaped (MixedVecs s sh (Mixed (MapJust sh') a))
instance Elt a => Elt (Shaped sh a) where
mshape :: forall (sh :: [Maybe Nat]). Mixed sh (Shaped sh a) -> IShX sh
mshape (M_Shaped Mixed sh (Mixed (MapJust sh) a)
arr) = Mixed sh (Mixed (MapJust sh) a) -> IShX sh
forall (sh :: [Maybe Nat]).
Mixed sh (Mixed (MapJust sh) a) -> IShX sh
forall a (sh :: [Maybe Nat]). Elt a => Mixed sh a -> IShX sh
mshape Mixed sh (Mixed (MapJust sh) a)
arr
mindex :: forall (sh :: [Maybe Nat]).
Mixed sh (Shaped sh a) -> IIxX sh -> Shaped sh a
mindex (M_Shaped Mixed sh (Mixed (MapJust sh) a)
arr) IIxX sh
i = Mixed (MapJust sh) a -> Shaped sh a
forall (sh :: [Nat]) a. Mixed (MapJust sh) a -> Shaped sh a
Shaped (Mixed sh (Mixed (MapJust sh) a) -> IIxX sh -> Mixed (MapJust sh) a
forall (sh :: [Maybe Nat]).
Mixed sh (Mixed (MapJust sh) a) -> IIxX sh -> Mixed (MapJust sh) a
forall a (sh :: [Maybe Nat]). Elt a => Mixed sh a -> IIxX sh -> a
mindex Mixed sh (Mixed (MapJust sh) a)
arr IIxX sh
i)
mindexPartial :: forall sh1 sh2. Mixed (sh1 ++ sh2) (Shaped sh a) -> IIxX sh1 -> Mixed sh2 (Shaped sh a)
mindexPartial :: forall (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]).
Mixed (sh ++ sh') (Shaped sh a)
-> IIxX sh -> Mixed sh' (Shaped sh a)
mindexPartial (M_Shaped Mixed (sh1 ++ sh2) (Mixed (MapJust sh) a)
arr) IIxX sh1
i =
forall a b. Coercible a b => a -> b
forall a b. Coercible a b => a -> b
coerce @(Mixed sh2 (Mixed (MapJust sh) a)) @(Mixed sh2 (Shaped sh a)) (Mixed sh2 (Mixed (MapJust sh) a) -> Mixed sh2 (Shaped sh a))
-> Mixed sh2 (Mixed (MapJust sh) a) -> Mixed sh2 (Shaped sh a)
forall a b. (a -> b) -> a -> b
$
Mixed (sh1 ++ sh2) (Mixed (MapJust sh) a)
-> IIxX sh1 -> Mixed sh2 (Mixed (MapJust sh) a)
forall (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]).
Mixed (sh ++ sh') (Mixed (MapJust sh) a)
-> IIxX sh -> Mixed sh' (Mixed (MapJust sh) a)
forall a (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]).
Elt a =>
Mixed (sh ++ sh') a -> IIxX sh -> Mixed sh' a
mindexPartial Mixed (sh1 ++ sh2) (Mixed (MapJust sh) a)
arr IIxX sh1
i
mscalar :: Shaped sh a -> Mixed '[] (Shaped sh a)
mscalar (Shaped Mixed (MapJust sh) a
x) = Mixed '[] (Mixed (MapJust sh) a) -> Mixed '[] (Shaped sh a)
forall (sh :: [Maybe Nat]) (sh' :: [Nat]) a.
Mixed sh (Mixed (MapJust sh') a) -> Mixed sh (Shaped sh' a)
M_Shaped (IShX '[]
-> Mixed ('[] ++ MapJust sh) a -> Mixed '[] (Mixed (MapJust sh) a)
forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]) a.
IShX sh1 -> Mixed (sh1 ++ sh2) a -> Mixed sh1 (Mixed sh2 a)
M_Nest IShX '[]
forall (sh :: [Maybe Nat]) i. (sh ~ '[]) => ShX sh i
ZSX Mixed (MapJust sh) a
Mixed ('[] ++ MapJust sh) a
x)
mfromListOuter :: forall sh'. NonEmpty (Mixed sh' (Shaped sh a)) -> Mixed (Nothing : sh') (Shaped sh a)
mfromListOuter :: forall (sh :: [Maybe Nat]).
NonEmpty (Mixed sh (Shaped sh a))
-> Mixed ('Nothing : sh) (Shaped sh a)
mfromListOuter NonEmpty (Mixed sh' (Shaped sh a))
l = Mixed ('Nothing : sh') (Mixed (MapJust sh) a)
-> Mixed ('Nothing : sh') (Shaped sh a)
forall (sh :: [Maybe Nat]) (sh' :: [Nat]) a.
Mixed sh (Mixed (MapJust sh') a) -> Mixed sh (Shaped sh' a)
M_Shaped (NonEmpty (Mixed sh' (Mixed (MapJust sh) a))
-> Mixed ('Nothing : sh') (Mixed (MapJust sh) a)
forall (sh :: [Maybe Nat]).
NonEmpty (Mixed sh (Mixed (MapJust sh) a))
-> Mixed ('Nothing : sh) (Mixed (MapJust sh) a)
forall a (sh :: [Maybe Nat]).
Elt a =>
NonEmpty (Mixed sh a) -> Mixed ('Nothing : sh) a
mfromListOuter (NonEmpty (Mixed sh' (Shaped sh a))
-> NonEmpty (Mixed sh' (Mixed (MapJust sh) a))
forall a b. Coercible a b => a -> b
coerce NonEmpty (Mixed sh' (Shaped sh a))
l))
mtoListOuter :: forall n sh'. Mixed (n : sh') (Shaped sh a) -> [Mixed sh' (Shaped sh a)]
mtoListOuter :: forall (n :: Maybe Nat) (sh :: [Maybe Nat]).
Mixed (n : sh) (Shaped sh a) -> [Mixed sh (Shaped sh a)]
mtoListOuter (M_Shaped Mixed (n : sh') (Mixed (MapJust sh) a)
arr)
= forall a b. Coercible a b => a -> b
forall a b. Coercible a b => a -> b
coerce @[Mixed sh' (Mixed (MapJust sh) a)] @[Mixed sh' (Shaped sh a)] (Mixed (n : sh') (Mixed (MapJust sh) a)
-> [Mixed sh' (Mixed (MapJust sh) a)]
forall (n :: Maybe Nat) (sh :: [Maybe Nat]).
Mixed (n : sh) (Mixed (MapJust sh) a)
-> [Mixed sh (Mixed (MapJust sh) a)]
forall a (n :: Maybe Nat) (sh :: [Maybe Nat]).
Elt a =>
Mixed (n : sh) a -> [Mixed sh a]
mtoListOuter Mixed (n : sh') (Mixed (MapJust sh) a)
arr)
mlift :: forall sh1 sh2.
StaticShX sh2
-> (forall sh' b. Storable b => StaticShX sh' -> XArray (sh1 ++ sh') b -> XArray (sh2 ++ sh') b)
-> Mixed sh1 (Shaped sh a) -> Mixed sh2 (Shaped sh a)
mlift :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]).
StaticShX sh2
-> (forall (sh' :: [Maybe Nat]) b.
Storable b =>
StaticShX sh' -> XArray (sh1 ++ sh') b -> XArray (sh2 ++ sh') b)
-> Mixed sh1 (Shaped sh a)
-> Mixed sh2 (Shaped sh a)
mlift StaticShX sh2
ssh2 forall (sh' :: [Maybe Nat]) b.
Storable b =>
StaticShX sh' -> XArray (sh1 ++ sh') b -> XArray (sh2 ++ sh') b
f (M_Shaped Mixed sh1 (Mixed (MapJust sh) a)
arr) =
forall a b. Coercible a b => a -> b
forall a b. Coercible a b => a -> b
coerce @(Mixed sh2 (Mixed (MapJust sh) a)) @(Mixed sh2 (Shaped sh a)) (Mixed sh2 (Mixed (MapJust sh) a) -> Mixed sh2 (Shaped sh a))
-> Mixed sh2 (Mixed (MapJust sh) a) -> Mixed sh2 (Shaped sh a)
forall a b. (a -> b) -> a -> b
$
StaticShX sh2
-> (forall (sh' :: [Maybe Nat]) b.
Storable b =>
StaticShX sh' -> XArray (sh1 ++ sh') b -> XArray (sh2 ++ sh') b)
-> Mixed sh1 (Mixed (MapJust sh) a)
-> Mixed sh2 (Mixed (MapJust sh) a)
forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]).
StaticShX sh2
-> (forall (sh' :: [Maybe Nat]) b.
Storable b =>
StaticShX sh' -> XArray (sh1 ++ sh') b -> XArray (sh2 ++ sh') b)
-> Mixed sh1 (Mixed (MapJust sh) a)
-> Mixed sh2 (Mixed (MapJust sh) a)
forall a (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]).
Elt a =>
StaticShX sh2
-> (forall (sh' :: [Maybe Nat]) b.
Storable b =>
StaticShX sh' -> XArray (sh1 ++ sh') b -> XArray (sh2 ++ sh') b)
-> Mixed sh1 a
-> Mixed sh2 a
mlift StaticShX sh2
ssh2 StaticShX sh' -> XArray (sh1 ++ sh') b -> XArray (sh2 ++ sh') b
forall (sh' :: [Maybe Nat]) b.
Storable b =>
StaticShX sh' -> XArray (sh1 ++ sh') b -> XArray (sh2 ++ sh') b
f Mixed sh1 (Mixed (MapJust sh) a)
arr
mlift2 :: forall sh1 sh2 sh3.
StaticShX sh3
-> (forall sh' b. Storable b => StaticShX sh' -> XArray (sh1 ++ sh') b -> XArray (sh2 ++ sh') b -> XArray (sh3 ++ sh') b)
-> Mixed sh1 (Shaped sh a) -> Mixed sh2 (Shaped sh a) -> Mixed sh3 (Shaped sh a)
mlift2 :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat])
(sh3 :: [Maybe Nat]).
StaticShX sh3
-> (forall (sh' :: [Maybe Nat]) b.
Storable b =>
StaticShX sh'
-> XArray (sh1 ++ sh') b
-> XArray (sh2 ++ sh') b
-> XArray (sh3 ++ sh') b)
-> Mixed sh1 (Shaped sh a)
-> Mixed sh2 (Shaped sh a)
-> Mixed sh3 (Shaped sh a)
mlift2 StaticShX sh3
ssh3 forall (sh' :: [Maybe Nat]) b.
Storable b =>
StaticShX sh'
-> XArray (sh1 ++ sh') b
-> XArray (sh2 ++ sh') b
-> XArray (sh3 ++ sh') b
f (M_Shaped Mixed sh1 (Mixed (MapJust sh) a)
arr1) (M_Shaped Mixed sh2 (Mixed (MapJust sh) a)
arr2) =
forall a b. Coercible a b => a -> b
forall a b. Coercible a b => a -> b
coerce @(Mixed sh3 (Mixed (MapJust sh) a)) @(Mixed sh3 (Shaped sh a)) (Mixed sh3 (Mixed (MapJust sh) a) -> Mixed sh3 (Shaped sh a))
-> Mixed sh3 (Mixed (MapJust sh) a) -> Mixed sh3 (Shaped sh a)
forall a b. (a -> b) -> a -> b
$
StaticShX sh3
-> (forall (sh' :: [Maybe Nat]) b.
Storable b =>
StaticShX sh'
-> XArray (sh1 ++ sh') b
-> XArray (sh2 ++ sh') b
-> XArray (sh3 ++ sh') b)
-> Mixed sh1 (Mixed (MapJust sh) a)
-> Mixed sh2 (Mixed (MapJust sh) a)
-> Mixed sh3 (Mixed (MapJust sh) a)
forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat])
(sh3 :: [Maybe Nat]).
StaticShX sh3
-> (forall (sh' :: [Maybe Nat]) b.
Storable b =>
StaticShX sh'
-> XArray (sh1 ++ sh') b
-> XArray (sh2 ++ sh') b
-> XArray (sh3 ++ sh') b)
-> Mixed sh1 (Mixed (MapJust sh) a)
-> Mixed sh2 (Mixed (MapJust sh) a)
-> Mixed sh3 (Mixed (MapJust sh) a)
forall a (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat])
(sh3 :: [Maybe Nat]).
Elt a =>
StaticShX sh3
-> (forall (sh' :: [Maybe Nat]) b.
Storable b =>
StaticShX sh'
-> XArray (sh1 ++ sh') b
-> XArray (sh2 ++ sh') b
-> XArray (sh3 ++ sh') b)
-> Mixed sh1 a
-> Mixed sh2 a
-> Mixed sh3 a
mlift2 StaticShX sh3
ssh3 StaticShX sh'
-> XArray (sh1 ++ sh') b
-> XArray (sh2 ++ sh') b
-> XArray (sh3 ++ sh') b
forall (sh' :: [Maybe Nat]) b.
Storable b =>
StaticShX sh'
-> XArray (sh1 ++ sh') b
-> XArray (sh2 ++ sh') b
-> XArray (sh3 ++ sh') b
f Mixed sh1 (Mixed (MapJust sh) a)
arr1 Mixed sh2 (Mixed (MapJust sh) a)
arr2
mliftL :: forall sh1 sh2.
StaticShX sh2
-> (forall sh' b. Storable b => StaticShX sh' -> NonEmpty (XArray (sh1 ++ sh') b) -> NonEmpty (XArray (sh2 ++ sh') b))
-> NonEmpty (Mixed sh1 (Shaped sh a)) -> NonEmpty (Mixed sh2 (Shaped sh a))
mliftL :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]).
StaticShX sh2
-> (forall (sh' :: [Maybe Nat]) b.
Storable b =>
StaticShX sh'
-> NonEmpty (XArray (sh1 ++ sh') b)
-> NonEmpty (XArray (sh2 ++ sh') b))
-> NonEmpty (Mixed sh1 (Shaped sh a))
-> NonEmpty (Mixed sh2 (Shaped sh a))
mliftL StaticShX sh2
ssh2 forall (sh' :: [Maybe Nat]) b.
Storable b =>
StaticShX sh'
-> NonEmpty (XArray (sh1 ++ sh') b)
-> NonEmpty (XArray (sh2 ++ sh') b)
f NonEmpty (Mixed sh1 (Shaped sh a))
l =
forall a b. Coercible a b => a -> b
forall a b. Coercible a b => a -> b
coerce @(NonEmpty (Mixed sh2 (Mixed (MapJust sh) a)))
@(NonEmpty (Mixed sh2 (Shaped sh a))) (NonEmpty (Mixed sh2 (Mixed (MapJust sh) a))
-> NonEmpty (Mixed sh2 (Shaped sh a)))
-> NonEmpty (Mixed sh2 (Mixed (MapJust sh) a))
-> NonEmpty (Mixed sh2 (Shaped sh a))
forall a b. (a -> b) -> a -> b
$
StaticShX sh2
-> (forall (sh' :: [Maybe Nat]) b.
Storable b =>
StaticShX sh'
-> NonEmpty (XArray (sh1 ++ sh') b)
-> NonEmpty (XArray (sh2 ++ sh') b))
-> NonEmpty (Mixed sh1 (Mixed (MapJust sh) a))
-> NonEmpty (Mixed sh2 (Mixed (MapJust sh) a))
forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]).
StaticShX sh2
-> (forall (sh' :: [Maybe Nat]) b.
Storable b =>
StaticShX sh'
-> NonEmpty (XArray (sh1 ++ sh') b)
-> NonEmpty (XArray (sh2 ++ sh') b))
-> NonEmpty (Mixed sh1 (Mixed (MapJust sh) a))
-> NonEmpty (Mixed sh2 (Mixed (MapJust sh) a))
forall a (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]).
Elt a =>
StaticShX sh2
-> (forall (sh' :: [Maybe Nat]) b.
Storable b =>
StaticShX sh'
-> NonEmpty (XArray (sh1 ++ sh') b)
-> NonEmpty (XArray (sh2 ++ sh') b))
-> NonEmpty (Mixed sh1 a)
-> NonEmpty (Mixed sh2 a)
mliftL StaticShX sh2
ssh2 StaticShX sh'
-> NonEmpty (XArray (sh1 ++ sh') b)
-> NonEmpty (XArray (sh2 ++ sh') b)
forall (sh' :: [Maybe Nat]) b.
Storable b =>
StaticShX sh'
-> NonEmpty (XArray (sh1 ++ sh') b)
-> NonEmpty (XArray (sh2 ++ sh') b)
f (NonEmpty (Mixed sh1 (Shaped sh a))
-> NonEmpty (Mixed sh1 (Mixed (MapJust sh) a))
forall a b. Coercible a b => a -> b
coerce NonEmpty (Mixed sh1 (Shaped sh a))
l)
mcastPartial :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat])
(sh' :: [Maybe Nat]).
(Rank sh1 ~ Rank sh2) =>
StaticShX sh1
-> StaticShX sh2
-> Proxy sh'
-> Mixed (sh1 ++ sh') (Shaped sh a)
-> Mixed (sh2 ++ sh') (Shaped sh a)
mcastPartial StaticShX sh1
ssh1 StaticShX sh2
ssh2 Proxy sh'
psh' (M_Shaped Mixed (sh1 ++ sh') (Mixed (MapJust sh) a)
arr) = Mixed (sh2 ++ sh') (Mixed (MapJust sh) a)
-> Mixed (sh2 ++ sh') (Shaped sh a)
forall (sh :: [Maybe Nat]) (sh' :: [Nat]) a.
Mixed sh (Mixed (MapJust sh') a) -> Mixed sh (Shaped sh' a)
M_Shaped (StaticShX sh1
-> StaticShX sh2
-> Proxy sh'
-> Mixed (sh1 ++ sh') (Mixed (MapJust sh) a)
-> Mixed (sh2 ++ sh') (Mixed (MapJust sh) a)
forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat])
(sh' :: [Maybe Nat]).
(Rank sh1 ~ Rank sh2) =>
StaticShX sh1
-> StaticShX sh2
-> Proxy sh'
-> Mixed (sh1 ++ sh') (Mixed (MapJust sh) a)
-> Mixed (sh2 ++ sh') (Mixed (MapJust sh) a)
forall a (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat])
(sh' :: [Maybe Nat]).
(Elt a, Rank sh1 ~ Rank sh2) =>
StaticShX sh1
-> StaticShX sh2
-> Proxy sh'
-> Mixed (sh1 ++ sh') a
-> Mixed (sh2 ++ sh') a
mcastPartial StaticShX sh1
ssh1 StaticShX sh2
ssh2 Proxy sh'
psh' Mixed (sh1 ++ sh') (Mixed (MapJust sh) a)
arr)
mtranspose :: forall (is :: [Nat]) (sh :: [Maybe Nat]).
(IsPermutation is, Rank is <= Rank sh) =>
Perm is
-> Mixed sh (Shaped sh a)
-> Mixed (PermutePrefix is sh) (Shaped sh a)
mtranspose Perm is
perm (M_Shaped Mixed sh (Mixed (MapJust sh) a)
arr) = Mixed
(Permute is (TakeLen is sh) ++ DropLen is sh)
(Mixed (MapJust sh) a)
-> Mixed
(Permute is (TakeLen is sh) ++ DropLen is sh) (Shaped sh a)
forall (sh :: [Maybe Nat]) (sh' :: [Nat]) a.
Mixed sh (Mixed (MapJust sh') a) -> Mixed sh (Shaped sh' a)
M_Shaped (Perm is
-> Mixed sh (Mixed (MapJust sh) a)
-> Mixed
(Permute is (TakeLen is sh) ++ DropLen is sh)
(Mixed (MapJust sh) a)
forall (is :: [Nat]) (sh :: [Maybe Nat]).
(IsPermutation is, Rank is <= Rank sh) =>
Perm is
-> Mixed sh (Mixed (MapJust sh) a)
-> Mixed (PermutePrefix is sh) (Mixed (MapJust sh) a)
forall a (is :: [Nat]) (sh :: [Maybe Nat]).
(Elt a, IsPermutation is, Rank is <= Rank sh) =>
Perm is -> Mixed sh a -> Mixed (PermutePrefix is sh) a
mtranspose Perm is
perm Mixed sh (Mixed (MapJust sh) a)
arr)
mconcat :: forall (sh :: [Maybe Nat]).
NonEmpty (Mixed ('Nothing : sh) (Shaped sh a))
-> Mixed ('Nothing : sh) (Shaped sh a)
mconcat NonEmpty (Mixed ('Nothing : sh) (Shaped sh a))
l = Mixed ('Nothing : sh) (Mixed (MapJust sh) a)
-> Mixed ('Nothing : sh) (Shaped sh a)
forall (sh :: [Maybe Nat]) (sh' :: [Nat]) a.
Mixed sh (Mixed (MapJust sh') a) -> Mixed sh (Shaped sh' a)
M_Shaped (NonEmpty (Mixed ('Nothing : sh) (Mixed (MapJust sh) a))
-> Mixed ('Nothing : sh) (Mixed (MapJust sh) a)
forall (sh :: [Maybe Nat]).
NonEmpty (Mixed ('Nothing : sh) (Mixed (MapJust sh) a))
-> Mixed ('Nothing : sh) (Mixed (MapJust sh) a)
forall a (sh :: [Maybe Nat]).
Elt a =>
NonEmpty (Mixed ('Nothing : sh) a) -> Mixed ('Nothing : sh) a
mconcat (NonEmpty (Mixed ('Nothing : sh) (Shaped sh a))
-> NonEmpty (Mixed ('Nothing : sh) (Mixed (MapJust sh) a))
forall a b. Coercible a b => a -> b
coerce NonEmpty (Mixed ('Nothing : sh) (Shaped sh a))
l))
mrnf :: forall (sh :: [Maybe Nat]). Mixed sh (Shaped sh a) -> ()
mrnf (M_Shaped Mixed sh (Mixed (MapJust sh) a)
arr) = Mixed sh (Mixed (MapJust sh) a) -> ()
forall (sh :: [Maybe Nat]). Mixed sh (Mixed (MapJust sh) a) -> ()
forall a (sh :: [Maybe Nat]). Elt a => Mixed sh a -> ()
mrnf Mixed sh (Mixed (MapJust sh) a)
arr
type ShapeTree (Shaped sh a) = (ShS sh, ShapeTree a)
mshapeTree :: Shaped sh a -> ShapeTree (Shaped sh a)
mshapeTree (Shaped Mixed (MapJust sh) a
arr) = (ShX (MapJust sh) Int -> ShS sh)
-> (ShX (MapJust sh) Int, ShapeTree a) -> (ShS sh, ShapeTree a)
forall a b c. (a -> b) -> (a, c) -> (b, c)
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first ShX (MapJust sh) Int -> ShS sh
forall (sh :: [Nat]) i. ShX (MapJust sh) i -> ShS sh
shsFromShX (Mixed (MapJust sh) a -> ShapeTree (Mixed (MapJust sh) a)
forall a. Elt a => a -> ShapeTree a
mshapeTree Mixed (MapJust sh) a
arr)
mshapeTreeEq :: Proxy (Shaped sh a)
-> ShapeTree (Shaped sh a) -> ShapeTree (Shaped sh a) -> Bool
mshapeTreeEq Proxy (Shaped sh a)
_ (ShS sh
sh1, ShapeTree a
t1) (ShS sh
sh2, ShapeTree a
t2) = ShS sh
sh1 ShS sh -> ShS sh -> Bool
forall a. Eq a => a -> a -> Bool
== ShS sh
sh2 Bool -> Bool -> Bool
&& Proxy a -> ShapeTree a -> ShapeTree a -> Bool
forall a. Elt a => Proxy a -> ShapeTree a -> ShapeTree a -> Bool
mshapeTreeEq (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @a) ShapeTree a
t1 ShapeTree a
t2
mshapeTreeEmpty :: Proxy (Shaped sh a) -> ShapeTree (Shaped sh a) -> Bool
mshapeTreeEmpty Proxy (Shaped sh a)
_ (ShS sh
sh, ShapeTree a
t) = ShS sh -> Int
forall (sh :: [Nat]). ShS sh -> Int
shsSize ShS sh
sh Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 Bool -> Bool -> Bool
&& Proxy a -> ShapeTree a -> Bool
forall a. Elt a => Proxy a -> ShapeTree a -> Bool
mshapeTreeEmpty (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @a) ShapeTree a
t
mshowShapeTree :: Proxy (Shaped sh a) -> ShapeTree (Shaped sh a) -> String
mshowShapeTree Proxy (Shaped sh a)
_ (ShS sh
sh, ShapeTree a
t) = String
"(" String -> ShowS
forall a. [a] -> [a] -> [a]
++ ShS sh -> String
forall a. Show a => a -> String
show ShS sh
sh String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
", " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Proxy a -> ShapeTree a -> String
forall a. Elt a => Proxy a -> ShapeTree a -> String
mshowShapeTree (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @a) ShapeTree a
t String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
")"
marrayStrides :: forall (sh :: [Maybe Nat]). Mixed sh (Shaped sh a) -> Bag [Int]
marrayStrides (M_Shaped Mixed sh (Mixed (MapJust sh) a)
arr) = Mixed sh (Mixed (MapJust sh) a) -> Bag [Int]
forall (sh :: [Maybe Nat]).
Mixed sh (Mixed (MapJust sh) a) -> Bag [Int]
forall a (sh :: [Maybe Nat]). Elt a => Mixed sh a -> Bag [Int]
marrayStrides Mixed sh (Mixed (MapJust sh) a)
arr
mvecsWrite :: forall sh' s. IShX sh' -> IIxX sh' -> Shaped sh a -> MixedVecs s sh' (Shaped sh a) -> ST s ()
mvecsWrite :: forall (sh :: [Maybe Nat]) s.
IShX sh
-> IIxX sh
-> Shaped sh a
-> MixedVecs s sh (Shaped sh a)
-> ST s ()
mvecsWrite IShX sh'
sh IIxX sh'
idx (Shaped Mixed (MapJust sh) a
arr) MixedVecs s sh' (Shaped sh a)
vecs =
IShX sh'
-> IIxX sh'
-> Mixed (MapJust sh) a
-> MixedVecs s sh' (Mixed (MapJust sh) a)
-> ST s ()
forall (sh :: [Maybe Nat]) s.
IShX sh
-> IIxX sh
-> Mixed (MapJust sh) a
-> MixedVecs s sh (Mixed (MapJust sh) a)
-> ST s ()
forall a (sh :: [Maybe Nat]) s.
Elt a =>
IShX sh -> IIxX sh -> a -> MixedVecs s sh a -> ST s ()
mvecsWrite IShX sh'
sh IIxX sh'
idx Mixed (MapJust sh) a
arr
(forall a b. Coercible a b => a -> b
forall a b. Coercible a b => a -> b
coerce @(MixedVecs s sh' (Shaped sh a)) @(MixedVecs s sh' (Mixed (MapJust sh) a))
MixedVecs s sh' (Shaped sh a)
vecs)
mvecsWritePartial :: forall sh1 sh2 s.
IShX (sh1 ++ sh2) -> IIxX sh1 -> Mixed sh2 (Shaped sh a)
-> MixedVecs s (sh1 ++ sh2) (Shaped sh a)
-> ST s ()
mvecsWritePartial :: forall (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]) s.
IShX (sh ++ sh')
-> IIxX sh
-> Mixed sh' (Shaped sh a)
-> MixedVecs s (sh ++ sh') (Shaped sh a)
-> ST s ()
mvecsWritePartial IShX (sh1 ++ sh2)
sh IIxX sh1
idx Mixed sh2 (Shaped sh a)
arr MixedVecs s (sh1 ++ sh2) (Shaped sh a)
vecs =
IShX (sh1 ++ sh2)
-> IIxX sh1
-> Mixed sh2 (Mixed (MapJust sh) a)
-> MixedVecs s (sh1 ++ sh2) (Mixed (MapJust sh) a)
-> ST s ()
forall (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]) s.
IShX (sh ++ sh')
-> IIxX sh
-> Mixed sh' (Mixed (MapJust sh) a)
-> MixedVecs s (sh ++ sh') (Mixed (MapJust sh) a)
-> ST s ()
forall a (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]) s.
Elt a =>
IShX (sh ++ sh')
-> IIxX sh -> Mixed sh' a -> MixedVecs s (sh ++ sh') a -> ST s ()
mvecsWritePartial IShX (sh1 ++ sh2)
sh IIxX sh1
idx
(forall a b. Coercible a b => a -> b
forall a b. Coercible a b => a -> b
coerce @(Mixed sh2 (Shaped sh a))
@(Mixed sh2 (Mixed (MapJust sh) a))
Mixed sh2 (Shaped sh a)
arr)
(forall a b. Coercible a b => a -> b
forall a b. Coercible a b => a -> b
coerce @(MixedVecs s (sh1 ++ sh2) (Shaped sh a))
@(MixedVecs s (sh1 ++ sh2) (Mixed (MapJust sh) a))
MixedVecs s (sh1 ++ sh2) (Shaped sh a)
vecs)
mvecsFreeze :: forall sh' s. IShX sh' -> MixedVecs s sh' (Shaped sh a) -> ST s (Mixed sh' (Shaped sh a))
mvecsFreeze :: forall (sh :: [Maybe Nat]) s.
IShX sh
-> MixedVecs s sh (Shaped sh a) -> ST s (Mixed sh (Shaped sh a))
mvecsFreeze IShX sh'
sh MixedVecs s sh' (Shaped sh a)
vecs =
forall a b. Coercible a b => a -> b
forall a b. Coercible a b => a -> b
coerce @(Mixed sh' (Mixed (MapJust sh) a))
@(Mixed sh' (Shaped sh a))
(Mixed sh' (Mixed (MapJust sh) a) -> Mixed sh' (Shaped sh a))
-> ST s (Mixed sh' (Mixed (MapJust sh) a))
-> ST s (Mixed sh' (Shaped sh a))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IShX sh'
-> MixedVecs s sh' (Mixed (MapJust sh) a)
-> ST s (Mixed sh' (Mixed (MapJust sh) a))
forall (sh :: [Maybe Nat]) s.
IShX sh
-> MixedVecs s sh (Mixed (MapJust sh) a)
-> ST s (Mixed sh (Mixed (MapJust sh) a))
forall a (sh :: [Maybe Nat]) s.
Elt a =>
IShX sh -> MixedVecs s sh a -> ST s (Mixed sh a)
mvecsFreeze IShX sh'
sh
(forall a b. Coercible a b => a -> b
forall a b. Coercible a b => a -> b
coerce @(MixedVecs s sh' (Shaped sh a))
@(MixedVecs s sh' (Mixed (MapJust sh) a))
MixedVecs s sh' (Shaped sh a)
vecs)
instance (KnownShS sh, KnownElt a) => KnownElt (Shaped sh a) where
memptyArrayUnsafe :: forall sh'. IShX sh' -> Mixed sh' (Shaped sh a)
memptyArrayUnsafe :: forall (sh :: [Maybe Nat]). IShX sh -> Mixed sh (Shaped sh a)
memptyArrayUnsafe IShX sh'
i
| Dict KnownShX (MapJust sh)
Dict <- Proxy sh -> Dict KnownShX (MapJust sh)
forall (sh :: [Nat]).
KnownShS sh =>
Proxy sh -> Dict KnownShX (MapJust sh)
lemKnownMapJust (forall (t :: [Nat]). Proxy t
forall {k} (t :: k). Proxy t
Proxy @sh)
= forall a b. Coercible a b => a -> b
forall a b. Coercible a b => a -> b
coerce @(Mixed sh' (Mixed (MapJust sh) a)) @(Mixed sh' (Shaped sh a)) (Mixed sh' (Mixed (MapJust sh) a) -> Mixed sh' (Shaped sh a))
-> Mixed sh' (Mixed (MapJust sh) a) -> Mixed sh' (Shaped sh a)
forall a b. (a -> b) -> a -> b
$
IShX sh' -> Mixed sh' (Mixed (MapJust sh) a)
forall (sh :: [Maybe Nat]).
IShX sh -> Mixed sh (Mixed (MapJust sh) a)
forall a (sh :: [Maybe Nat]). KnownElt a => IShX sh -> Mixed sh a
memptyArrayUnsafe IShX sh'
i
mvecsUnsafeNew :: forall (sh :: [Maybe Nat]) s.
IShX sh -> Shaped sh a -> ST s (MixedVecs s sh (Shaped sh a))
mvecsUnsafeNew IShX sh
idx (Shaped Mixed (MapJust sh) a
arr)
| Dict KnownShX (MapJust sh)
Dict <- Proxy sh -> Dict KnownShX (MapJust sh)
forall (sh :: [Nat]).
KnownShS sh =>
Proxy sh -> Dict KnownShX (MapJust sh)
lemKnownMapJust (forall (t :: [Nat]). Proxy t
forall {k} (t :: k). Proxy t
Proxy @sh)
= MixedVecs s sh (Mixed (MapJust sh) a)
-> MixedVecs s sh (Shaped sh a)
forall s (sh :: [Maybe Nat]) (sh' :: [Nat]) a.
MixedVecs s sh (Mixed (MapJust sh') a)
-> MixedVecs s sh (Shaped sh' a)
MV_Shaped (MixedVecs s sh (Mixed (MapJust sh) a)
-> MixedVecs s sh (Shaped sh a))
-> ST s (MixedVecs s sh (Mixed (MapJust sh) a))
-> ST s (MixedVecs s sh (Shaped sh a))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IShX sh
-> Mixed (MapJust sh) a
-> ST s (MixedVecs s sh (Mixed (MapJust sh) a))
forall (sh :: [Maybe Nat]) s.
IShX sh
-> Mixed (MapJust sh) a
-> ST s (MixedVecs s sh (Mixed (MapJust sh) a))
forall a (sh :: [Maybe Nat]) s.
KnownElt a =>
IShX sh -> a -> ST s (MixedVecs s sh a)
mvecsUnsafeNew IShX sh
idx Mixed (MapJust sh) a
arr
mvecsNewEmpty :: forall s (sh :: [Maybe Nat]).
Proxy (Shaped sh a) -> ST s (MixedVecs s sh (Shaped sh a))
mvecsNewEmpty Proxy (Shaped sh a)
_
| Dict KnownShX (MapJust sh)
Dict <- Proxy sh -> Dict KnownShX (MapJust sh)
forall (sh :: [Nat]).
KnownShS sh =>
Proxy sh -> Dict KnownShX (MapJust sh)
lemKnownMapJust (forall (t :: [Nat]). Proxy t
forall {k} (t :: k). Proxy t
Proxy @sh)
= MixedVecs s sh (Mixed (MapJust sh) a)
-> MixedVecs s sh (Shaped sh a)
forall s (sh :: [Maybe Nat]) (sh' :: [Nat]) a.
MixedVecs s sh (Mixed (MapJust sh') a)
-> MixedVecs s sh (Shaped sh' a)
MV_Shaped (MixedVecs s sh (Mixed (MapJust sh) a)
-> MixedVecs s sh (Shaped sh a))
-> ST s (MixedVecs s sh (Mixed (MapJust sh) a))
-> ST s (MixedVecs s sh (Shaped sh a))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Proxy (Mixed (MapJust sh) a)
-> ST s (MixedVecs s sh (Mixed (MapJust sh) a))
forall a s (sh :: [Maybe Nat]).
KnownElt a =>
Proxy a -> ST s (MixedVecs s sh a)
forall s (sh :: [Maybe Nat]).
Proxy (Mixed (MapJust sh) a)
-> ST s (MixedVecs s sh (Mixed (MapJust sh) a))
mvecsNewEmpty (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @(Mixed (MapJust sh) a))
liftShaped1 :: forall sh a b.
(Mixed (MapJust sh) a -> Mixed (MapJust sh) b)
-> Shaped sh a -> Shaped sh b
liftShaped1 :: forall (sh :: [Nat]) a b.
(Mixed (MapJust sh) a -> Mixed (MapJust sh) b)
-> Shaped sh a -> Shaped sh b
liftShaped1 = (Mixed (MapJust sh) a -> Mixed (MapJust sh) b)
-> Shaped sh a -> Shaped sh b
forall a b. Coercible a b => a -> b
coerce
liftShaped2 :: forall sh a b c.
(Mixed (MapJust sh) a -> Mixed (MapJust sh) b -> Mixed (MapJust sh) c)
-> Shaped sh a -> Shaped sh b -> Shaped sh c
liftShaped2 :: forall (sh :: [Nat]) a b c.
(Mixed (MapJust sh) a
-> Mixed (MapJust sh) b -> Mixed (MapJust sh) c)
-> Shaped sh a -> Shaped sh b -> Shaped sh c
liftShaped2 = (Mixed (MapJust sh) a
-> Mixed (MapJust sh) b -> Mixed (MapJust sh) c)
-> Shaped sh a -> Shaped sh b -> Shaped sh c
forall a b. Coercible a b => a -> b
coerce
instance (NumElt a, PrimElt a) => Num (Shaped sh a) where
+ :: Shaped sh a -> Shaped sh a -> Shaped sh a
(+) = (Mixed (MapJust sh) a
-> Mixed (MapJust sh) a -> Mixed (MapJust sh) a)
-> Shaped sh a -> Shaped sh a -> Shaped sh a
forall (sh :: [Nat]) a b c.
(Mixed (MapJust sh) a
-> Mixed (MapJust sh) b -> Mixed (MapJust sh) c)
-> Shaped sh a -> Shaped sh b -> Shaped sh c
liftShaped2 Mixed (MapJust sh) a
-> Mixed (MapJust sh) a -> Mixed (MapJust sh) a
forall a. Num a => a -> a -> a
(+)
(-) = (Mixed (MapJust sh) a
-> Mixed (MapJust sh) a -> Mixed (MapJust sh) a)
-> Shaped sh a -> Shaped sh a -> Shaped sh a
forall (sh :: [Nat]) a b c.
(Mixed (MapJust sh) a
-> Mixed (MapJust sh) b -> Mixed (MapJust sh) c)
-> Shaped sh a -> Shaped sh b -> Shaped sh c
liftShaped2 (-)
* :: Shaped sh a -> Shaped sh a -> Shaped sh a
(*) = (Mixed (MapJust sh) a
-> Mixed (MapJust sh) a -> Mixed (MapJust sh) a)
-> Shaped sh a -> Shaped sh a -> Shaped sh a
forall (sh :: [Nat]) a b c.
(Mixed (MapJust sh) a
-> Mixed (MapJust sh) b -> Mixed (MapJust sh) c)
-> Shaped sh a -> Shaped sh b -> Shaped sh c
liftShaped2 Mixed (MapJust sh) a
-> Mixed (MapJust sh) a -> Mixed (MapJust sh) a
forall a. Num a => a -> a -> a
(*)
negate :: Shaped sh a -> Shaped sh a
negate = (Mixed (MapJust sh) a -> Mixed (MapJust sh) a)
-> Shaped sh a -> Shaped sh a
forall (sh :: [Nat]) a b.
(Mixed (MapJust sh) a -> Mixed (MapJust sh) b)
-> Shaped sh a -> Shaped sh b
liftShaped1 Mixed (MapJust sh) a -> Mixed (MapJust sh) a
forall a. Num a => a -> a
negate
abs :: Shaped sh a -> Shaped sh a
abs = (Mixed (MapJust sh) a -> Mixed (MapJust sh) a)
-> Shaped sh a -> Shaped sh a
forall (sh :: [Nat]) a b.
(Mixed (MapJust sh) a -> Mixed (MapJust sh) b)
-> Shaped sh a -> Shaped sh b
liftShaped1 Mixed (MapJust sh) a -> Mixed (MapJust sh) a
forall a. Num a => a -> a
abs
signum :: Shaped sh a -> Shaped sh a
signum = (Mixed (MapJust sh) a -> Mixed (MapJust sh) a)
-> Shaped sh a -> Shaped sh a
forall (sh :: [Nat]) a b.
(Mixed (MapJust sh) a -> Mixed (MapJust sh) b)
-> Shaped sh a -> Shaped sh b
liftShaped1 Mixed (MapJust sh) a -> Mixed (MapJust sh) a
forall a. Num a => a -> a
signum
fromInteger :: Integer -> Shaped sh a
fromInteger = String -> Integer -> Shaped sh a
forall a. HasCallStack => String -> a
error String
"Data.Array.Nested.fromInteger: No singletons available, use explicit sreplicateScal"
instance (FloatElt a, PrimElt a) => Fractional (Shaped sh a) where
fromRational :: Rational -> Shaped sh a
fromRational = String -> Rational -> Shaped sh a
forall a. HasCallStack => String -> a
error String
"Data.Array.Nested.fromRational: No singletons available, use explicit sreplicateScal"
recip :: Shaped sh a -> Shaped sh a
recip = (Mixed (MapJust sh) a -> Mixed (MapJust sh) a)
-> Shaped sh a -> Shaped sh a
forall (sh :: [Nat]) a b.
(Mixed (MapJust sh) a -> Mixed (MapJust sh) b)
-> Shaped sh a -> Shaped sh b
liftShaped1 Mixed (MapJust sh) a -> Mixed (MapJust sh) a
forall a. Fractional a => a -> a
recip
/ :: Shaped sh a -> Shaped sh a -> Shaped sh a
(/) = (Mixed (MapJust sh) a
-> Mixed (MapJust sh) a -> Mixed (MapJust sh) a)
-> Shaped sh a -> Shaped sh a -> Shaped sh a
forall (sh :: [Nat]) a b c.
(Mixed (MapJust sh) a
-> Mixed (MapJust sh) b -> Mixed (MapJust sh) c)
-> Shaped sh a -> Shaped sh b -> Shaped sh c
liftShaped2 Mixed (MapJust sh) a
-> Mixed (MapJust sh) a -> Mixed (MapJust sh) a
forall a. Fractional a => a -> a -> a
(/)
instance (FloatElt a, PrimElt a) => Floating (Shaped sh a) where
pi :: Shaped sh a
pi = String -> Shaped sh a
forall a. HasCallStack => String -> a
error String
"Data.Array.Nested.pi: No singletons available, use explicit sreplicateScal"
exp :: Shaped sh a -> Shaped sh a
exp = (Mixed (MapJust sh) a -> Mixed (MapJust sh) a)
-> Shaped sh a -> Shaped sh a
forall (sh :: [Nat]) a b.
(Mixed (MapJust sh) a -> Mixed (MapJust sh) b)
-> Shaped sh a -> Shaped sh b
liftShaped1 Mixed (MapJust sh) a -> Mixed (MapJust sh) a
forall a. Floating a => a -> a
exp
log :: Shaped sh a -> Shaped sh a
log = (Mixed (MapJust sh) a -> Mixed (MapJust sh) a)
-> Shaped sh a -> Shaped sh a
forall (sh :: [Nat]) a b.
(Mixed (MapJust sh) a -> Mixed (MapJust sh) b)
-> Shaped sh a -> Shaped sh b
liftShaped1 Mixed (MapJust sh) a -> Mixed (MapJust sh) a
forall a. Floating a => a -> a
log
sqrt :: Shaped sh a -> Shaped sh a
sqrt = (Mixed (MapJust sh) a -> Mixed (MapJust sh) a)
-> Shaped sh a -> Shaped sh a
forall (sh :: [Nat]) a b.
(Mixed (MapJust sh) a -> Mixed (MapJust sh) b)
-> Shaped sh a -> Shaped sh b
liftShaped1 Mixed (MapJust sh) a -> Mixed (MapJust sh) a
forall a. Floating a => a -> a
sqrt
** :: Shaped sh a -> Shaped sh a -> Shaped sh a
(**) = (Mixed (MapJust sh) a
-> Mixed (MapJust sh) a -> Mixed (MapJust sh) a)
-> Shaped sh a -> Shaped sh a -> Shaped sh a
forall (sh :: [Nat]) a b c.
(Mixed (MapJust sh) a
-> Mixed (MapJust sh) b -> Mixed (MapJust sh) c)
-> Shaped sh a -> Shaped sh b -> Shaped sh c
liftShaped2 Mixed (MapJust sh) a
-> Mixed (MapJust sh) a -> Mixed (MapJust sh) a
forall a. Floating a => a -> a -> a
(**)
logBase :: Shaped sh a -> Shaped sh a -> Shaped sh a
logBase = (Mixed (MapJust sh) a
-> Mixed (MapJust sh) a -> Mixed (MapJust sh) a)
-> Shaped sh a -> Shaped sh a -> Shaped sh a
forall (sh :: [Nat]) a b c.
(Mixed (MapJust sh) a
-> Mixed (MapJust sh) b -> Mixed (MapJust sh) c)
-> Shaped sh a -> Shaped sh b -> Shaped sh c
liftShaped2 Mixed (MapJust sh) a
-> Mixed (MapJust sh) a -> Mixed (MapJust sh) a
forall a. Floating a => a -> a -> a
logBase
sin :: Shaped sh a -> Shaped sh a
sin = (Mixed (MapJust sh) a -> Mixed (MapJust sh) a)
-> Shaped sh a -> Shaped sh a
forall (sh :: [Nat]) a b.
(Mixed (MapJust sh) a -> Mixed (MapJust sh) b)
-> Shaped sh a -> Shaped sh b
liftShaped1 Mixed (MapJust sh) a -> Mixed (MapJust sh) a
forall a. Floating a => a -> a
sin
cos :: Shaped sh a -> Shaped sh a
cos = (Mixed (MapJust sh) a -> Mixed (MapJust sh) a)
-> Shaped sh a -> Shaped sh a
forall (sh :: [Nat]) a b.
(Mixed (MapJust sh) a -> Mixed (MapJust sh) b)
-> Shaped sh a -> Shaped sh b
liftShaped1 Mixed (MapJust sh) a -> Mixed (MapJust sh) a
forall a. Floating a => a -> a
cos
tan :: Shaped sh a -> Shaped sh a
tan = (Mixed (MapJust sh) a -> Mixed (MapJust sh) a)
-> Shaped sh a -> Shaped sh a
forall (sh :: [Nat]) a b.
(Mixed (MapJust sh) a -> Mixed (MapJust sh) b)
-> Shaped sh a -> Shaped sh b
liftShaped1 Mixed (MapJust sh) a -> Mixed (MapJust sh) a
forall a. Floating a => a -> a
tan
asin :: Shaped sh a -> Shaped sh a
asin = (Mixed (MapJust sh) a -> Mixed (MapJust sh) a)
-> Shaped sh a -> Shaped sh a
forall (sh :: [Nat]) a b.
(Mixed (MapJust sh) a -> Mixed (MapJust sh) b)
-> Shaped sh a -> Shaped sh b
liftShaped1 Mixed (MapJust sh) a -> Mixed (MapJust sh) a
forall a. Floating a => a -> a
asin
acos :: Shaped sh a -> Shaped sh a
acos = (Mixed (MapJust sh) a -> Mixed (MapJust sh) a)
-> Shaped sh a -> Shaped sh a
forall (sh :: [Nat]) a b.
(Mixed (MapJust sh) a -> Mixed (MapJust sh) b)
-> Shaped sh a -> Shaped sh b
liftShaped1 Mixed (MapJust sh) a -> Mixed (MapJust sh) a
forall a. Floating a => a -> a
acos
atan :: Shaped sh a -> Shaped sh a
atan = (Mixed (MapJust sh) a -> Mixed (MapJust sh) a)
-> Shaped sh a -> Shaped sh a
forall (sh :: [Nat]) a b.
(Mixed (MapJust sh) a -> Mixed (MapJust sh) b)
-> Shaped sh a -> Shaped sh b
liftShaped1 Mixed (MapJust sh) a -> Mixed (MapJust sh) a
forall a. Floating a => a -> a
atan
sinh :: Shaped sh a -> Shaped sh a
sinh = (Mixed (MapJust sh) a -> Mixed (MapJust sh) a)
-> Shaped sh a -> Shaped sh a
forall (sh :: [Nat]) a b.
(Mixed (MapJust sh) a -> Mixed (MapJust sh) b)
-> Shaped sh a -> Shaped sh b
liftShaped1 Mixed (MapJust sh) a -> Mixed (MapJust sh) a
forall a. Floating a => a -> a
sinh
cosh :: Shaped sh a -> Shaped sh a
cosh = (Mixed (MapJust sh) a -> Mixed (MapJust sh) a)
-> Shaped sh a -> Shaped sh a
forall (sh :: [Nat]) a b.
(Mixed (MapJust sh) a -> Mixed (MapJust sh) b)
-> Shaped sh a -> Shaped sh b
liftShaped1 Mixed (MapJust sh) a -> Mixed (MapJust sh) a
forall a. Floating a => a -> a
cosh
tanh :: Shaped sh a -> Shaped sh a
tanh = (Mixed (MapJust sh) a -> Mixed (MapJust sh) a)
-> Shaped sh a -> Shaped sh a
forall (sh :: [Nat]) a b.
(Mixed (MapJust sh) a -> Mixed (MapJust sh) b)
-> Shaped sh a -> Shaped sh b
liftShaped1 Mixed (MapJust sh) a -> Mixed (MapJust sh) a
forall a. Floating a => a -> a
tanh
asinh :: Shaped sh a -> Shaped sh a
asinh = (Mixed (MapJust sh) a -> Mixed (MapJust sh) a)
-> Shaped sh a -> Shaped sh a
forall (sh :: [Nat]) a b.
(Mixed (MapJust sh) a -> Mixed (MapJust sh) b)
-> Shaped sh a -> Shaped sh b
liftShaped1 Mixed (MapJust sh) a -> Mixed (MapJust sh) a
forall a. Floating a => a -> a
asinh
acosh :: Shaped sh a -> Shaped sh a
acosh = (Mixed (MapJust sh) a -> Mixed (MapJust sh) a)
-> Shaped sh a -> Shaped sh a
forall (sh :: [Nat]) a b.
(Mixed (MapJust sh) a -> Mixed (MapJust sh) b)
-> Shaped sh a -> Shaped sh b
liftShaped1 Mixed (MapJust sh) a -> Mixed (MapJust sh) a
forall a. Floating a => a -> a
acosh
atanh :: Shaped sh a -> Shaped sh a
atanh = (Mixed (MapJust sh) a -> Mixed (MapJust sh) a)
-> Shaped sh a -> Shaped sh a
forall (sh :: [Nat]) a b.
(Mixed (MapJust sh) a -> Mixed (MapJust sh) b)
-> Shaped sh a -> Shaped sh b
liftShaped1 Mixed (MapJust sh) a -> Mixed (MapJust sh) a
forall a. Floating a => a -> a
atanh
log1p :: Shaped sh a -> Shaped sh a
log1p = (Mixed (MapJust sh) a -> Mixed (MapJust sh) a)
-> Shaped sh a -> Shaped sh a
forall (sh :: [Nat]) a b.
(Mixed (MapJust sh) a -> Mixed (MapJust sh) b)
-> Shaped sh a -> Shaped sh b
liftShaped1 Mixed (MapJust sh) a -> Mixed (MapJust sh) a
forall a. Floating a => a -> a
GHC.Float.log1p
expm1 :: Shaped sh a -> Shaped sh a
expm1 = (Mixed (MapJust sh) a -> Mixed (MapJust sh) a)
-> Shaped sh a -> Shaped sh a
forall (sh :: [Nat]) a b.
(Mixed (MapJust sh) a -> Mixed (MapJust sh) b)
-> Shaped sh a -> Shaped sh b
liftShaped1 Mixed (MapJust sh) a -> Mixed (MapJust sh) a
forall a. Floating a => a -> a
GHC.Float.expm1
log1pexp :: Shaped sh a -> Shaped sh a
log1pexp = (Mixed (MapJust sh) a -> Mixed (MapJust sh) a)
-> Shaped sh a -> Shaped sh a
forall (sh :: [Nat]) a b.
(Mixed (MapJust sh) a -> Mixed (MapJust sh) b)
-> Shaped sh a -> Shaped sh b
liftShaped1 Mixed (MapJust sh) a -> Mixed (MapJust sh) a
forall a. Floating a => a -> a
GHC.Float.log1pexp
log1mexp :: Shaped sh a -> Shaped sh a
log1mexp = (Mixed (MapJust sh) a -> Mixed (MapJust sh) a)
-> Shaped sh a -> Shaped sh a
forall (sh :: [Nat]) a b.
(Mixed (MapJust sh) a -> Mixed (MapJust sh) b)
-> Shaped sh a -> Shaped sh b
liftShaped1 Mixed (MapJust sh) a -> Mixed (MapJust sh) a
forall a. Floating a => a -> a
GHC.Float.log1mexp
squotArray, sremArray :: (IntElt a, PrimElt a) => Shaped sh a -> Shaped sh a -> Shaped sh a
squotArray :: forall a (sh :: [Nat]).
(IntElt a, PrimElt a) =>
Shaped sh a -> Shaped sh a -> Shaped sh a
squotArray = (Mixed (MapJust sh) a
-> Mixed (MapJust sh) a -> Mixed (MapJust sh) a)
-> Shaped sh a -> Shaped sh a -> Shaped sh a
forall (sh :: [Nat]) a b c.
(Mixed (MapJust sh) a
-> Mixed (MapJust sh) b -> Mixed (MapJust sh) c)
-> Shaped sh a -> Shaped sh b -> Shaped sh c
liftShaped2 Mixed (MapJust sh) a
-> Mixed (MapJust sh) a -> Mixed (MapJust sh) a
forall a (sh :: [Maybe Nat]).
(IntElt a, PrimElt a) =>
Mixed sh a -> Mixed sh a -> Mixed sh a
mquotArray
sremArray :: forall a (sh :: [Nat]).
(IntElt a, PrimElt a) =>
Shaped sh a -> Shaped sh a -> Shaped sh a
sremArray = (Mixed (MapJust sh) a
-> Mixed (MapJust sh) a -> Mixed (MapJust sh) a)
-> Shaped sh a -> Shaped sh a -> Shaped sh a
forall (sh :: [Nat]) a b c.
(Mixed (MapJust sh) a
-> Mixed (MapJust sh) b -> Mixed (MapJust sh) c)
-> Shaped sh a -> Shaped sh b -> Shaped sh c
liftShaped2 Mixed (MapJust sh) a
-> Mixed (MapJust sh) a -> Mixed (MapJust sh) a
forall a (sh :: [Maybe Nat]).
(IntElt a, PrimElt a) =>
Mixed sh a -> Mixed sh a -> Mixed sh a
mremArray
satan2Array :: (FloatElt a, PrimElt a) => Shaped sh a -> Shaped sh a -> Shaped sh a
satan2Array :: forall a (sh :: [Nat]).
(FloatElt a, PrimElt a) =>
Shaped sh a -> Shaped sh a -> Shaped sh a
satan2Array = (Mixed (MapJust sh) a
-> Mixed (MapJust sh) a -> Mixed (MapJust sh) a)
-> Shaped sh a -> Shaped sh a -> Shaped sh a
forall (sh :: [Nat]) a b c.
(Mixed (MapJust sh) a
-> Mixed (MapJust sh) b -> Mixed (MapJust sh) c)
-> Shaped sh a -> Shaped sh b -> Shaped sh c
liftShaped2 Mixed (MapJust sh) a
-> Mixed (MapJust sh) a -> Mixed (MapJust sh) a
forall a (sh :: [Maybe Nat]).
(FloatElt a, PrimElt a) =>
Mixed sh a -> Mixed sh a -> Mixed sh a
matan2Array
sshape :: forall sh a. Elt a => Shaped sh a -> ShS sh
sshape :: forall (sh :: [Nat]) a. Elt a => Shaped sh a -> ShS sh
sshape (Shaped Mixed (MapJust sh) a
arr) = ShX (MapJust sh) Int -> ShS sh
forall (sh :: [Nat]) i. ShX (MapJust sh) i -> ShS sh
shsFromShX (Mixed (MapJust sh) a -> ShX (MapJust sh) Int
forall (sh :: [Maybe Nat]). Mixed sh a -> IShX sh
forall a (sh :: [Maybe Nat]). Elt a => Mixed sh a -> IShX sh
mshape Mixed (MapJust sh) a
arr)
shsFromShX :: forall sh i. ShX (MapJust sh) i -> ShS sh
shsFromShX :: forall (sh :: [Nat]) i. ShX (MapJust sh) i -> ShS sh
shsFromShX ShX (MapJust sh) i
ZSX = (ShS '[] :~: ShS sh) -> ShS '[] -> ShS sh
forall a b. (a :~: b) -> a -> b
castWith (('[] :~: sh) -> ShS '[] :~: ShS sh
forall {k1} {k2} (f :: k1 -> k2) (a :: k1) (b :: k1).
(a :~: b) -> f a :~: f b
subst1 ('[] :~: sh
forall {k} (a :: k) (b :: k). a :~: b
unsafeCoerceRefl :: '[] :~: sh)) ShS '[]
forall (sh :: [Nat]). (sh ~ '[]) => ShS sh
ZSS
shsFromShX (SKnown n :: SNat n1
n@SNat n1
SNat :$% (ShX sh i
idx :: ShX mjshT i)) =
(ShS (n1 : Tail sh) :~: ShS sh) -> ShS (n1 : Tail sh) -> ShS sh
forall a b. (a :~: b) -> a -> b
castWith (((n1 : Tail sh) :~: sh) -> ShS (n1 : Tail sh) :~: ShS sh
forall {k1} {k2} (f :: k1 -> k2) (a :: k1) (b :: k1).
(a :~: b) -> f a :~: f b
subst1 ((sh :~: (n1 : Tail sh)) -> (n1 : Tail sh) :~: sh
forall {k} (a :: k) (b :: k). (a :~: b) -> b :~: a
sym ((MapJust sh :~: ('Just n1 : sh)) -> sh :~: (n1 : Tail sh)
forall {a} (sh :: [a]) (n :: a) (sh' :: [Maybe a]).
(MapJust sh :~: ('Just n : sh')) -> sh :~: (n : Tail sh)
lemMapJustCons ('Just n1 : sh) :~: ('Just n1 : sh)
MapJust sh :~: ('Just n1 : sh)
forall {k} (a :: k). a :~: a
Refl))) (ShS (n1 : Tail sh) -> ShS sh) -> ShS (n1 : Tail sh) -> ShS sh
forall a b. (a -> b) -> a -> b
$
SNat n1
n SNat n1 -> ShS (Tail sh) -> ShS (n1 : Tail sh)
forall {sh1 :: [Nat]} (n :: Nat) (sh :: [Nat]).
(KnownNat n, (n : sh) ~ sh1) =>
SNat n -> ShS sh -> ShS sh1
:$$ forall (sh :: [Nat]) i. ShX (MapJust sh) i -> ShS sh
shsFromShX @(Tail sh) ((ShX sh i :~: ShX (MapJust (Tail sh)) i)
-> ShX sh i -> ShX (MapJust (Tail sh)) i
forall a b. (a :~: b) -> a -> b
castWith ((sh :~: MapJust (Tail sh))
-> ShX sh i :~: ShX (MapJust (Tail sh)) i
forall {k1} {k2} {k3} (f :: k1 -> k2 -> k3) (c :: k2) (a :: k1)
(b :: k1).
(a :~: b) -> f a c :~: f b c
subst2 (sh :~: MapJust (Tail sh)
forall {k} (a :: k) (b :: k). a :~: b
unsafeCoerceRefl :: mjshT :~: MapJust (Tail sh)))
ShX sh i
idx)
shsFromShX (SUnknown i
_ :$% ShX sh i
_) = String -> ShS sh
forall a. HasCallStack => String -> a
error String
"impossible"