{-# LINE 1 "src/ArrayFire/Internal/Types.hsc" #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE CPP #-}
module ArrayFire.Internal.Types where
import ArrayFire.Internal.Defines
import Data.Complex
import Data.Proxy
import Data.Word
import Foreign.C.String
import Foreign.C.Types
import Foreign.ForeignPtr
import Foreign.Storable
import GHC.Int
data AFSeq
= AFSeq
{ afSeqBegin :: {-# UNPACK #-} !Double
, afSeqEnd :: {-# UNPACK #-} !Double
, afSeqStep :: {-# UNPACK #-} !Double
} deriving (Show, Eq)
instance Storable AFSeq where
sizeOf _ = (24)
{-# LINE 32 "src/ArrayFire/Internal/Types.hsc" #-}
alignment _ = 8
{-# LINE 33 "src/ArrayFire/Internal/Types.hsc" #-}
peek ptr = do
afSeqBegin <- (\hsc_ptr -> peekByteOff hsc_ptr 0) ptr
{-# LINE 35 "src/ArrayFire/Internal/Types.hsc" #-}
afSeqEnd <- (\hsc_ptr -> peekByteOff hsc_ptr 8) ptr
{-# LINE 36 "src/ArrayFire/Internal/Types.hsc" #-}
afSeqStep <- (\hsc_ptr -> peekByteOff hsc_ptr 16) ptr
{-# LINE 37 "src/ArrayFire/Internal/Types.hsc" #-}
pure AFSeq {..}
poke ptr AFSeq{..} = do
(\hsc_ptr -> pokeByteOff hsc_ptr 0) ptr afSeqBegin
{-# LINE 40 "src/ArrayFire/Internal/Types.hsc" #-}
(\hsc_ptr -> pokeByteOff hsc_ptr 8) ptr afSeqEnd
{-# LINE 41 "src/ArrayFire/Internal/Types.hsc" #-}
(\hsc_ptr -> pokeByteOff hsc_ptr 16) ptr afSeqStep
{-# LINE 42 "src/ArrayFire/Internal/Types.hsc" #-}
data AFIndex
= AFIndex
{ afIdx :: !(Either AFArray AFSeq)
, afIsSeq :: !Bool
, afIsBatch :: !Bool
}
instance Storable AFIndex where
sizeOf _ = (32)
{-# LINE 52 "src/ArrayFire/Internal/Types.hsc" #-}
alignment _ = 8
{-# LINE 53 "src/ArrayFire/Internal/Types.hsc" #-}
peek ptr = do
afIsSeq <- (\hsc_ptr -> peekByteOff hsc_ptr 24) ptr
{-# LINE 55 "src/ArrayFire/Internal/Types.hsc" #-}
afIsBatch <- (\hsc_ptr -> peekByteOff hsc_ptr 25) ptr
{-# LINE 56 "src/ArrayFire/Internal/Types.hsc" #-}
afIdx <-
if afIsSeq
then Left <$> (\hsc_ptr -> peekByteOff hsc_ptr 0) ptr
{-# LINE 59 "src/ArrayFire/Internal/Types.hsc" #-}
else Right <$> (\hsc_ptr -> peekByteOff hsc_ptr 0) ptr
{-# LINE 60 "src/ArrayFire/Internal/Types.hsc" #-}
pure AFIndex{..}
poke ptr AFIndex{..} = do
case afIdx of
Left afarr -> (\hsc_ptr -> pokeByteOff hsc_ptr 0) ptr afarr
{-# LINE 64 "src/ArrayFire/Internal/Types.hsc" #-}
Right afseq -> (\hsc_ptr -> pokeByteOff hsc_ptr 0) ptr afseq
{-# LINE 65 "src/ArrayFire/Internal/Types.hsc" #-}
(\hsc_ptr -> pokeByteOff hsc_ptr 24) ptr afIsSeq
{-# LINE 66 "src/ArrayFire/Internal/Types.hsc" #-}
(\hsc_ptr -> pokeByteOff hsc_ptr 25) ptr afIsBatch
{-# LINE 67 "src/ArrayFire/Internal/Types.hsc" #-}
data AFCFloat
= AFCFloat
{ afcReal :: {-# UNPACK #-} !Float
, afcImag :: {-# UNPACK #-} !Float
} deriving (Eq, Show)
instance Storable AFCFloat where
sizeOf _ = (8)
{-# LINE 76 "src/ArrayFire/Internal/Types.hsc" #-}
alignment _ = 4
{-# LINE 77 "src/ArrayFire/Internal/Types.hsc" #-}
peek ptr = do
afcReal <- (\hsc_ptr -> peekByteOff hsc_ptr 0) ptr
{-# LINE 79 "src/ArrayFire/Internal/Types.hsc" #-}
afcImag <- (\hsc_ptr -> peekByteOff hsc_ptr 4) ptr
{-# LINE 80 "src/ArrayFire/Internal/Types.hsc" #-}
pure AFCFloat{..}
poke ptr AFCFloat{..} = do
(\hsc_ptr -> pokeByteOff hsc_ptr 0) ptr afcReal
{-# LINE 83 "src/ArrayFire/Internal/Types.hsc" #-}
(\hsc_ptr -> pokeByteOff hsc_ptr 4) ptr afcImag
{-# LINE 84 "src/ArrayFire/Internal/Types.hsc" #-}
data AFCell
= AFCell
{ afCellRow :: {-# UNPACK #-} !Int
, afCellCol :: {-# UNPACK #-} !Int
, afCellTitle :: {-# UNPACK #-} !CString
, afCellColorMap :: {-# UNPACK #-} !AFColorMap
} deriving (Show, Eq)
instance Storable AFCell where
sizeOf _ = (24)
{-# LINE 95 "src/ArrayFire/Internal/Types.hsc" #-}
alignment _ = 8
{-# LINE 96 "src/ArrayFire/Internal/Types.hsc" #-}
peek ptr = do
afCellRow <- (\hsc_ptr -> peekByteOff hsc_ptr 0) ptr
{-# LINE 98 "src/ArrayFire/Internal/Types.hsc" #-}
afCellCol <- (\hsc_ptr -> peekByteOff hsc_ptr 4) ptr
{-# LINE 99 "src/ArrayFire/Internal/Types.hsc" #-}
afCellTitle <- (\hsc_ptr -> peekByteOff hsc_ptr 8) ptr
{-# LINE 100 "src/ArrayFire/Internal/Types.hsc" #-}
afCellColorMap <- (\hsc_ptr -> peekByteOff hsc_ptr 16) ptr
{-# LINE 101 "src/ArrayFire/Internal/Types.hsc" #-}
pure AFCell{..}
poke ptr AFCell{..} = do
(\hsc_ptr -> pokeByteOff hsc_ptr 0) ptr afCellRow
{-# LINE 104 "src/ArrayFire/Internal/Types.hsc" #-}
(\hsc_ptr -> pokeByteOff hsc_ptr 4) ptr afCellCol
{-# LINE 105 "src/ArrayFire/Internal/Types.hsc" #-}
(\hsc_ptr -> pokeByteOff hsc_ptr 8) ptr afCellTitle
{-# LINE 106 "src/ArrayFire/Internal/Types.hsc" #-}
(\hsc_ptr -> pokeByteOff hsc_ptr 16) ptr afCellColorMap
{-# LINE 107 "src/ArrayFire/Internal/Types.hsc" #-}
newtype Array a = Array (ForeignPtr ())
newtype Features = Features (ForeignPtr ())
newtype RandomEngine = RandomEngine (ForeignPtr ())
newtype Window = Window (ForeignPtr ())
class Storable a => AFType a where
afType :: Proxy a -> AFDtype
instance AFType Double where
afType Proxy = f64
instance AFType Float where
afType Proxy = f32
instance AFType (Complex Double) where
afType Proxy = c64
instance AFType (Complex Float) where
afType Proxy = c32
instance AFType CBool where
afType Proxy = b8
instance AFType Int32 where
afType Proxy = s32
instance AFType Word32 where
afType Proxy = u32
instance AFType Word8 where
afType Proxy = u8
instance AFType Int64 where
afType Proxy = s64
instance AFType Int where
afType Proxy = s64
instance AFType Int16 where
afType Proxy = s16
instance AFType Word16 where
afType Proxy = u16
instance AFType Word64 where
afType Proxy = u64
instance AFType Word where
afType Proxy = u64
data Backend
= Default
| CPU
| CUDA
| OpenCL
deriving (Show, Eq, Ord)
toBackend :: AFBackend -> Backend
toBackend (AFBackend 0) = Default
toBackend (AFBackend 1) = CPU
toBackend (AFBackend 2) = CUDA
toBackend (AFBackend 4) = OpenCL
toBackend (AFBackend x) = error $ "Invalid backend: " <> show x
toAFBackend :: Backend -> AFBackend
toAFBackend Default = (AFBackend 0)
toAFBackend CPU = (AFBackend 1)
toAFBackend CUDA = (AFBackend 2)
toAFBackend OpenCL = (AFBackend 4)
toBackends :: Int -> [Backend]
toBackends 1 = [CPU]
toBackends 2 = [CUDA]
toBackends 3 = [CPU,CUDA]
toBackends 4 = [OpenCL]
toBackends 5 = [CPU,OpenCL]
toBackends 6 = [CUDA,OpenCL]
toBackends 7 = [CPU,CUDA,OpenCL]
toBackends _ = []
data MatProp
= None
| Trans
| CTrans
| Conj
| Upper
| Lower
| DiagUnit
| Sym
| PosDef
| Orthog
| TriDiag
| BlockDiag
deriving (Show, Eq, Ord)
fromMatProp
:: AFMatProp
-> MatProp
fromMatProp (AFMatProp 0) = None
fromMatProp (AFMatProp 1) = Trans
fromMatProp (AFMatProp 2) = CTrans
fromMatProp (AFMatProp 4) = Conj
fromMatProp (AFMatProp 32) = Upper
fromMatProp (AFMatProp 64) = Lower
fromMatProp (AFMatProp 128) = DiagUnit
fromMatProp (AFMatProp 512) = Sym
fromMatProp (AFMatProp 1024) = PosDef
fromMatProp (AFMatProp 2048) = Orthog
fromMatProp (AFMatProp 4096) = TriDiag
fromMatProp (AFMatProp 8192) = BlockDiag
fromMatProp x = error $ "Invalid AFMatProp value: " <> show x
toMatProp
:: MatProp
-> AFMatProp
toMatProp None = (AFMatProp 0)
toMatProp Trans = (AFMatProp 1)
toMatProp CTrans = (AFMatProp 2)
toMatProp Conj = (AFMatProp 4)
toMatProp Upper = (AFMatProp 32)
toMatProp Lower = (AFMatProp 64)
toMatProp DiagUnit = (AFMatProp 128)
toMatProp Sym = (AFMatProp 512)
toMatProp PosDef = (AFMatProp 1024)
toMatProp Orthog = (AFMatProp 2048)
toMatProp TriDiag = (AFMatProp 4096)
toMatProp BlockDiag = (AFMatProp 8192)
data BinaryOp
= Add
| Mul
| Min
| Max
deriving (Show, Eq, Ord)
toBinaryOp :: BinaryOp -> AFBinaryOp
toBinaryOp Add = AFBinaryOp 0
toBinaryOp Mul = AFBinaryOp 1
toBinaryOp Min = AFBinaryOp 2
toBinaryOp Max = AFBinaryOp 3
fromBinaryOp :: AFBinaryOp -> BinaryOp
fromBinaryOp (AFBinaryOp 0) = Add
fromBinaryOp (AFBinaryOp 1) = Mul
fromBinaryOp (AFBinaryOp 2) = Min
fromBinaryOp (AFBinaryOp 3) = Max
fromBinaryOp x = error ("Invalid Binary Op: " <> show x)
data Storage
= Dense
| CSR
| CSC
| COO
deriving (Show, Eq, Ord, Enum)
toStorage :: Storage -> AFStorage
toStorage = AFStorage . fromIntegral . fromEnum
fromStorage :: AFStorage -> Storage
fromStorage (AFStorage (fromIntegral -> x))
| x `elem` [0..3] = toEnum x
| otherwise = error $ "Invalid Storage " <> (show x)
data RandomEngineType
= Philox
| ThreeFry
| Mersenne
deriving (Eq, Show)
toRandomEngine :: AFRandomEngineType -> RandomEngineType
toRandomEngine (AFRandomEngineType 100) = Philox
toRandomEngine (AFRandomEngineType 200) = ThreeFry
toRandomEngine (AFRandomEngineType 300) = Mersenne
toRandomEngine (AFRandomEngineType x) =
error ("Invalid random engine: " <> show x)
fromRandomEngine :: RandomEngineType -> AFRandomEngineType
fromRandomEngine Philox = (AFRandomEngineType 100)
fromRandomEngine ThreeFry = (AFRandomEngineType 200)
fromRandomEngine Mersenne = (AFRandomEngineType 300)
data InterpType
= Nearest
| Linear
| Bilinear
| Cubic
| LowerInterp
| LinearCosine
| BilinearCosine
| Bicubic
| CubicSpline
| BicubicSpline
deriving (Show, Eq, Ord, Enum)
toInterpType :: AFInterpType -> InterpType
toInterpType (AFInterpType (fromIntegral -> x)) = toEnum x
fromInterpType :: InterpType -> AFInterpType
fromInterpType = AFInterpType . fromIntegral . fromEnum
data BorderType
= PadZero
| PadSym
deriving (Show, Ord, Enum, Eq)
toBorderType :: AFBorderType -> BorderType
toBorderType (AFBorderType (fromIntegral -> x)) = toEnum x
fromBorderType :: BorderType -> AFBorderType
fromBorderType = AFBorderType . fromIntegral . fromEnum
data Connectivity
= Conn4
| Conn8
deriving (Show, Ord, Enum, Eq)
toConnectivity :: AFConnectivity -> Connectivity
toConnectivity (AFConnectivity 4) = Conn4
toConnectivity (AFConnectivity 8) = Conn4
toConnectivity (AFConnectivity x) = error ("Unknown connectivity option: " <> show x)
fromConnectivity :: Connectivity -> AFConnectivity
fromConnectivity Conn4 = AFConnectivity 4
fromConnectivity Conn8 = AFConnectivity 8
data CSpace
= Gray
| RGB
| HSV
| YCBCR
deriving (Show, Eq, Ord, Enum)
toCSpace :: AFCSpace -> CSpace
toCSpace (AFCSpace (fromIntegral -> x)) = toEnum x
fromCSpace :: CSpace -> AFCSpace
fromCSpace = AFCSpace . fromIntegral . fromEnum
data YccStd
= Ycc601
| Ycc709
| Ycc2020
deriving (Show, Eq, Ord)
toAFYccStd :: AFYccStd -> YccStd
toAFYccStd (AFYccStd 601) = Ycc601
toAFYccStd (AFYccStd 709) = Ycc709
toAFYccStd (AFYccStd 2020) = Ycc2020
toAFYccStd (AFYccStd x) = error ("Unknown AFYccStd option: " <> show x)
fromAFYccStd :: YccStd -> AFYccStd
fromAFYccStd Ycc601 = afYcc601
fromAFYccStd Ycc709 = afYcc709
fromAFYccStd Ycc2020 = afYcc2020
data MomentType
= M00
| M01
| M10
| M11
| FirstOrder
deriving (Show, Eq, Ord)
toMomentType :: AFMomentType -> MomentType
toMomentType x
| x == afMomentM00 = M00
| x == afMomentM01 = M01
| x == afMomentM10 = M10
| x == afMomentM11 = M11
| x == afMomentFirstOrder = FirstOrder
| otherwise = error ("Unknown moment type: " <> show x)
fromMomentType :: MomentType -> AFMomentType
fromMomentType M00 = afMomentM00
fromMomentType M01 = afMomentM01
fromMomentType M10 = afMomentM10
fromMomentType M11 = afMomentM11
fromMomentType FirstOrder = afMomentFirstOrder
data CannyThreshold
= Manual
| AutoOtsu
deriving (Show, Eq, Ord, Enum)
toCannyThreshold :: AFCannyThreshold -> CannyThreshold
toCannyThreshold (AFCannyThreshold (fromIntegral -> x)) = toEnum x
fromCannyThreshold :: CannyThreshold -> AFCannyThreshold
fromCannyThreshold = AFCannyThreshold . fromIntegral . fromEnum
data FluxFunction
= FluxDefault
| FluxQuadratic
| FluxExponential
deriving (Show, Eq, Ord, Enum)
toFluxFunction :: AFFluxFunction -> FluxFunction
toFluxFunction (AFFluxFunction (fromIntegral -> x)) = toEnum x
fromFluxFunction :: FluxFunction -> AFFluxFunction
fromFluxFunction = AFFluxFunction . fromIntegral . fromEnum
data DiffusionEq
= DiffusionDefault
| DiffusionGrad
| DiffusionMCDE
deriving (Show, Eq, Ord, Enum)
toDiffusionEq :: AFDiffusionEq -> DiffusionEq
toDiffusionEq (AFDiffusionEq (fromIntegral -> x)) = toEnum x
fromDiffusionEq :: DiffusionEq -> AFDiffusionEq
fromDiffusionEq = AFDiffusionEq . fromIntegral . fromEnum
data IterativeDeconvAlgo
= DeconvDefault
| DeconvLandweber
| DeconvRichardsonLucy
deriving (Show, Eq, Ord, Enum)
toIterativeDeconvAlgo :: AFIterativeDeconvAlgo -> IterativeDeconvAlgo
toIterativeDeconvAlgo (AFIterativeDeconvAlgo (fromIntegral -> x)) = toEnum x
fromIterativeDeconvAlgo :: IterativeDeconvAlgo -> AFIterativeDeconvAlgo
fromIterativeDeconvAlgo = AFIterativeDeconvAlgo . fromIntegral . fromEnum
data InverseDeconvAlgo
= InverseDeconvDefault
| InverseDeconvTikhonov
deriving (Show, Eq, Ord, Enum)
toInverseDeconvAlgo :: AFInverseDeconvAlgo -> InverseDeconvAlgo
toInverseDeconvAlgo (AFInverseDeconvAlgo (fromIntegral -> x)) = toEnum x
fromInverseDeconvAlgo :: InverseDeconvAlgo -> AFInverseDeconvAlgo
fromInverseDeconvAlgo = AFInverseDeconvAlgo . fromIntegral . fromEnum
data Cell
= Cell
{ cellRow :: Int
, cellCol :: Int
, cellTitle :: String
, cellColorMap :: ColorMap
} deriving (Show, Eq)
cellToAFCell :: Cell -> IO AFCell
cellToAFCell Cell {..} =
withCString cellTitle $ \cstr ->
pure AFCell { afCellRow = cellRow
, afCellCol = cellCol
, afCellTitle = cstr
, afCellColorMap = fromColorMap cellColorMap
}
data ColorMap
= ColorMapDefault
| ColorMapSpectrum
| ColorMapColors
| ColorMapRed
| ColorMapMood
| ColorMapHeat
| ColorMapBlue
| ColorMapInferno
| ColorMapMagma
| ColorMapPlasma
| ColorMapViridis
deriving (Show, Eq, Ord, Enum)
fromColorMap :: ColorMap -> AFColorMap
fromColorMap = AFColorMap . fromIntegral . fromEnum
toColorMap :: AFColorMap -> ColorMap
toColorMap (AFColorMap (fromIntegral -> x)) = toEnum x
data MarkerType
= MarkerTypeNone
| MarkerTypePoint
| MarkerTypeCircle
| MarkerTypeSquare
| MarkerTypeTriangle
| MarkerTypeCross
| MarkerTypePlus
| MarkerTypeStar
deriving (Show, Eq, Ord, Enum)
fromMarkerType :: MarkerType -> AFMarkerType
fromMarkerType = AFMarkerType . fromIntegral . fromEnum
toMarkerType :: AFMarkerType -> MarkerType
toMarkerType (AFMarkerType (fromIntegral -> x)) = toEnum x
data MatchType
= MatchTypeSAD
| MatchTypeZSAD
| MatchTypeLSAD
| MatchTypeSSD
| MatchTypeZSSD
| MatchTypeLSSD
| MatchTypeNCC
| MatchTypeZNCC
| MatchTypeSHD
deriving (Show, Eq, Ord, Enum)
fromMatchType :: MatchType -> AFMatchType
fromMatchType = AFMatchType . fromIntegral . fromEnum
toMatchType :: AFMatchType -> MatchType
toMatchType (AFMatchType (fromIntegral -> x)) = toEnum x
data TopK
= TopKDefault
| TopKMin
| TopKMax
deriving (Show, Eq, Ord, Enum)
fromTopK :: TopK -> AFTopkFunction
fromTopK = AFTopkFunction . fromIntegral . fromEnum
toTopK :: AFTopkFunction -> TopK
toTopK (AFTopkFunction (fromIntegral -> x)) = toEnum x
data HomographyType
= RANSAC
| LMEDS
deriving (Show, Eq, Ord, Enum)
fromHomographyType :: HomographyType -> AFHomographyType
fromHomographyType = AFHomographyType . fromIntegral . fromEnum
toHomographyType :: AFHomographyType -> HomographyType
toHomographyType (AFHomographyType (fromIntegral -> x)) = toEnum x
data Seq
= Seq
{ seqBegin :: !Double
, seqEnd :: !Double
, seqStep :: !Double
} deriving (Show, Eq, Ord)
toAFSeq :: Seq -> AFSeq
toAFSeq (Seq x y z) = (AFSeq x y z)
data Index a
= Index
{ idx :: Either (Array a) Seq
, isSeq :: !Bool
, isBatch :: !Bool
}
seqIdx :: Seq -> Bool -> Index a
seqIdx s = Index (Right s) True
arrIdx :: Array a -> Bool -> Index a
arrIdx a = Index (Left a) False
toAFIndex :: Index a -> IO AFIndex
toAFIndex (Index a b c) = do
case a of
Right s -> pure $ AFIndex (Right (toAFSeq s)) b c
Left (Array fptr) -> do
withForeignPtr fptr $ \ptr ->
pure $ AFIndex (Left ptr) b c
type Version = (Int,Int,Int)
data NormType
= NormVectorOne
| NormVectorInf
| NormVector2
| NormVectorP
| NormMatrix1
| NormMatrixInf
| NormMatrix2
| NormMatrixLPQ
| NormEuclid
deriving (Show, Eq, Enum)
fromNormType :: NormType -> AFNormType
fromNormType = AFNormType . fromIntegral . fromEnum
toNormType :: AFNormType -> NormType
toNormType (AFNormType (fromIntegral -> x)) = toEnum x
data ConvDomain
= ConvDomainAuto
| ConvDomainSpatial
| ConvDomainFreq
deriving (Show, Eq, Enum)
data ConvMode
= ConvDefault
| ConvExpand
deriving (Show, Eq, Enum)
fromConvDomain :: ConvDomain -> AFConvDomain
fromConvDomain = AFConvDomain . fromIntegral . fromEnum
toConvDomain :: AFConvDomain -> ConvDomain
toConvDomain (AFConvDomain (fromIntegral -> x)) = toEnum x
fromConvMode :: AFConvMode -> ConvMode
fromConvMode (AFConvMode (fromIntegral -> x)) = toEnum x
toConvMode :: ConvMode -> AFConvMode
toConvMode = AFConvMode . fromIntegral . fromEnum
data AFDType
= F32
| C32
| F64
| C64
| B8
| S32
| U32
| U8
| S64
| U64
| S16
| U16
deriving (Show, Eq, Enum)
fromAFType :: AFDtype -> AFDType
fromAFType (AFDtype (fromIntegral -> x)) = toEnum x
toAFType :: AFDType -> AFDtype
toAFType = AFDtype . fromIntegral . fromEnum