{-# LANGUAGE AllowAmbiguousTypes #-}
module Telescope.Asdf.NDArray.Types where
import Data.ByteString (ByteString)
import Data.ByteString qualified as BS
import GHC.Int (Int16, Int32, Int64)
import Telescope.Data.Axes
import Telescope.Data.Binary
data NDArrayData = NDArrayData
{ NDArrayData -> ByteString
bytes :: ByteString
, NDArrayData -> ByteOrder
byteorder :: ByteOrder
, NDArrayData -> DataType
datatype :: DataType
, NDArrayData -> Axes 'Row
shape :: Axes Row
}
deriving (NDArrayData -> NDArrayData -> Bool
(NDArrayData -> NDArrayData -> Bool)
-> (NDArrayData -> NDArrayData -> Bool) -> Eq NDArrayData
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NDArrayData -> NDArrayData -> Bool
== :: NDArrayData -> NDArrayData -> Bool
$c/= :: NDArrayData -> NDArrayData -> Bool
/= :: NDArrayData -> NDArrayData -> Bool
Eq)
instance Show NDArrayData where
show :: NDArrayData -> String
show NDArrayData
nd = [String] -> String
unwords [String
"NDArrayData", Int -> String
forall a. Show a => a -> String
show (ByteString -> Int
BS.length NDArrayData
nd.bytes), ByteOrder -> String
forall a. Show a => a -> String
show NDArrayData
nd.byteorder, Axes 'Row -> String
forall a. Show a => a -> String
show NDArrayData
nd.shape]
data DataType
= Float64
| Float32
| Int64
| Int32
| Int16
| Int8
| Bool8
| Ucs4 Int
deriving (Int -> DataType -> ShowS
[DataType] -> ShowS
DataType -> String
(Int -> DataType -> ShowS)
-> (DataType -> String) -> ([DataType] -> ShowS) -> Show DataType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DataType -> ShowS
showsPrec :: Int -> DataType -> ShowS
$cshow :: DataType -> String
show :: DataType -> String
$cshowList :: [DataType] -> ShowS
showList :: [DataType] -> ShowS
Show, DataType -> DataType -> Bool
(DataType -> DataType -> Bool)
-> (DataType -> DataType -> Bool) -> Eq DataType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DataType -> DataType -> Bool
== :: DataType -> DataType -> Bool
$c/= :: DataType -> DataType -> Bool
/= :: DataType -> DataType -> Bool
Eq)
class IsDataType a where
dataType :: DataType
instance IsDataType Double where
dataType :: DataType
dataType = DataType
Float64
instance IsDataType Float where
dataType :: DataType
dataType = DataType
Float32
instance IsDataType Int64 where
dataType :: DataType
dataType = DataType
Int64
instance IsDataType Int32 where
dataType :: DataType
dataType = DataType
Int32
instance IsDataType Int16 where
dataType :: DataType
dataType = DataType
Int16
instance IsDataType Int8 where
dataType :: DataType
dataType = DataType
Int8
instance (IsDataType a) => IsDataType [a] where
dataType :: DataType
dataType = forall a. IsDataType a => DataType
forall {k} (a :: k). IsDataType a => DataType
dataType @a