module Telescope.Data.Array where
import Control.Exception (throw)
import Control.Monad.Catch
import Data.Binary.Get (ByteOffset, runGetOrFail)
import Data.Binary.Put (Put, runPut)
import Data.ByteString qualified as BS
import Data.ByteString.Lazy qualified as BL
import Data.Massiv.Array (Array, Comp (..), D, Index, Ix1, Ix2 (..), Ix3, Ix4, Ix5, IxN (..), Lower, Prim, Source, Stream, Sz (..), Vector)
import Data.Massiv.Array qualified as M
import Data.Word (Word8)
import Telescope.Data.Axes
import Telescope.Data.Binary
decodeArray
:: forall ix a m
. (AxesIndex ix, Prim a, BinaryValue a, MonadThrow m, MonadCatch m)
=> Axes Row
-> BS.ByteString
-> m (Array D ix a)
decodeArray :: forall ix a (m :: * -> *).
(AxesIndex ix, Prim a, BinaryValue a, MonadThrow m,
MonadCatch m) =>
Axes 'Row -> ByteString -> m (Array D ix a)
decodeArray = ByteOrder -> Axes 'Row -> ByteString -> m (Array D ix a)
forall ix a (m :: * -> *).
(AxesIndex ix, BinaryValue a, MonadThrow m, MonadCatch m) =>
ByteOrder -> Axes 'Row -> ByteString -> m (Array D ix a)
decodeArrayOrder ByteOrder
BigEndian
encodeArray
:: (Source r a, Stream r Ix1 a, PutArray ix, BinaryValue a, Prim a)
=> Array r ix a
-> BS.ByteString
encodeArray :: forall r a ix.
(Source r a, Stream r Ix1 a, PutArray ix, BinaryValue a, Prim a) =>
Array r ix a -> ByteString
encodeArray = LazyByteString -> ByteString
BL.toStrict (LazyByteString -> ByteString)
-> (Array r ix a -> LazyByteString) -> Array r ix a -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Put -> LazyByteString
runPut (Put -> LazyByteString)
-> (Array r ix a -> Put) -> Array r ix a -> LazyByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteOrder -> Array r ix a -> Put
forall ix a r.
(PutArray ix, BinaryValue a, Source r a, Stream r Ix1 a, Prim a) =>
ByteOrder -> Array r ix a -> Put
forall a r.
(BinaryValue a, Source r a, Stream r Ix1 a, Prim a) =>
ByteOrder -> Array r ix a -> Put
putArray ByteOrder
BigEndian
decodeArrayOrder
:: forall ix a m
. (AxesIndex ix, BinaryValue a, MonadThrow m, MonadCatch m)
=> ByteOrder
-> Axes Row
-> BS.ByteString
-> m (Array D ix a)
decodeArrayOrder :: forall ix a (m :: * -> *).
(AxesIndex ix, BinaryValue a, MonadThrow m, MonadCatch m) =>
ByteOrder -> Axes 'Row -> ByteString -> m (Array D ix a)
decodeArrayOrder ByteOrder
bo Axes 'Row
as ByteString
inp = do
Axes 'Row -> Vector D a -> m (Array D ix a)
forall ix a (m :: * -> *).
(AxesIndex ix, MonadThrow m, MonadCatch m) =>
Axes 'Row -> Vector D a -> m (Array D ix a)
fromVector Axes 'Row
as (Vector D a -> m (Array D ix a)) -> Vector D a -> m (Array D ix a)
forall a b. (a -> b) -> a -> b
$ forall a.
BinaryValue a =>
Comp -> ByteOrder -> ByteString -> Vector D a
decodeVector @a Comp
Par ByteOrder
bo ByteString
inp
decodeVector
:: forall a
. (BinaryValue a)
=> Comp
-> ByteOrder
-> BS.ByteString
-> Vector D a
decodeVector :: forall a.
BinaryValue a =>
Comp -> ByteOrder -> ByteString -> Vector D a
decodeVector Comp
c ByteOrder
bo ByteString
inp =
let v :: Vector D Word8
v = ByteString -> Vector D Word8
parseWordVector ByteString
inp
in Comp -> Sz Ix1 -> (Ix1 -> a) -> Array D Ix1 a
forall r ix e.
Load r ix e =>
Comp -> Sz ix -> (ix -> e) -> Array r ix e
M.makeArray Comp
c (Vector D Word8 -> Sz Ix1
arraySize Vector D Word8
v) (Vector D Word8 -> Ix1 -> a
valueAt Vector D Word8
v)
where
numBytes :: Ix1
numBytes = forall a. BinaryValue a => Ix1
byteSize @a
arraySize :: Vector D Word8 -> Sz Ix1
arraySize Vector D Word8
v =
let Sz Ix1
s = Vector D Word8 -> Sz Ix1
forall r ix e. Size r => Array r ix e -> Sz ix
forall ix e. Array D ix e -> Sz ix
M.size Vector D Word8
v
in Ix1 -> Sz Ix1
forall ix. Index ix => ix -> Sz ix
Sz (Ix1 -> Sz Ix1) -> Ix1 -> Sz Ix1
forall a b. (a -> b) -> a -> b
$ Ix1
s Ix1 -> Ix1 -> Ix1
forall a. Integral a => a -> a -> a
`div` Ix1
numBytes
valueAt :: Vector D Word8 -> Ix1 -> a
valueAt :: Vector D Word8 -> Ix1 -> a
valueAt Vector D Word8
v Ix1
ix =
[Word8] -> a
fromWords ([Word8] -> a) -> [Word8] -> a
forall a b. (a -> b) -> a -> b
$ Vector D Word8 -> Ix1 -> [Word8]
wordsAt Vector D Word8
v Ix1
ix
wordsAt :: Vector D Word8 -> Ix1 -> [Word8]
wordsAt :: Vector D Word8 -> Ix1 -> [Word8]
wordsAt Vector D Word8
v Ix1
ix =
Vector D Word8 -> [Word8]
forall ix r e. (Index ix, Source r e) => Array r ix e -> [e]
M.toList (Vector D Word8 -> [Word8]) -> Vector D Word8 -> [Word8]
forall a b. (a -> b) -> a -> b
$ Ix1 -> Sz Ix1 -> Vector D Word8 -> Vector D Word8
forall r e. Source r e => Ix1 -> Sz Ix1 -> Vector r e -> Vector r e
M.slice (Ix1
ix Ix1 -> Ix1 -> Ix1
forall a. Num a => a -> a -> a
* Ix1
numBytes) (Ix1 -> Sz Ix1
forall ix. Index ix => ix -> Sz ix
Sz Ix1
numBytes) Vector D Word8
v
parseWordVector :: BS.ByteString -> Vector D Word8
parseWordVector :: ByteString -> Vector D Word8
parseWordVector = Comp -> ByteString -> Vector D Word8
forall r. Load r Ix1 Word8 => Comp -> ByteString -> Vector r Word8
M.fromByteString Comp
c
fromWords :: [Word8] -> a
fromWords :: [Word8] -> a
fromWords [Word8]
ws =
case Get a
-> LazyByteString
-> Either
(LazyByteString, ByteOffset, String)
(LazyByteString, ByteOffset, a)
forall a.
Get a
-> LazyByteString
-> Either
(LazyByteString, ByteOffset, String)
(LazyByteString, ByteOffset, a)
runGetOrFail (ByteOrder -> Get a
forall a. BinaryValue a => ByteOrder -> Get a
get ByteOrder
bo) ([Word8] -> LazyByteString
BL.pack [Word8]
ws) of
Left (LazyByteString
ip, ByteOffset
byts, String
e) -> ArrayError -> a
forall a e. Exception e => e -> a
throw (ArrayError -> a) -> ArrayError -> a
forall a b. (a -> b) -> a -> b
$ ByteOffset -> String -> ArrayError
BinaryParseError ByteOffset
byts (String
e String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
" " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> LazyByteString -> String
forall a. Show a => a -> String
show LazyByteString
ip String -> String -> String
forall a. Semigroup a => a -> a -> a
<> [Word8] -> String
forall a. Show a => a -> String
show [Word8]
ws)
Right (LazyByteString
_, ByteOffset
_, a
a) -> a
a
fromVector
:: forall ix a m
. (AxesIndex ix, MonadThrow m, MonadCatch m)
=> Axes Row
-> Vector D a
-> m (Array D ix a)
fromVector :: forall ix a (m :: * -> *).
(AxesIndex ix, MonadThrow m, MonadCatch m) =>
Axes 'Row -> Vector D a -> m (Array D ix a)
fromVector Axes 'Row
as Vector D a
v = do
ix
ix <- Axes 'Row -> m ix
forall ix (m :: * -> *).
(AxesIndex ix, MonadThrow m) =>
Axes 'Row -> m ix
forall (m :: * -> *). MonadThrow m => Axes 'Row -> m ix
axesIndex Axes 'Row
as
Either SizeException (Array D ix a)
ea <- m (Array D ix a) -> m (Either SizeException (Array D ix a))
forall (m :: * -> *) e a.
(HasCallStack, MonadCatch m, Exception e) =>
m a -> m (Either e a)
try (m (Array D ix a) -> m (Either SizeException (Array D ix a)))
-> m (Array D ix a) -> m (Either SizeException (Array D ix a))
forall a b. (a -> b) -> a -> b
$ Sz ix -> Vector D a -> m (Array D ix a)
forall r ix ix' e (m :: * -> *).
(MonadThrow m, Index ix', Index ix, Size r) =>
Sz ix' -> Array r ix e -> m (Array r ix' e)
M.resizeM (ix -> Sz ix
forall ix. Index ix => ix -> Sz ix
Sz ix
ix) Vector D a
v
case Either SizeException (Array D ix a)
ea of
Left (SizeException
e :: M.SizeException) -> ArrayError -> m (Array D ix a)
forall e a. (HasCallStack, Exception e) => e -> m a
forall (m :: * -> *) e a.
(MonadThrow m, HasCallStack, Exception e) =>
e -> m a
throwM (ArrayError -> m (Array D ix a)) -> ArrayError -> m (Array D ix a)
forall a b. (a -> b) -> a -> b
$ String -> ArrayError
ResizeMismatch (SizeException -> String
forall a. Show a => a -> String
show SizeException
e)
Right Array D ix a
a -> Array D ix a -> m (Array D ix a)
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Array D ix a
a
data ArrayError
= BinaryParseError !ByteOffset String
| AxesMismatch !(Axes Row)
| ResizeMismatch String
deriving (Ix1 -> ArrayError -> String -> String
[ArrayError] -> String -> String
ArrayError -> String
(Ix1 -> ArrayError -> String -> String)
-> (ArrayError -> String)
-> ([ArrayError] -> String -> String)
-> Show ArrayError
forall a.
(Ix1 -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Ix1 -> ArrayError -> String -> String
showsPrec :: Ix1 -> ArrayError -> String -> String
$cshow :: ArrayError -> String
show :: ArrayError -> String
$cshowList :: [ArrayError] -> String -> String
showList :: [ArrayError] -> String -> String
Show, Show ArrayError
Typeable ArrayError
(Typeable ArrayError, Show ArrayError) =>
(ArrayError -> SomeException)
-> (SomeException -> Maybe ArrayError)
-> (ArrayError -> String)
-> Exception ArrayError
SomeException -> Maybe ArrayError
ArrayError -> String
ArrayError -> SomeException
forall e.
(Typeable e, Show e) =>
(e -> SomeException)
-> (SomeException -> Maybe e) -> (e -> String) -> Exception e
$ctoException :: ArrayError -> SomeException
toException :: ArrayError -> SomeException
$cfromException :: SomeException -> Maybe ArrayError
fromException :: SomeException -> Maybe ArrayError
$cdisplayException :: ArrayError -> String
displayException :: ArrayError -> String
Exception)
class (Index ix) => AxesIndex ix where
axesIndex :: (MonadThrow m) => Axes Row -> m ix
indexAxes :: ix -> Axes Row
instance AxesIndex Ix1 where
axesIndex :: forall (m :: * -> *). MonadThrow m => Axes 'Row -> m Ix1
axesIndex (Axes [Ix1
i]) = Ix1 -> m Ix1
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Ix1
i
axesIndex Axes 'Row
as = ArrayError -> m Ix1
forall e a. (HasCallStack, Exception e) => e -> m a
forall (m :: * -> *) e a.
(MonadThrow m, HasCallStack, Exception e) =>
e -> m a
throwM (ArrayError -> m Ix1) -> ArrayError -> m Ix1
forall a b. (a -> b) -> a -> b
$ Axes 'Row -> ArrayError
AxesMismatch Axes 'Row
as
indexAxes :: Ix1 -> Axes 'Row
indexAxes Ix1
n = [Ix1] -> Axes 'Row
forall (a :: Major). [Ix1] -> Axes a
Axes [Ix1
n]
instance AxesIndex Ix2 where
axesIndex :: forall (m :: * -> *). MonadThrow m => Axes 'Row -> m Ix2
axesIndex (Axes [Ix1
c, Ix1
r]) = do
Ix1
ix1 <- Axes 'Row -> m Ix1
forall ix (m :: * -> *).
(AxesIndex ix, MonadThrow m) =>
Axes 'Row -> m ix
forall (m :: * -> *). MonadThrow m => Axes 'Row -> m Ix1
axesIndex (Axes 'Row -> m Ix1) -> Axes 'Row -> m Ix1
forall a b. (a -> b) -> a -> b
$ [Ix1] -> Axes 'Row
forall (a :: Major). [Ix1] -> Axes a
Axes [Ix1
r]
Ix2 -> m Ix2
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Ix2 -> m Ix2) -> Ix2 -> m Ix2
forall a b. (a -> b) -> a -> b
$ Ix1
c Ix1 -> Ix1 -> Ix2
:. Ix1
ix1
axesIndex Axes 'Row
as = ArrayError -> m Ix2
forall e a. (HasCallStack, Exception e) => e -> m a
forall (m :: * -> *) e a.
(MonadThrow m, HasCallStack, Exception e) =>
e -> m a
throwM (ArrayError -> m Ix2) -> ArrayError -> m Ix2
forall a b. (a -> b) -> a -> b
$ Axes 'Row -> ArrayError
AxesMismatch Axes 'Row
as
indexAxes :: Ix2 -> Axes 'Row
indexAxes (Ix1
c :. Ix1
r) = [Ix1] -> Axes 'Row
forall (a :: Major). [Ix1] -> Axes a
Axes [Ix1
c, Ix1
r]
instance AxesIndex Ix3 where
axesIndex :: forall (m :: * -> *). MonadThrow m => Axes 'Row -> m Ix3
axesIndex = Axes 'Row -> m Ix3
forall (n :: Nat) (m :: * -> *).
(AxesIndex (Lower (IxN n)), MonadThrow m) =>
Axes 'Row -> m (IxN n)
axesIndexN
indexAxes :: Ix3 -> Axes 'Row
indexAxes = Ix3 -> Axes 'Row
forall (n :: Nat). AxesIndex (Lower (IxN n)) => IxN n -> Axes 'Row
indexAxesN
instance AxesIndex Ix4 where
axesIndex :: forall (m :: * -> *). MonadThrow m => Axes 'Row -> m Ix4
axesIndex = Axes 'Row -> m Ix4
forall (n :: Nat) (m :: * -> *).
(AxesIndex (Lower (IxN n)), MonadThrow m) =>
Axes 'Row -> m (IxN n)
axesIndexN
indexAxes :: Ix4 -> Axes 'Row
indexAxes = Ix4 -> Axes 'Row
forall (n :: Nat). AxesIndex (Lower (IxN n)) => IxN n -> Axes 'Row
indexAxesN
instance AxesIndex Ix5 where
axesIndex :: forall (m :: * -> *). MonadThrow m => Axes 'Row -> m Ix5
axesIndex = Axes 'Row -> m Ix5
forall (n :: Nat) (m :: * -> *).
(AxesIndex (Lower (IxN n)), MonadThrow m) =>
Axes 'Row -> m (IxN n)
axesIndexN
indexAxes :: Ix5 -> Axes 'Row
indexAxes = Ix5 -> Axes 'Row
forall (n :: Nat). AxesIndex (Lower (IxN n)) => IxN n -> Axes 'Row
indexAxesN
class PutArray ix where
putArray
:: (BinaryValue a, Source r a, Stream r Ix1 a, Prim a)
=> ByteOrder
-> Array r ix a
-> Put
instance PutArray Ix1 where
putArray :: forall a r.
(BinaryValue a, Source r a, Stream r Ix1 a, Prim a) =>
ByteOrder -> Array r Ix1 a -> Put
putArray ByteOrder
bo = (Put -> a -> Put) -> Put -> Array r Ix1 a -> Put
forall r ix e a.
Stream r ix e =>
(a -> e -> a) -> a -> Array r ix e -> a
M.sfoldl (\Put
b a
a -> Put
b Put -> Put -> Put
forall a. Semigroup a => a -> a -> a
<> ByteOrder -> a -> Put
forall a. BinaryValue a => ByteOrder -> a -> Put
put ByteOrder
bo a
a) Put
forall a. Monoid a => a
mempty
instance PutArray Ix2 where
putArray :: forall a r.
(BinaryValue a, Source r a, Stream r Ix1 a, Prim a) =>
ByteOrder -> Array r Ix2 a -> Put
putArray = (Array r Ix1 a -> Put) -> Array r Ix2 a -> Put
(Array r (Lower Ix2) a -> Put) -> Array r Ix2 a -> Put
forall ix r e m.
(Index ix, Index (Lower ix), Source r e, Monoid m) =>
(Array r (Lower ix) e -> m) -> Array r ix e -> m
M.foldOuterSlice ((Array r Ix1 a -> Put) -> Array r Ix2 a -> Put)
-> (ByteOrder -> Array r Ix1 a -> Put)
-> ByteOrder
-> Array r Ix2 a
-> Put
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteOrder -> Array r Ix1 a -> Put
forall ix a r.
(PutArray ix, BinaryValue a, Source r a, Stream r Ix1 a, Prim a) =>
ByteOrder -> Array r ix a -> Put
forall a r.
(BinaryValue a, Source r a, Stream r Ix1 a, Prim a) =>
ByteOrder -> Array r Ix1 a -> Put
putArray
instance PutArray Ix3 where
putArray :: forall a r.
(BinaryValue a, Source r a, Stream r Ix1 a, Prim a) =>
ByteOrder -> Array r Ix3 a -> Put
putArray = (Array r (Lower Ix3) a -> Put) -> Array r Ix3 a -> Put
(Array r Ix2 a -> Put) -> Array r Ix3 a -> Put
forall ix r e m.
(Index ix, Index (Lower ix), Source r e, Monoid m) =>
(Array r (Lower ix) e -> m) -> Array r ix e -> m
M.foldOuterSlice ((Array r Ix2 a -> Put) -> Array r Ix3 a -> Put)
-> (ByteOrder -> Array r Ix2 a -> Put)
-> ByteOrder
-> Array r Ix3 a
-> Put
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteOrder -> Array r Ix2 a -> Put
forall ix a r.
(PutArray ix, BinaryValue a, Source r a, Stream r Ix1 a, Prim a) =>
ByteOrder -> Array r ix a -> Put
forall a r.
(BinaryValue a, Source r a, Stream r Ix1 a, Prim a) =>
ByteOrder -> Array r Ix2 a -> Put
putArray
instance PutArray Ix4 where
putArray :: forall a r.
(BinaryValue a, Source r a, Stream r Ix1 a, Prim a) =>
ByteOrder -> Array r Ix4 a -> Put
putArray = (Array r (Lower Ix4) a -> Put) -> Array r Ix4 a -> Put
(Array r Ix3 a -> Put) -> Array r Ix4 a -> Put
forall ix r e m.
(Index ix, Index (Lower ix), Source r e, Monoid m) =>
(Array r (Lower ix) e -> m) -> Array r ix e -> m
M.foldOuterSlice ((Array r Ix3 a -> Put) -> Array r Ix4 a -> Put)
-> (ByteOrder -> Array r Ix3 a -> Put)
-> ByteOrder
-> Array r Ix4 a
-> Put
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteOrder -> Array r Ix3 a -> Put
forall ix a r.
(PutArray ix, BinaryValue a, Source r a, Stream r Ix1 a, Prim a) =>
ByteOrder -> Array r ix a -> Put
forall a r.
(BinaryValue a, Source r a, Stream r Ix1 a, Prim a) =>
ByteOrder -> Array r Ix3 a -> Put
putArray
instance PutArray Ix5 where
putArray :: forall a r.
(BinaryValue a, Source r a, Stream r Ix1 a, Prim a) =>
ByteOrder -> Array r Ix5 a -> Put
putArray = (Array r (Lower Ix5) a -> Put) -> Array r Ix5 a -> Put
(Array r Ix4 a -> Put) -> Array r Ix5 a -> Put
forall ix r e m.
(Index ix, Index (Lower ix), Source r e, Monoid m) =>
(Array r (Lower ix) e -> m) -> Array r ix e -> m
M.foldOuterSlice ((Array r Ix4 a -> Put) -> Array r Ix5 a -> Put)
-> (ByteOrder -> Array r Ix4 a -> Put)
-> ByteOrder
-> Array r Ix5 a
-> Put
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteOrder -> Array r Ix4 a -> Put
forall ix a r.
(PutArray ix, BinaryValue a, Source r a, Stream r Ix1 a, Prim a) =>
ByteOrder -> Array r ix a -> Put
forall a r.
(BinaryValue a, Source r a, Stream r Ix1 a, Prim a) =>
ByteOrder -> Array r Ix4 a -> Put
putArray
axesIndexN :: (AxesIndex (Lower (IxN n))) => (MonadThrow m) => Axes Row -> m (IxN n)
axesIndexN :: forall (n :: Nat) (m :: * -> *).
(AxesIndex (Lower (IxN n)), MonadThrow m) =>
Axes 'Row -> m (IxN n)
axesIndexN (Axes (Ix1
a : [Ix1]
as)) = do
Ix (n - 1)
ixl <- Axes 'Row -> m (Ix (n - 1))
forall ix (m :: * -> *).
(AxesIndex ix, MonadThrow m) =>
Axes 'Row -> m ix
forall (m :: * -> *). MonadThrow m => Axes 'Row -> m (Ix (n - 1))
axesIndex ([Ix1] -> Axes 'Row
forall (a :: Major). [Ix1] -> Axes a
Axes [Ix1]
as)
IxN n -> m (IxN n)
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (IxN n -> m (IxN n)) -> IxN n -> m (IxN n)
forall a b. (a -> b) -> a -> b
$ Ix1
a Ix1 -> Ix (n - 1) -> IxN n
forall (n :: Nat). Ix1 -> Ix (n - 1) -> IxN n
:> Ix (n - 1)
ixl
axesIndexN Axes 'Row
as = ArrayError -> m (IxN n)
forall e a. (HasCallStack, Exception e) => e -> m a
forall (m :: * -> *) e a.
(MonadThrow m, HasCallStack, Exception e) =>
e -> m a
throwM (ArrayError -> m (IxN n)) -> ArrayError -> m (IxN n)
forall a b. (a -> b) -> a -> b
$ Axes 'Row -> ArrayError
AxesMismatch Axes 'Row
as
indexAxesN :: (AxesIndex (Lower (IxN n))) => IxN n -> Axes Row
indexAxesN :: forall (n :: Nat). AxesIndex (Lower (IxN n)) => IxN n -> Axes 'Row
indexAxesN (Ix1
d :> Ix (n - 1)
ix) =
let Axes [Ix1]
ax = Ix (n - 1) -> Axes 'Row
forall ix. AxesIndex ix => ix -> Axes 'Row
indexAxes Ix (n - 1)
ix
in [Ix1] -> Axes 'Row
forall (a :: Major). [Ix1] -> Axes a
Axes ([Ix1] -> Axes 'Row) -> [Ix1] -> Axes 'Row
forall a b. (a -> b) -> a -> b
$ Ix1
d Ix1 -> [Ix1] -> [Ix1]
forall a. a -> [a] -> [a]
: [Ix1]
ax
sizeAxes :: (AxesIndex ix, Index ix) => Sz ix -> Axes Column
sizeAxes :: forall ix. (AxesIndex ix, Index ix) => Sz ix -> Axes 'Column
sizeAxes (Sz ix
ix) = Axes 'Row -> Axes 'Column
toColumnMajor (Axes 'Row -> Axes 'Column) -> Axes 'Row -> Axes 'Column
forall a b. (a -> b) -> a -> b
$ ix -> Axes 'Row
forall ix. AxesIndex ix => ix -> Axes 'Row
indexAxes ix
ix