{-# LINE 1 "src/ArrayFire/Internal/Defines.hsc" #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE CPP             #-}
{-# LANGUAGE RecordWildCards #-}
module ArrayFire.Internal.Defines where

import Foreign.Ptr
import Foreign.C.Types
import Foreign.Storable






afVersion :: Integer
afVersion :: Integer
afVersion = Integer
38
{-# LINE 17 "src/ArrayFire/Internal/Defines.hsc" #-}

newtype AFErr = AFErr { AFErr -> CInt
afError :: CInt }
  deriving (Int -> AFErr -> ShowS
[AFErr] -> ShowS
AFErr -> String
(Int -> AFErr -> ShowS)
-> (AFErr -> String) -> ([AFErr] -> ShowS) -> Show AFErr
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AFErr] -> ShowS
$cshowList :: [AFErr] -> ShowS
show :: AFErr -> String
$cshow :: AFErr -> String
showsPrec :: Int -> AFErr -> ShowS
$cshowsPrec :: Int -> AFErr -> ShowS
Show, AFErr -> AFErr -> Bool
(AFErr -> AFErr -> Bool) -> (AFErr -> AFErr -> Bool) -> Eq AFErr
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AFErr -> AFErr -> Bool
$c/= :: AFErr -> AFErr -> Bool
== :: AFErr -> AFErr -> Bool
$c== :: AFErr -> AFErr -> Bool
Eq)

afSuccess  :: AFErr
afSuccess :: AFErr
afSuccess  = CInt -> AFErr
AFErr CInt
0
afErrNoMem  :: AFErr
afErrNoMem :: AFErr
afErrNoMem  = CInt -> AFErr
AFErr CInt
101
afErrDriver  :: AFErr
afErrDriver :: AFErr
afErrDriver  = CInt -> AFErr
AFErr CInt
102
afErrRuntime  :: AFErr
afErrRuntime :: AFErr
afErrRuntime  = CInt -> AFErr
AFErr CInt
103
afErrInvalidArray  :: AFErr
afErrInvalidArray :: AFErr
afErrInvalidArray  = CInt -> AFErr
AFErr CInt
201
afErrArg  :: AFErr
afErrArg :: AFErr
afErrArg  = CInt -> AFErr
AFErr CInt
202
afErrSize  :: AFErr
afErrSize :: AFErr
afErrSize  = CInt -> AFErr
AFErr CInt
203
afErrType  :: AFErr
afErrType :: AFErr
afErrType  = CInt -> AFErr
AFErr CInt
204
afErrDiffType  :: AFErr
afErrDiffType :: AFErr
afErrDiffType  = CInt -> AFErr
AFErr CInt
205
afErrBatch  :: AFErr
afErrBatch :: AFErr
afErrBatch  = CInt -> AFErr
AFErr CInt
207
afErrDevice  :: AFErr
afErrDevice :: AFErr
afErrDevice  = CInt -> AFErr
AFErr CInt
208
afErrNotSupported  :: AFErr
afErrNotSupported :: AFErr
afErrNotSupported  = CInt -> AFErr
AFErr CInt
301
afErrNotConfigured  :: AFErr
afErrNotConfigured :: AFErr
afErrNotConfigured  = CInt -> AFErr
AFErr CInt
302
afErrNonFree  :: AFErr
afErrNonFree :: AFErr
afErrNonFree  = CInt -> AFErr
AFErr CInt
303
afErrNoDbl  :: AFErr
afErrNoDbl :: AFErr
afErrNoDbl  = CInt -> AFErr
AFErr CInt
401
afErrNoGfx  :: AFErr
afErrNoGfx  = AFErr 402
afErrLoadLib  :: AFErr
afErrLoadLib :: AFErr
afErrLoadLib  = CInt -> AFErr
AFErr CInt
501
afErrLoadSym  :: AFErr
afErrLoadSym :: AFErr
afErrLoadSym  = CInt -> AFErr
AFErr CInt
502
afErrArrBkndMismatch  :: AFErr
afErrArrBkndMismatch :: AFErr
afErrArrBkndMismatch  = CInt -> AFErr
AFErr CInt
503
afErrInternal  :: AFErr
afErrInternal :: AFErr
afErrInternal  CInt
= CInt -> AFErr
AFErr CInt
998
afErrUnknown  :: AFErr
afErrUnknown :: AFErr
afErrUnknown  = CInt -> AFErr
AFErr CInt
999

{-# LINE 44 "src/ArrayFire/Internal/Defines.hsc" #-}

-- | Low-level for representation of ArrayFire types

-- | AFDType
-- Newtype over ArrayFire's internal type tag
newtype AFDtype = AFDtype
  { afDType :: CInt
  -- ^ Value corresponding to ArrayFire type
  } deriving (Show, Eq, Storable)

-- | Enums for AFDtype
f32  :: AFDtype
f32  = AFDtype 0
c32  :: AFDtype
c32  = AFDtype 1
f64  :: AFDtype
f64  = AFDtype 2
c64  :: AFDtype
c64  = AFDtype 3
b8  :: AFDtype
b8  = AFDtype 4
s32  :: AFDtype
s32 :: AFDtype
s32  = CInt -> AFDtype
AFDtype CInt
5
u32  :: AFDtype
u32 :: AFDtype
u32  = CInt -> AFDtype
AFDtype CInt
6
u8  :: AFDtype
u8 :: AFDtype
u8  = CInt -> AFDtype
AFDtype CInt
7
s64  :: AFDtype
s64 :: AFDtype
s64  = CInt -> AFDtype
AFDtype CInt
8
u64  :: AFDtype
u64 :: AFDtype
u64  = CInt -> AFDtype
AFDtype CInt
9
s16  :: AFDtype
s16 :: AFDtype
s16  = CInt -> AFDtype
AFDtype CInt
10
u16  :: AFDtype
u16 :: AFDtype
u16  = AFDtype 11

{-# LINE 69 "src/ArrayFire/Internal/Defines.hsc" #-}

newtype AFSource = AFSource CInt
  deriving (Ord, Show, Eq)

afDevice  :: AFSource
afDevice  = AFSource 0
afHost  :: AFSource
afHost  = AFSource 1

{-# LINE 77 "src/ArrayFire/Internal/Defines.hsc" #-}

afMaxDims :: Integer
afMaxDims = 4
{-# LINE 80 "src/ArrayFire/Internal/Defines.hsc" #-}

newtype AFSomeEnum = AFSomeEnum Int
  deriving (Eq AFSomeEnum
Eq AFSomeEnum
-> (AFSomeEnum -> AFSomeEnum -> Ordering)
-> (AFSomeEnum -> AFSomeEnum -> Bool)
-> (AFSomeEnum -> AFSomeEnum -> Bool)
-> (AFSomeEnum -> AFSomeEnum -> Bool)
-> (AFSomeEnum -> AFSomeEnum -> Bool)
-> (AFSomeEnum -> AFSomeEnum -> AFSomeEnum)
-> (AFSomeEnum -> AFSomeEnum -> AFSomeEnum)
-> Ord AFSomeEnum
AFSomeEnum -> AFSomeEnum -> Bool
AFSomeEnum -> AFSomeEnum -> Ordering
AFSomeEnum -> AFSomeEnum -> AFSomeEnum
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: AFSomeEnum -> AFSomeEnum -> AFSomeEnum
$cmin :: AFSomeEnum -> AFSomeEnum -> AFSomeEnum
max :: AFSomeEnum -> AFSomeEnum -> AFSomeEnum
$cmax :: AFSomeEnum -> AFSomeEnum -> AFSomeEnum
>= :: AFSomeEnum -> AFSomeEnum -> Bool
$c>= :: AFSomeEnum -> AFSomeEnum -> Bool
> :: AFSomeEnum -> AFSomeEnum -> Bool
$c> :: AFSomeEnum -> AFSomeEnum -> Bool
<= :: AFSomeEnum -> AFSomeEnum -> Bool
$c<= :: AFSomeEnum -> AFSomeEnum -> Bool
< :: AFSomeEnum -> AFSomeEnum -> Bool
$c< :: AFSomeEnum -> AFSomeEnum -> Bool
compare :: AFSomeEnum -> AFSomeEnum -> Ordering
$ccompare :: AFSomeEnum -> AFSomeEnum -> Ordering
Ord, Int -> AFSomeEnum -> ShowS
[AFSomeEnum] -> ShowS
AFSomeEnum -> String
(Int -> AFSomeEnum -> ShowS)
-> (AFSomeEnum -> String)
-> ([AFSomeEnum] -> ShowS)
-> Show AFSomeEnum
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AFSomeEnum] -> ShowS
$cshowList :: [AFSomeEnum] -> ShowS
show :: AFSomeEnum -> String
$cshow :: AFSomeEnum -> String
showsPrec :: Int -> AFSomeEnum -> ShowS
$cshowsPrec :: Int -> AFSomeEnum -> ShowS
Show, AFSomeEnum -> AFSomeEnum -> Bool
(AFSomeEnum -> AFSomeEnum -> Bool)
-> (AFSomeEnum -> AFSomeEnum -> Bool) -> Eq AFSomeEnum
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AFSomeEnum -> AFSomeEnum -> Bool
$c/= :: AFSomeEnum -> AFSomeEnum -> Bool
== :: AFSomeEnum -> AFSomeEnum -> Bool
$c== :: AFSomeEnum -> AFSomeEnum -> Bool
Eq, Ptr AFSomeEnum -> IO AFSomeEnum
Ptr AFSomeEnum -> Int -> IO AFSomeEnum
Ptr AFSomeEnum -> Int -> AFSomeEnum -> IO ()
Ptr AFSomeEnum -> AFSomeEnum -> IO ()
AFSomeEnum -> Int
(AFSomeEnum -> Int)
-> (AFSomeEnum -> Int)
-> (Ptr AFSomeEnum -> Int -> IO AFSomeEnum)
-> (Ptr AFSomeEnum -> Int -> AFSomeEnum -> IO ())
-> (forall b. Ptr b -> Int -> IO AFSomeEnum)
-> (forall b. Ptr b -> Int -> AFSomeEnum -> IO ())
-> (Ptr AFSomeEnum -> IO AFSomeEnum)
-> (Ptr AFSomeEnum -> AFSomeEnum -> IO ())
-> Storable AFSomeEnum
forall b. Ptr b -> Int -> IO AFSomeEnum
forall b. Ptr b -> Int -> AFSomeEnum -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
poke :: Ptr AFSomeEnum -> AFSomeEnum -> IO ()
$cpoke :: Ptr AFSomeEnum -> AFSomeEnum -> IO ()
peek :: Ptr AFSomeEnum -> IO AFSomeEnum
$cpeek :: Ptr AFSomeEnum -> IO AFSomeEnum
pokeByteOff :: forall b. Ptr b -> Int -> AFSomeEnum -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> AFSomeEnum -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO AFSomeEnum
$cpeekByteOff :: forall b. Ptr b -> Int -> IO AFSomeEnum
pokeElemOff :: Ptr AFSomeEnum -> Int -> AFSomeEnum -> IO ()
$cpokeElemOff :: Ptr AFSomeEnum -> Int -> AFSomeEnum -> IO ()
peekElemOff :: Ptr AFSomeEnum -> Int -> IO AFSomeEnum
$cpeekElemOff :: Ptr AFSomeEnum -> Int -> IO AFSomeEnum
alignment :: AFSomeEnum -> Int
$calignment :: AFSomeEnum -> Int
sizeOf :: AFSomeEnum -> Int
$csizeOf :: AFSomeEnum -> Int
Storable)

afSomeEnum  :: AFSomeEnum
afSomeEnum :: AFSomeEnum
afSomeEnum  = Int -> AFSomeEnum
AFSomeEnum Int
0

{-# LINE 87 "src/ArrayFire/Internal/Defines.hsc" #-}


-- // A handle for an internal array object
type AFArray = Ptr ()
type AFFeatures = Ptr ()
type AFRandomEngine = Ptr ()

-- // A handle for an internal array object
type AFWindow = Ptr ()

newtype AFInterpType = AFInterpType CInt
  deriving (Eq AFInterpType
Eq AFInterpType
-> (AFInterpType -> AFInterpType -> Ordering)
-> (AFInterpType -> AFInterpType -> Bool)
-> (AFInterpType -> AFInterpType -> Bool)
-> (AFInterpType -> AFInterpType -> Bool)
-> (AFInterpType -> AFInterpType -> Bool)
-> (AFInterpType -> AFInterpType -> AFInterpType)
-> (AFInterpType -> AFInterpType -> AFInterpType)
-> Ord AFInterpType
AFInterpType -> AFInterpType -> Bool
AFInterpType -> AFInterpType -> Ordering
AFInterpType -> AFInterpType -> AFInterpType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: AFInterpType -> AFInterpType -> AFInterpType
$cmin :: AFInterpType -> AFInterpType -> AFInterpType
max :: AFInterpType -> AFInterpType -> AFInterpType
$cmax :: AFInterpType -> AFInterpType -> AFInterpType
>= :: AFInterpType -> AFInterpType -> Bool
$c>= :: AFInterpType -> AFInterpType -> Bool
> :: AFInterpType -> AFInterpType -> Bool
$c> :: AFInterpType -> AFInterpType -> Bool
<= :: AFInterpType -> AFInterpType -> Bool
$c<= :: AFInterpType -> AFInterpType -> Bool
< :: AFInterpType -> AFInterpType -> Bool
$c< :: AFInterpType -> AFInterpType -> Bool
compare :: AFInterpType -> AFInterpType -> Ordering
$ccompare :: AFInterpType -> AFInterpType -> Ordering
Ord, Int -> AFInterpType -> ShowS
[AFInterpType] -> ShowS
AFInterpType -> String
(Int -> AFInterpType -> ShowS)
-> (AFInterpType -> String)
-> ([AFInterpType] -> ShowS)
-> Show AFInterpType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AFInterpType] -> ShowS
$cshowList :: [AFInterpType] -> ShowS
show :: AFInterpType -> String
$cshow :: AFInterpType -> String
showsPrec :: Int -> AFInterpType -> ShowS
$cshowsPrec :: Int -> AFInterpType -> ShowS
Show, AFInterpType -> AFInterpType -> Bool
(AFInterpType -> AFInterpType -> Bool)
-> (AFInterpType -> AFInterpType -> Bool) -> Eq AFInterpType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AFInterpType -> AFInterpType -> Bool
$c/= :: AFInterpType -> AFInterpType -> Bool
== :: AFInterpType -> AFInterpType -> Bool
$c== :: AFInterpType -> AFInterpType -> Bool
Eq, Ptr AFInterpType -> IO AFInterpType
Ptr AFInterpType -> Int -> IO AFInterpType
Ptr AFInterpType -> Int -> AFInterpType -> IO ()
Ptr AFInterpType -> AFInterpType -> IO ()
AFInterpType -> Int
(AFInterpType -> Int)
-> (AFInterpType -> Int)
-> (Ptr AFInterpType -> Int -> IO AFInterpType)
-> (Ptr AFInterpType -> Int -> AFInterpType -> IO ())
-> (forall b. Ptr b -> Int -> IO AFInterpType)
-> (forall b. Ptr b -> Int -> AFInterpType -> IO ())
-> (Ptr AFInterpType -> IO AFInterpType)
-> (Ptr AFInterpType -> AFInterpType -> IO ())
-> Storable AFInterpType
forall b. Ptr b -> Int -> IO AFInterpType
forall b. Ptr b -> Int -> AFInterpType -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
poke :: Ptr AFInterpType -> AFInterpType -> IO ()
$cpoke :: Ptr AFInterpType -> AFInterpType -> IO ()
peek :: Ptr AFInterpType -> IO AFInterpType
$cpeek :: Ptr AFInterpType -> IO AFInterpType
pokeByteOff :: forall b. Ptr b -> Int -> AFInterpType -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> AFInterpType -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO AFInterpType
$cpeekByteOff :: forall b. Ptr b -> Int -> IO AFInterpType
pokeElemOff :: Ptr AFInterpType -> Int -> AFInterpType -> IO ()
$cpokeElemOff :: Ptr AFInterpType -> Int -> AFInterpType -> IO ()
peekElemOff :: Ptr AFInterpType -> Int -> IO AFInterpType
$cpeekElemOff :: Ptr AFInterpType -> Int -> IO AFInterpType
alignment :: AFInterpType -> Int
$calignment :: AFInterpType -> Int
sizeOf :: AFInterpType -> Int
$csizeOf :: AFInterpType -> Int
Storable)

afInterpNearest  :: AFInterpType
afInterpNearest :: AFInterpType
afInterpNearest  = CInt -> AFInterpType
AFInterpType CInt
0
afInterpLinear  :: AFInterpType
afInterpLinear :: AFInterpType
afInterpLinear  = CInt -> AFInterpType
AFInterpType CInt
1
afInterpBilinear  :: AFInterpType
afInterpBilinear :: AFInterpType
afInterpBilinear  = CInt -> AFInterpType
AFInterpType CInt
2
afInterpCubic  :: AFInterpType
afInterpCubic :: AFInterpType
afInterpCubic  = CInt -> AFInterpType
AFInterpType CInt
3
afInterpLower  :: AFInterpType
afInterpLower :: AFInterpType
afInterpLower  = CInt -> AFInterpType
AFInterpType CInt
4
afInterpLinearCosine  :: AFInterpType
afInterpLinearCosine :: AFInterpType
afInterpLinearCosine  = CInt -> AFInterpType
AFInterpType CInt
5
afInterpBilinearCosine  :: AFInterpType
afInterpBilinearCosine :: AFInterpType
afInterpBilinearCosine  = AFInterpType 6
afInterpBicubic  :: AFInterpType
afInterpBicubic :: AFInterpType
afInterpBicubic  = CInt -> AFInterpType
AFInterpType CInt
7
afInterpCubicSpline  :: AFInterpType
afInterpCubicSpline :: AFInterpType
afInterpCubicSpline  = CInt -> AFInterpType
AFInterpType CInt
8
afInterpBicubicSpline  :: AFInterpType
afInterpBicubicSpline :: AFInterpType
afInterpBicubicSpline  = AFInterpType 9

{-# LINE 112 "src/ArrayFire/Internal/Defines.hsc" #-}

newtype AFBorderType = AFBorderType CInt
  deriving (Ord, Show, Eq, Storable)

afBorderPadZero  :: AFBorderType
afBorderPadZero  = AFBorderType 0
afPadSym  :: AFBorderType
afPadSym  = AFBorderType 1

{-# LINE 120 "src/ArrayFire/Internal/Defines.hsc" #-}

newtype AFConnectivity = AFConnectivity CInt
  deriving (Ord, Show, Eq, Storable)

afConnectivity4  :: AFConnectivity
afConnectivity4 :: AFConnectivity
afConnectivity4  = CInt -> AFConnectivity
AFConnectivity CInt
4
afConnectivity8  :: AFConnectivity
afConnectivity8 :: AFConnectivity
afConnectivity8  = CInt -> AFConnectivity
AFConnectivity CInt
8

{-# LINE 128 "src/ArrayFire/Internal/Defines.hsc" #-}

newtype AFConvMode = AFConvMode CInt
  deriving (Ord, Show, Eq, Storable)

afConvDefault  :: AFConvMode
afConvDefault :: AFConvMode
afConvDefault  = CInt -> AFConvMode
AFConvMode CInt
0
afConvExpand  :: AFConvMode
afConvExpand :: AFConvMode
afConvExpand  = CInt -> AFConvMode
AFConvMode CInt
1

{-# LINE 136 "src/ArrayFire/Internal/Defines.hsc" #-}

newtype AFConvDomain = AFConvDomain CInt
  deriving (Ord, Show, Eq, Storable)

afConvAuto  :: AFConvDomain
afConvAuto :: AFConvDomain
afConvAuto  = CInt -> AFConvDomain
AFConvDomain CInt
0
afConvSpatial  :: AFConvDomain
afConvSpatial :: AFConvDomain
afConvSpatial  = CInt -> AFConvDomain
AFConvDomain CInt
1
afConvFreq  :: AFConvDomain
afConvFreq :: AFConvDomain
afConvFreq  = CInt -> AFConvDomain
AFConvDomain CInt
2

{-# LINE 145 "src/ArrayFire/Internal/Defines.hsc" #-}

newtype AFMatchType = AFMatchType CInt
  deriving (Ord, Show, Eq, Storable)

afSAD   :: AFMatchType
afSAD :: AFMatchType
afSAD   = CInt -> AFMatchType
AFMatchType CInt
0
afZSAD  :: AFMatchType
afZSAD :: AFMatchType
afZSAD  = CInt -> AFMatchType
AFMatchType CInt
1
afLSAD  :: AFMatchType
afLSAD :: AFMatchType
afLSAD  = CInt -> AFMatchType
AFMatchType CInt
2
afSSD   :: AFMatchType
afSSD :: AFMatchType
afSSD   = CInt -> AFMatchType
AFMatchType CInt
3
afZSSD  :: AFMatchType
afZSSD :: AFMatchType
afZSSD  = CInt -> AFMatchType
AFMatchType CInt
4
afLSSD  :: AFMatchType
afLSSD :: AFMatchType
afLSSD  = CInt -> AFMatchType
AFMatchType CInt
5
afNCC   :: AFMatchType
afNCC :: AFMatchType
afNCC   = CInt -> AFMatchType
AFMatchType CInt
6
afZNCC  :: AFMatchType
afZNCC :: AFMatchType
afZNCC  = AFMatchType CInt
7
afSHD   :: AFMatchType
afSHD :: AFMatchType
afSHD   = AFMatchType CInt
8

{-# LINE 160 "src/ArrayFire/Internal/Defines.hsc" #-}

newtype AFYccStd = AFYccStd Int
  deriving (Ord, Show, Eq, Storable)

afYcc601  :: AFYccStd
afYcc601  = AFYccStd 601
afYcc709  :: AFYccStd
afYcc709  = AFYccStd 709
afYcc2020  :: AFYccStd
afYcc2020 :: AFYccStd
afYcc2020  = Int -> AFYccStd
AFYccStd Int
2020

{-# LINE 169 "src/ArrayFire/Internal/Defines.hsc" #-}

newtype AFCSpace = AFCSpace Int
  deriving (Ord, Show, Eq, Storable)

afGray  :: AFCSpace
afGray :: AFCSpace
afGray  = Int -> AFCSpace
AFCSpace Int
0
afRgb  :: AFCSpace
afRgb :: AFCSpace
afRgb  = Int -> AFCSpace
AFCSpace Int
1
afHsv  :: AFCSpace
afHsv :: AFCSpace
afHsv  = Int -> AFCSpace
AFCSpace Int
2
afYCbCr  :: AFCSpace
afYCbCr :: AFCSpace
afYCbCr  = AFCSpace 3

{-# LINE 179 "src/ArrayFire/Internal/Defines.hsc" #-}

newtype AFMatProp = AFMatProp Int
  deriving (Ord, Show, Eq, Storable)

afMatNone  :: AFMatProp
afMatNone :: AFMatProp
afMatNone  = Int -> AFMatProp
AFMatProp Int
0
afMatTrans  :: AFMatProp
afMatTrans :: AFMatProp
afMatTrans  = Int -> AFMatProp
AFMatProp Int
1
afMatCtrans  :: AFMatProp
afMatCtrans :: AFMatProp
afMatCtrans  = Int -> AFMatProp
AFMatProp Int
2
afMatConj  :: AFMatProp
afMatConj :: AFMatProp
afMatConj  = Int -> AFMatProp
AFMatProp Int
4
afMatUpper  :: AFMatProp
afMatUpper :: AFMatProp
afMatUpper  = Int -> AFMatProp
AFMatProp Int
32
afMatLower  :: AFMatProp
afMatLower :: AFMatProp
afMatLower  = Int -> AFMatProp
AFMatProp Int
64
afMatDiagUnit  :: AFMatProp
afMatDiagUnit :: AFMatProp
afMatDiagUnit  = Int -> AFMatProp
AFMatProp Int
128
afMatSym  :: AFMatProp
afMatSym :: AFMatProp
afMatSym  = AFMatProp 512
afMatPosdef  :: AFMatProp
afMatPosdef :: AFMatProp
afMatPosdef  = Int -> AFMatProp
AFMatProp Int
1024
afMatOrthog  :: AFMatProp
afMatOrthog :: AFMatProp
afMatOrthog  = Int -> AFMatProp
AFMatProp 2048
afMatTriDiag  :: AFMatProp
afMatTriDiag :: AFMatProp
afMatTriDiag  = Int -> AFMatProp
AFMatProp Int
4096
afMatBlockDiag  :: AFMatProp
afMatBlockDiag :: AFMatProp
afMatBlockDiag  = AFMatProp Int
8192

{-# LINE 197 "src/ArrayFire/Internal/Defines.hsc" #-}

newtype AFNormType = AFNormType Int
  deriving (Ord, Show, Eq, Storable)

afNormVector1  :: AFNormType
afNormVector1  = AFNormType 0
afNormVectorInf  :: AFNormType
afNormVectorInf  = AFNormType 1
afNormVector2  :: AFNormType
afNormVector2  = AFNormType 2
afNormVectorP  :: AFNormType
afNormVectorP  = AFNormType 3
afNormMatrix1  :: AFNormType
afNormMatrix1 :: AFNormType
afNormMatrix1  = Int -> AFNormType
AFNormType Int
4
afNormMatrixInf  :: AFNormType
afNormMatrixInf :: AFNormType
afNormMatrixInf  = Int -> AFNormType
AFNormType Int
5
afNormMatrix2  :: AFNormType
afNormMatrix2 :: AFNormType
afNormMatrix2  = Int -> AFNormType
AFNormType Int
6
afNormMatrixLPq  :: AFNormType
afNormMatrixLPq :: AFNormType
afNormMatrixLPq  = Int -> AFNormType
AFNormType Int
7
afNormEuclid  :: AFNormType
afNormEuclid :: AFNormType
afNormEuclid  = AFNormType Int
2

{-# LINE 212 "src/ArrayFire/Internal/Defines.hsc" #-}

newtype AFImageFormat = AFImageFormat Int
  deriving (Ord, Show, Eq, Storable)

afFIFBmp  :: AFImageFormat
afFIFBmp  = AFImageFormat 0
afFIFIco  :: AFImageFormat
afFIFIco  = AFImageFormat 1
afFIFJpeg  :: AFImageFormat
afFIFJpeg :: AFImageFormat
afFIFJpeg  = Int -> AFImageFormat
AFImageFormat Int
2
afFIFJng  :: AFImageFormat
afFIFJng :: AFImageFormat
afFIFJng  = Int -> AFImageFormat
AFImageFormat Int
3
afFIFPng  :: AFImageFormat
afFIFPng :: AFImageFormat
afFIFPng  = Int -> AFImageFormat
AFImageFormat Int
13
afFIFPpm  :: AFImageFormat
afFIFPpm :: AFImageFormat
afFIFPpm  = Int -> AFImageFormat
AFImageFormat Int
14
afFIFPpmraw  :: AFImageFormat
afFIFPpmraw :: AFImageFormat
afFIFPpmraw  = Int -> AFImageFormat
AFImageFormat Int
15
afFIFTiff  :: AFImageFormat
afFIFTiff :: AFImageFormat
afFIFTiff  = Int -> AFImageFormat
AFImageFormat Int
18
afFIFPsd  :: AFImageFormat
afFIFPsd :: AFImageFormat
afFIFPsd  = Int -> AFImageFormat
AFImageFormat Int
20
afFIFHdr  :: AFImageFormat
afFIFHdr :: AFImageFormat
afFIFHdr  = Int -> AFImageFormat
AFImageFormat Int
26
afFIFExr  :: AFImageFormat
afFIFExr :: AFImageFormat
afFIFExr  = Int -> AFImageFormat
AFImageFormat Int
29
afFIFJp2  :: AFImageFormat
afFIFJp2 :: AFImageFormat
afFIFJp2  = Int -> AFImageFormat
AFImageFormat Int
31
afFIFRaw  :: AFImageFormat
afFIFRaw :: AFImageFormat
afFIFRaw  = Int -> AFImageFormat
AFImageFormat Int
34

{-# LINE 231 "src/ArrayFire/Internal/Defines.hsc" #-}

newtype AFMomentType = AFMomentType Int
  deriving (Ord, Show, Eq, Storable)

afMomentM00  :: AFMomentType
afMomentM00  = AFMomentType 1
afMomentM01  :: AFMomentType
afMomentM01  = AFMomentType 2
afMomentM10  :: AFMomentType
afMomentM10  = AFMomentType 4
afMomentM11  :: AFMomentType
afMomentM11  = AFMomentType 8
afMomentFirstOrder  :: AFMomentType
afMomentFirstOrder  = AFMomentType 15

{-# LINE 242 "src/ArrayFire/Internal/Defines.hsc" #-}

newtype AFHomographyType = AFHomographyType CInt
  deriving (Ord, Show, Eq, Storable)

afHomographyRansac  :: AFHomographyType
afHomographyRansac :: AFHomographyType
afHomographyRansac  = CInt -> AFHomographyType
AFHomographyType CInt
0
afHomographyLmeds   :: AFHomographyType
afHomographyLmeds :: AFHomographyType
afHomographyLmeds   = CInt -> AFHomographyType
AFHomographyType CInt
1

{-# LINE 250 "src/ArrayFire/Internal/Defines.hsc" #-}

newtype AFBackend = AFBackend CInt
  deriving (Ord, Show, Eq, Storable)

afBackendDefault  :: AFBackend
afBackendDefault :: AFBackend
afBackendDefault  = CInt -> AFBackend
AFBackend CInt
0
afBackendCpu      :: AFBackend
afBackendCpu :: AFBackend
afBackendCpu      = CInt -> AFBackend
AFBackend CInt
0
afBackendCuda     :: AFBackend
afBackendCuda :: AFBackend
afBackendCuda     = CInt -> AFBackend
AFBackend CInt
2
afBackendOpencl   :: AFBackend
afBackendOpencl :: AFBackend
afBackendOpencl   = AFBackend 4

{-# LINE 260 "src/ArrayFire/Internal/Defines.hsc" #-}

newtype AFID = AFID CInt
  deriving (Ord, Show, Eq, Storable)


{-# LINE 267 "src/ArrayFire/Internal/Defines.hsc" #-}

newtype AFBinaryOp = AFBinaryOp CInt
  deriving (Eq AFBinaryOp
Eq AFBinaryOp
-> (AFBinaryOp -> AFBinaryOp -> Ordering)
-> (AFBinaryOp -> AFBinaryOp -> Bool)
-> (AFBinaryOp -> AFBinaryOp -> Bool)
-> (AFBinaryOp -> AFBinaryOp -> Bool)
-> (AFBinaryOp -> AFBinaryOp -> Bool)
-> (AFBinaryOp -> AFBinaryOp -> AFBinaryOp)
-> (AFBinaryOp -> AFBinaryOp -> AFBinaryOp)
-> Ord AFBinaryOp
AFBinaryOp -> AFBinaryOp -> Bool
AFBinaryOp -> AFBinaryOp -> Ordering
AFBinaryOp -> AFBinaryOp -> AFBinaryOp
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: AFBinaryOp -> AFBinaryOp -> AFBinaryOp
$cmin :: AFBinaryOp -> AFBinaryOp -> AFBinaryOp
max :: AFBinaryOp -> AFBinaryOp -> AFBinaryOp
$cmax :: AFBinaryOp -> AFBinaryOp -> AFBinaryOp
>= :: AFBinaryOp -> AFBinaryOp -> Bool
$c>= :: AFBinaryOp -> AFBinaryOp -> Bool
> :: AFBinaryOp -> AFBinaryOp -> Bool
$c> :: AFBinaryOp -> AFBinaryOp -> Bool
<= :: AFBinaryOp -> AFBinaryOp -> Bool
$c<= :: AFBinaryOp -> AFBinaryOp -> Bool
< :: AFBinaryOp -> AFBinaryOp -> Bool
$c< :: AFBinaryOp -> AFBinaryOp -> Bool
compare :: AFBinaryOp -> AFBinaryOp -> Ordering
$ccompare :: AFBinaryOp -> AFBinaryOp -> Ordering
Ord, Int -> AFBinaryOp -> ShowS
[AFBinaryOp] -> ShowS
AFBinaryOp -> String
(Int -> AFBinaryOp -> ShowS)
-> (AFBinaryOp -> String)
-> ([AFBinaryOp] -> ShowS)
-> Show AFBinaryOp
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AFBinaryOp] -> ShowS
$cshowList :: [AFBinaryOp] -> ShowS
show :: AFBinaryOp -> String
$cshow :: AFBinaryOp -> String
showsPrec :: Int -> AFBinaryOp -> ShowS
$cshowsPrec :: Int -> AFBinaryOp -> ShowS
Show, AFBinaryOp -> AFBinaryOp -> Bool
(AFBinaryOp -> AFBinaryOp -> Bool)
-> (AFBinaryOp -> AFBinaryOp -> Bool) -> Eq AFBinaryOp
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AFBinaryOp -> AFBinaryOp -> Bool
$c/= :: AFBinaryOp -> AFBinaryOp -> Bool
== :: AFBinaryOp -> AFBinaryOp -> Bool
$c== :: AFBinaryOp -> AFBinaryOp -> Bool
Eq, Ptr AFBinaryOp -> IO AFBinaryOp
Ptr AFBinaryOp -> Int -> IO AFBinaryOp
Ptr AFBinaryOp -> Int -> AFBinaryOp -> IO ()
Ptr AFBinaryOp -> AFBinaryOp -> IO ()
AFBinaryOp -> Int
(AFBinaryOp -> Int)
-> (AFBinaryOp -> Int)
-> (Ptr AFBinaryOp -> Int -> IO AFBinaryOp)
-> (Ptr AFBinaryOp -> Int -> AFBinaryOp -> IO ())
-> (forall b. Ptr b -> Int -> IO AFBinaryOp)
-> (forall b. Ptr b -> Int -> AFBinaryOp -> IO ())
-> (Ptr AFBinaryOp -> IO AFBinaryOp)
-> (Ptr AFBinaryOp -> AFBinaryOp -> IO ())
-> Storable AFBinaryOp
forall b. Ptr b -> Int -> IO AFBinaryOp
forall b. Ptr b -> Int -> AFBinaryOp -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
poke :: Ptr AFBinaryOp -> AFBinaryOp -> IO ()
$cpoke :: Ptr AFBinaryOp -> AFBinaryOp -> IO ()
peek :: Ptr AFBinaryOp -> IO AFBinaryOp
$cpeek :: Ptr AFBinaryOp -> IO AFBinaryOp
pokeByteOff :: forall b. Ptr b -> Int -> AFBinaryOp -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> AFBinaryOp -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO AFBinaryOp
$cpeekByteOff :: forall b. Ptr b -> Int -> IO AFBinaryOp
pokeElemOff :: Ptr AFBinaryOp -> Int -> AFBinaryOp -> IO ()
$cpokeElemOff :: Ptr AFBinaryOp -> Int -> AFBinaryOp -> IO ()
peekElemOff :: Ptr AFBinaryOp -> Int -> IO AFBinaryOp
$cpeekElemOff :: Ptr AFBinaryOp -> Int -> IO AFBinaryOp
alignment :: AFBinaryOp -> Int
$calignment :: AFBinaryOp -> Int
sizeOf :: AFBinaryOp -> Int
$csizeOf :: AFBinaryOp -> Int
Storable)

afBinaryAdd   :: AFBinaryOp
afBinaryAdd :: AFBinaryOp
afBinaryAdd   = CInt -> AFBinaryOp
AFBinaryOp CInt
0
afBinaryMul   :: AFBinaryOp
afBinaryMul :: AFBinaryOp
afBinaryMul   = CInt -> AFBinaryOp
AFBinaryOp CInt
1
afBinaryMin   :: AFBinaryOp
afBinaryMin :: AFBinaryOp
afBinaryMin   = CInt -> AFBinaryOp
AFBinaryOp CInt
2
afBinaryMax   :: AFBinaryOp
afBinaryMax :: AFBinaryOp
afBinaryMax   = CInt -> AFBinaryOp
AFBinaryOp CInt
3

{-# LINE 277 "src/ArrayFire/Internal/Defines.hsc" #-}

newtype AFRandomEngineType = AFRandomEngineType CInt
  deriving (Ord, Show, Eq, Storable)

afRandomEnginePhilox4X3210  :: AFRandomEngineType
afRandomEnginePhilox4X3210 :: AFRandomEngineType
afRandomEnginePhilox4X3210  = CInt -> AFRandomEngineType
AFRandomEngineType CInt
100
afRandomEngineThreefry2X3216  :: AFRandomEngineType
afRandomEngineThreefry2X3216 :: AFRandomEngineType
afRandomEngineThreefry2X3216  = CInt -> AFRandomEngineType
AFRandomEngineType CInt
200
afRandomEngineMersenneGp11213  :: AFRandomEngineType
afRandomEngineMersenneGp11213 :: AFRandomEngineType
afRandomEngineMersenneGp11213  = CInt -> AFRandomEngineType
AFRandomEngineType CInt
300
afRandomEnginePhilox   :: AFRandomEngineType
afRandomEnginePhilox :: AFRandomEngineType
afRandomEnginePhilox   = CInt -> AFRandomEngineType
AFRandomEngineType CInt
100
afRandomEngineThreefry  :: AFRandomEngineType
afRandomEngineThreefry :: AFRandomEngineType
afRandomEngineThreefry  = CInt -> AFRandomEngineType
AFRandomEngineType CInt
200
afRandomEngineMersenne  :: AFRandomEngineType
afRandomEngineMersenne  = AFRandomEngineType 300
afRandomEngineDefault  :: AFRandomEngineType
afRandomEngineDefault :: AFRandomEngineType
afRandomEngineDefault  = CInt -> AFRandomEngineType
AFRandomEngineType CInt
100

{-# LINE 290 "src/ArrayFire/Internal/Defines.hsc" #-}

newtype AFColorMap = AFColorMap CInt
  deriving (Ord, Show, Eq, Storable)

afColormapDefault  :: AFColorMap
afColormapDefault  = AFColorMap 0
afColormapSpectrum :: AFColorMap
afColormapSpectrum :: AFColorMap
afColormapSpectrum = CInt -> AFColorMap
AFColorMap CInt
1
afColormapColors   :: AFColorMap
afColormapColors :: AFColorMap
afColormapColors   = CInt -> AFColorMap
AFColorMap CInt
2
afColormapRed      :: AFColorMap
afColormapRed :: AFColorMap
afColormapRed      = CInt -> AFColorMap
AFColorMap CInt
3
afColormapMood     :: AFColorMap
afColormapMood :: AFColorMap
afColormapMood     = CInt -> AFColorMap
AFColorMap CInt
4
afColormapHeat     :: AFColorMap
afColormapHeat :: AFColorMap
afColormapHeat     = CInt -> AFColorMap
AFColorMap CInt
5
afColormapBlue     :: AFColorMap
afColormapBlue :: AFColorMap
afColormapBlue     = CInt -> AFColorMap
AFColorMap CInt
6
afColormapInferno  :: AFColorMap
afColormapInferno :: AFColorMap
afColormapInferno  = CInt -> AFColorMap
AFColorMap CInt
7
afColormapMagma    :: AFColorMap
afColormapMagma :: AFColorMap
afColormapMagma    = CInt -> AFColorMap
AFColorMap CInt
8
afColormapPlasma   :: AFColorMap
afColormapPlasma :: AFColorMap
afColormapPlasma   = CInt -> AFColorMap
AFColorMap CInt
9
afColormapViridis  :: AFColorMap
afColormapViridis :: AFColorMap
afColormapViridis  = AFColorMap CInt
10

{-# LINE 307 "src/ArrayFire/Internal/Defines.hsc" #-}

newtype AFMarkerType = AFMarkerType CInt
  deriving (Ord, Show, Eq, Storable)

afMarkerNone      :: AFMarkerType
afMarkerNone      = AFMarkerType 0
afMarkerPoint     :: AFMarkerType
afMarkerPoint     = AFMarkerType 1
afMarkerCircle    :: AFMarkerType
afMarkerCircle    = AFMarkerType 2
afMarkerSquare    :: AFMarkerType
afMarkerSquare :: AFMarkerType
afMarkerSquare    = CInt -> AFMarkerType
AFMarkerType CInt
3
afMarkerTriangle  :: AFMarkerType
afMarkerTriangle :: AFMarkerType
afMarkerTriangle  = CInt -> AFMarkerType
AFMarkerType CInt
4
afMarkerCross     :: AFMarkerType
afMarkerCross :: AFMarkerType
afMarkerCross     = CInt -> AFMarkerType
AFMarkerType CInt
5
afMarkerPlus      :: AFMarkerType
afMarkerPlus :: AFMarkerType
afMarkerPlus      = CInt -> AFMarkerType
AFMarkerType CInt
6
afMarkerStar      :: AFMarkerType
afMarkerStar :: AFMarkerType
afMarkerStar      = AFMarkerType 7

{-# LINE 321 "src/ArrayFire/Internal/Defines.hsc" #-}

newtype AFCannyThreshold = AFCannyThreshold CInt
  deriving (Ord, Show, Eq, Storable)

afCannyThresholdManual  :: AFCannyThreshold
afCannyThresholdManual  = AFCannyThreshold 0
afCannyThresholdAutoOtsu  :: AFCannyThreshold
afCannyThresholdAutoOtsu  = AFCannyThreshold 1

{-# LINE 329 "src/ArrayFire/Internal/Defines.hsc" #-}

newtype AFStorage = AFStorage CInt
  deriving (Ord, Show, Eq, Storable)

afStorageDense  :: AFStorage
afStorageDense :: AFStorage
afStorageDense  = CInt -> AFStorage
AFStorage CInt
0
afStorageCsr  :: AFStorage
afStorageCsr :: AFStorage
afStorageCsr  = CInt -> AFStorage
AFStorage CInt
1
afStorageCsc  :: AFStorage
afStorageCsc :: AFStorage
afStorageCsc  = CInt -> AFStorage
AFStorage CInt
2
afStorageCoo  :: AFStorage
afStorageCoo :: AFStorage
afStorageCoo  = CInt -> AFStorage
AFStorage CInt
3

{-# LINE 339 "src/ArrayFire/Internal/Defines.hsc" #-}

newtype AFFluxFunction = AFFluxFunction CInt
  deriving (Ord, Show, Eq, Storable)

afFluxQuadratic  :: AFFluxFunction
afFluxQuadratic :: AFFluxFunction
afFluxQuadratic  = CInt -> AFFluxFunction
AFFluxFunction CInt
1
afFluxExponential  :: AFFluxFunction
afFluxExponential :: AFFluxFunction
afFluxExponential  = CInt -> AFFluxFunction
AFFluxFunction CInt
2
afFluxDefault  :: AFFluxFunction
afFluxDefault :: AFFluxFunction
afFluxDefault  = CInt -> AFFluxFunction
AFFluxFunction CInt
0

{-# LINE 348 "src/ArrayFire/Internal/Defines.hsc" #-}

newtype AFDiffusionEq = AFDiffusionEq CInt
  deriving (Ord, Show, Eq, Storable)

afDiffusionGrad  :: AFDiffusionEq
afDiffusionGrad :: AFDiffusionEq
afDiffusionGrad  = CInt -> AFDiffusionEq
AFDiffusionEq CInt
1
afDiffusionMcde  :: AFDiffusionEq
afDiffusionMcde :: AFDiffusionEq
afDiffusionMcde  = CInt -> AFDiffusionEq
AFDiffusionEq CInt
2
afDiffusionDefault  :: AFDiffusionEq
afDiffusionDefault :: AFDiffusionEq
afDiffusionDefault  = CInt -> AFDiffusionEq
AFDiffusionEq CInt
0

{-# LINE 357 "src/ArrayFire/Internal/Defines.hsc" #-}

newtype AFTopkFunction = AFTopkFunction CInt
  deriving (Ord, Show, Eq, Storable)

afTopkMin  :: AFTopkFunction
afTopkMin :: AFTopkFunction
afTopkMin  = CInt -> AFTopkFunction
AFTopkFunction CInt
1
afTopkMax  :: AFTopkFunction
afTopkMax :: AFTopkFunction
afTopkMax  = CInt -> AFTopkFunction
AFTopkFunction CInt
2
afTopkDefault  :: AFTopkFunction
afTopkDefault :: AFTopkFunction
afTopkDefault  = CInt -> AFTopkFunction
AFTopkFunction CInt
0

{-# LINE 366 "src/ArrayFire/Internal/Defines.hsc" #-}

newtype AFIterativeDeconvAlgo = AFIterativeDeconvAlgo CInt
  deriving (Ord, Show, Eq, Storable)

-- #{enum AFIterativeDeconvAlgo, AFIterativeDeconvAlgo
-- , afIterativeDeconvLandweber       = AF_ITERATIVE_DECONV_LANDWEBER
-- , afIterativeDeconvRichardsonlucy  = AF_ITERATIVE_DECONV_RICHARDSONLUCY
-- , afIterativeDeconvDefault         = AF_ITERATIVE_DECONV_DEFAULT
-- }

newtype AFInverseDeconvAlgo = AFInverseDeconvAlgo CInt
  deriving (Eq AFInverseDeconvAlgo
Eq AFInverseDeconvAlgo
-> (AFInverseDeconvAlgo -> AFInverseDeconvAlgo -> Ordering)
-> (AFInverseDeconvAlgo -> AFInverseDeconvAlgo -> Bool)
-> (AFInverseDeconvAlgo -> AFInverseDeconvAlgo -> Bool)
-> (AFInverseDeconvAlgo -> AFInverseDeconvAlgo -> Bool)
-> (AFInverseDeconvAlgo -> AFInverseDeconvAlgo -> Bool)
-> (AFInverseDeconvAlgo
    -> AFInverseDeconvAlgo -> AFInverseDeconvAlgo)
-> (AFInverseDeconvAlgo
    -> AFInverseDeconvAlgo -> AFInverseDeconvAlgo)
-> Ord AFInverseDeconvAlgo
AFInverseDeconvAlgo -> AFInverseDeconvAlgo -> Bool
AFInverseDeconvAlgo -> AFInverseDeconvAlgo -> Ordering
AFInverseDeconvAlgo -> AFInverseDeconvAlgo -> AFInverseDeconvAlgo
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: AFInverseDeconvAlgo -> AFInverseDeconvAlgo -> AFInverseDeconvAlgo
$cmin :: AFInverseDeconvAlgo -> AFInverseDeconvAlgo -> AFInverseDeconvAlgo
max :: AFInverseDeconvAlgo -> AFInverseDeconvAlgo -> AFInverseDeconvAlgo
$cmax :: AFInverseDeconvAlgo -> AFInverseDeconvAlgo -> AFInverseDeconvAlgo
>= :: AFInverseDeconvAlgo -> AFInverseDeconvAlgo -> Bool
$c>= :: AFInverseDeconvAlgo -> AFInverseDeconvAlgo -> Bool
> :: AFInverseDeconvAlgo -> AFInverseDeconvAlgo -> Bool
$c> :: AFInverseDeconvAlgo -> AFInverseDeconvAlgo -> Bool
<= :: AFInverseDeconvAlgo -> AFInverseDeconvAlgo -> Bool
$c<= :: AFInverseDeconvAlgo -> AFInverseDeconvAlgo -> Bool
< :: AFInverseDeconvAlgo -> AFInverseDeconvAlgo -> Bool
$c< :: AFInverseDeconvAlgo -> AFInverseDeconvAlgo -> Bool
compare :: AFInverseDeconvAlgo -> AFInverseDeconvAlgo -> Ordering
$ccompare :: AFInverseDeconvAlgo -> AFInverseDeconvAlgo -> Ordering
Ord, Int -> AFInverseDeconvAlgo -> ShowS
[AFInverseDeconvAlgo] -> ShowS
AFInverseDeconvAlgo -> String
(Int -> AFInverseDeconvAlgo -> ShowS)
-> (AFInverseDeconvAlgo -> String)
-> ([AFInverseDeconvAlgo] -> ShowS)
-> Show AFInverseDeconvAlgo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AFInverseDeconvAlgo] -> ShowS
$cshowList :: [AFInverseDeconvAlgo] -> ShowS
show :: AFInverseDeconvAlgo -> String
$cshow :: AFInverseDeconvAlgo -> String
showsPrec :: Int -> AFInverseDeconvAlgo -> ShowS
$cshowsPrec :: Int -> AFInverseDeconvAlgo -> ShowS
Show, AFInverseDeconvAlgo -> AFInverseDeconvAlgo -> Bool
(AFInverseDeconvAlgo -> AFInverseDeconvAlgo -> Bool)
-> (AFInverseDeconvAlgo -> AFInverseDeconvAlgo -> Bool)
-> Eq AFInverseDeconvAlgo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AFInverseDeconvAlgo -> AFInverseDeconvAlgo -> Bool
$c/= :: AFInverseDeconvAlgo -> AFInverseDeconvAlgo -> Bool
== :: AFInverseDeconvAlgo -> AFInverseDeconvAlgo -> Bool
$c== :: AFInverseDeconvAlgo -> AFInverseDeconvAlgo -> Bool
Eq, Ptr AFInverseDeconvAlgo -> IO AFInverseDeconvAlgo
Ptr AFInverseDeconvAlgo -> Int -> IO AFInverseDeconvAlgo
Ptr AFInverseDeconvAlgo -> Int -> AFInverseDeconvAlgo -> IO ()
Ptr AFInverseDeconvAlgo -> AFInverseDeconvAlgo -> IO ()
AFInverseDeconvAlgo -> Int
(AFInverseDeconvAlgo -> Int)
-> (AFInverseDeconvAlgo -> Int)
-> (Ptr AFInverseDeconvAlgo -> Int -> IO AFInverseDeconvAlgo)
-> (Ptr AFInverseDeconvAlgo -> Int -> AFInverseDeconvAlgo -> IO ())
-> (forall b. Ptr b -> Int -> IO AFInverseDeconvAlgo)
-> (forall b. Ptr b -> Int -> AFInverseDeconvAlgo -> IO ())
-> (Ptr AFInverseDeconvAlgo -> IO AFInverseDeconvAlgo)
-> (Ptr AFInverseDeconvAlgo -> AFInverseDeconvAlgo -> IO ())
-> Storable AFInverseDeconvAlgo
forall b. Ptr b -> Int -> IO AFInverseDeconvAlgo
forall b. Ptr b -> Int -> AFInverseDeconvAlgo -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
poke :: Ptr AFInverseDeconvAlgo -> AFInverseDeconvAlgo -> IO ()
$cpoke :: Ptr AFInverseDeconvAlgo -> AFInverseDeconvAlgo -> IO ()
peek :: Ptr AFInverseDeconvAlgo -> IO AFInverseDeconvAlgo
$cpeek :: Ptr AFInverseDeconvAlgo -> IO AFInverseDeconvAlgo
pokeByteOff :: forall b. Ptr b -> Int -> AFInverseDeconvAlgo -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> AFInverseDeconvAlgo -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO AFInverseDeconvAlgo
$cpeekByteOff :: forall b. Ptr b -> Int -> IO AFInverseDeconvAlgo
pokeElemOff :: Ptr AFInverseDeconvAlgo -> Int -> AFInverseDeconvAlgo -> IO ()
$cpokeElemOff :: Ptr AFInverseDeconvAlgo -> Int -> AFInverseDeconvAlgo -> IO ()
peekElemOff :: Ptr AFInverseDeconvAlgo -> Int -> IO AFInverseDeconvAlgo
$cpeekElemOff :: Ptr AFInverseDeconvAlgo -> Int -> IO AFInverseDeconvAlgo
alignment :: AFInverseDeconvAlgo -> Int
$calignment :: AFInverseDeconvAlgo -> Int
sizeOf :: AFInverseDeconvAlgo -> Int
$csizeOf :: AFInverseDeconvAlgo -> Int
Storable)


{-# LINE 383 "src/ArrayFire/Internal/Defines.hsc" #-}

-- newtype AFVarBias = AFVarBias Int
--   deriving (Ord, Show, Eq)

-- #{enum AFVarBias, AFVarBias
--  , afVarianceDefault = AF_VARIANCE_DEFAULT
--  , afVarianceSample = AF_VARIANCE_SAMPLE
--  , afVariancePopulation = AF_VARIANCE_POPULATION
-- }

newtype DimT = DimT CLLong
  deriving (Int -> DimT -> ShowS
[DimT] -> ShowS
DimT -> String
(Int -> DimT -> ShowS)
-> (DimT -> String) -> ([DimT] -> ShowS) -> Show DimT
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DimT] -> ShowS
$cshowList :: [DimT] -> ShowS
show :: DimT -> String
$cshow :: DimT -> String
showsPrec :: Int -> DimT -> ShowS
$cshowsPrec :: Int -> DimT -> ShowS
Show, DimT -> DimT -> Bool
(DimT -> DimT -> Bool) -> (DimT -> DimT -> Bool) -> Eq DimT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DimT -> DimT -> Bool
$c/= :: DimT -> DimT -> Bool
== :: DimT -> DimT -> Bool
$c== :: DimT -> DimT -> Bool
Eq, Ptr DimT -> IO DimT
Ptr DimT -> Int -> IO DimT
Ptr DimT -> Int -> DimT -> IO ()
Ptr DimT -> DimT -> IO ()
DimT -> Int
(DimT -> Int)
-> (DimT -> Int)
-> (Ptr DimT -> Int -> IO DimT)
-> (Ptr DimT -> Int -> DimT -> IO ())
-> (forall b. Ptr b -> Int -> IO DimT)
-> (forall b. Ptr b -> Int -> DimT -> IO ())
-> (Ptr DimT -> IO DimT)
-> (Ptr DimT -> DimT -> IO ())
-> Storable DimT
forall b. Ptr b -> Int -> IO DimT
forall b. Ptr b -> Int -> DimT -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
poke :: Ptr DimT -> DimT -> IO ()
$cpoke :: Ptr DimT -> DimT -> IO ()
peek :: Ptr DimT -> IO DimT
$cpeek :: Ptr DimT -> IO DimT
pokeByteOff :: forall b. Ptr b -> Int -> DimT -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> DimT -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO DimT
$cpeekByteOff :: forall b. Ptr b -> Int -> IO DimT
pokeElemOff :: Ptr DimT -> Int -> DimT -> IO ()
$cpokeElemOff :: Ptr DimT -> Int -> DimT -> IO ()
peekElemOff :: Ptr DimT -> Int -> IO DimT
$cpeekElemOff :: Ptr DimT -> Int -> IO DimT
alignment :: DimT -> Int
$calignment :: DimT -> Int
sizeOf :: DimT -> Int
$csizeOf :: DimT -> Int
Storable, Integer -> DimT
DimT -> DimT
DimT -> DimT -> DimT
(DimT -> DimT -> DimT)
-> (DimT -> DimT -> DimT)
-> (DimT -> DimT -> DimT)
-> (DimT -> DimT)
-> (DimT -> DimT)
-> (DimT -> DimT)
-> (Integer -> DimT)
-> Num DimT
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> DimT
$cfromInteger :: Integer -> DimT
signum :: DimT -> DimT
$csignum :: DimT -> DimT
abs :: DimT -> DimT
$cabs :: DimT -> DimT
negate :: DimT -> DimT
$cnegate :: DimT -> DimT
* :: DimT -> DimT -> DimT
$c* :: DimT -> DimT -> DimT
- :: DimT -> DimT -> DimT
$c- :: DimT -> DimT -> DimT
+ :: DimT -> DimT -> DimT
$c+ :: DimT -> DimT -> DimT
Num, Enum DimT
Real DimT
Real DimT
-> Enum DimT
-> (DimT -> DimT -> DimT)
-> (DimT -> DimT -> DimT)
-> (DimT -> DimT -> DimT)
-> (DimT -> DimT -> DimT)
-> (DimT -> DimT -> (DimT, DimT))
-> (DimT -> DimT -> (DimT, DimT))
-> (DimT -> Integer)
-> Integral DimT
DimT -> Integer
DimT -> DimT -> (DimT, DimT)
DimT -> DimT -> DimT
forall a.
Real a
-> Enum a
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
toInteger :: DimT -> Integer
$ctoInteger :: DimT -> Integer
divMod :: DimT -> DimT -> (DimT, DimT)
$cdivMod :: DimT -> DimT -> (DimT, DimT)
quotRem :: DimT -> DimT -> (DimT, DimT)
$cquotRem :: DimT -> DimT -> (DimT, DimT)
mod :: DimT -> DimT -> DimT
$cmod :: DimT -> DimT -> DimT
div :: DimT -> DimT -> DimT
$cdiv :: DimT -> DimT -> DimT
rem :: DimT -> DimT -> DimT
$crem :: DimT -> DimT -> DimT
quot :: DimT -> DimT -> DimT
$cquot :: DimT -> DimT -> DimT
Integral, Num DimT
Ord DimT
Num DimT -> Ord DimT -> (DimT -> Rational) -> Real DimT
DimT -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: DimT -> Rational
$ctoRational :: DimT -> Rational
Real, Int -> DimT
DimT -> Int
DimT -> [DimT]
DimT -> DimT
DimT -> DimT -> [DimT]
DimT -> DimT -> DimT -> [DimT]
(DimT -> DimT)
-> (DimT -> DimT)
-> (Int -> DimT)
-> (DimT -> Int)
-> (DimT -> [DimT])
-> (DimT -> DimT -> [DimT])
-> (DimT -> DimT -> [DimT])
-> (DimT -> DimT -> DimT -> [DimT])
-> Enum DimT
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: DimT -> DimT -> DimT -> [DimT]
$cenumFromThenTo :: DimT -> DimT -> DimT -> [DimT]
enumFromTo :: DimT -> DimT -> [DimT]
$cenumFromTo :: DimT -> DimT -> [DimT]
enumFromThen :: DimT -> DimT -> [DimT]
$cenumFromThen :: DimT -> DimT -> [DimT]
enumFrom :: DimT -> [DimT]
$cenumFrom :: DimT -> [DimT]
fromEnum :: DimT -> Int
$cfromEnum :: DimT -> Int
toEnum :: Int -> DimT
$ctoEnum :: Int -> DimT
pred :: DimT -> DimT
$cpred :: DimT -> DimT
succ :: DimT -> DimT
$csucc :: DimT -> DimT
Enum, Eq DimT
Eq DimT
-> (DimT -> DimT -> Ordering)
-> (DimT -> DimT -> Bool)
-> (DimT -> DimT -> Bool)
-> (DimT -> DimT -> Bool)
-> (DimT -> DimT -> Bool)
-> (DimT -> DimT -> DimT)
-> (DimT -> DimT -> DimT)
-> Ord DimT
DimT -> DimT -> Bool
DimT -> DimT -> Ordering
DimT -> DimT -> DimT
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: DimT -> DimT -> DimT
$cmin :: DimT -> DimT -> DimT
max :: DimT -> DimT -> DimT
$cmax :: DimT -> DimT -> DimT
>= :: DimT -> DimT -> Bool
$c>= :: DimT -> DimT -> Bool
> :: DimT -> DimT -> Bool
$c> :: DimT -> DimT -> Bool
<= :: DimT -> DimT -> Bool
$c<= :: DimT -> DimT -> Bool
< :: DimT -> DimT -> Bool
$c< :: DimT -> DimT -> Bool
compare :: DimT -> DimT -> Ordering
$ccompare :: DimT -> DimT -> Ordering
Ord)

newtype UIntL = UIntL CULLong
  deriving (Int -> UIntL -> ShowS
[UIntL] -> ShowS
UIntL -> String
(Int -> UIntL -> ShowS)
-> (UIntL -> String) -> ([UIntL] -> ShowS) -> Show UIntL
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UIntL] -> ShowS
$cshowList :: [UIntL] -> ShowS
show :: UIntL -> String
$cshow :: UIntL -> String
showsPrec :: Int -> UIntL -> ShowS
$cshowsPrec :: Int -> UIntL -> ShowS
Show, UIntL -> UIntL -> Bool
(UIntL -> UIntL -> Bool) -> (UIntL -> UIntL -> Bool) -> Eq UIntL
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UIntL -> UIntL -> Bool
$c/= :: UIntL -> UIntL -> Bool
== :: UIntL -> UIntL -> Bool
$c== :: UIntL -> UIntL -> Bool
Eq, Ptr UIntL -> IO UIntL
Ptr UIntL -> Int -> IO UIntL
Ptr UIntL -> Int -> UIntL -> IO ()
Ptr UIntL -> UIntL -> IO ()
UIntL -> Int
(UIntL -> Int)
-> (UIntL -> Int)
-> (Ptr UIntL -> Int -> IO UIntL)
-> (Ptr UIntL -> Int -> UIntL -> IO ())
-> (forall b. Ptr b -> Int -> IO UIntL)
-> (forall b. Ptr b -> Int -> UIntL -> IO ())
-> (Ptr UIntL -> IO UIntL)
-> (Ptr UIntL -> UIntL -> IO ())
-> Storable UIntL
forall b. Ptr b -> Int -> IO UIntL
forall b. Ptr b -> Int -> UIntL -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
poke :: Ptr UIntL -> UIntL -> IO ()
$cpoke :: Ptr UIntL -> UIntL -> IO ()
peek :: Ptr UIntL -> IO UIntL
$cpeek :: Ptr UIntL -> IO UIntL
pokeByteOff :: forall b. Ptr b -> Int -> UIntL -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> UIntL -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO UIntL
$cpeekByteOff :: forall b. Ptr b -> Int -> IO UIntL
pokeElemOff :: Ptr UIntL -> Int -> UIntL -> IO ()
$cpokeElemOff :: Ptr UIntL -> Int -> UIntL -> IO ()
peekElemOff :: Ptr UIntL -> Int -> IO UIntL
$cpeekElemOff :: Ptr UIntL -> Int -> IO UIntL
alignment :: UIntL -> Int
$calignment :: UIntL -> Int
sizeOf :: UIntL -> Int
$csizeOf :: UIntL -> Int
Storable, Integer -> UIntL
UIntL -> UIntL
UIntL -> UIntL -> UIntL
(UIntL -> UIntL -> UIntL)
-> (UIntL -> UIntL -> UIntL)
-> (UIntL -> UIntL -> UIntL)
-> (UIntL -> UIntL)
-> (UIntL -> UIntL)
-> (UIntL -> UIntL)
-> (Integer -> UIntL)
-> Num UIntL
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> UIntL
$cfromInteger :: Integer -> UIntL
signum :: UIntL -> UIntL
$csignum :: UIntL -> UIntL
abs :: UIntL -> UIntL
$cabs :: UIntL -> UIntL
negate :: UIntL -> UIntL
$cnegate :: UIntL -> UIntL
* :: UIntL -> UIntL -> UIntL
$c* :: UIntL -> UIntL -> UIntL
- :: UIntL -> UIntL -> UIntL
$c- :: UIntL -> UIntL -> UIntL
+ :: UIntL -> UIntL -> UIntL
$c+ :: UIntL -> UIntL -> UIntL
Num, Enum UIntL
Real UIntL
Real UIntL
-> Enum UIntL
-> (UIntL -> UIntL -> UIntL)
-> (UIntL -> UIntL -> UIntL)
-> (UIntL -> UIntL -> UIntL)
-> (UIntL -> UIntL -> UIntL)
-> (UIntL -> UIntL -> (UIntL, UIntL))
-> (UIntL -> UIntL -> (UIntL, UIntL))
-> (UIntL -> Integer)
-> Integral UIntL
UIntL -> Integer
UIntL -> UIntL -> (UIntL, UIntL)
UIntL -> UIntL -> UIntL
forall a.
Real a
-> Enum a
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
toInteger :: UIntL -> Integer
$ctoInteger :: UIntL -> Integer
divMod :: UIntL -> UIntL -> (UIntL, UIntL)
$cdivMod :: UIntL -> UIntL -> (UIntL, UIntL)
quotRem :: UIntL -> UIntL -> (UIntL, UIntL)
$cquotRem :: UIntL -> UIntL -> (UIntL, UIntL)
mod :: UIntL -> UIntL -> UIntL
$cmod :: UIntL -> UIntL -> UIntL
div :: UIntL -> UIntL -> UIntL
$cdiv :: UIntL -> UIntL -> UIntL
rem :: UIntL -> UIntL -> UIntL
$crem :: UIntL -> UIntL -> UIntL
quot :: UIntL -> UIntL -> UIntL
$cquot :: UIntL -> UIntL -> UIntL
Integral, Num UIntL
Ord UIntL
Num UIntL -> Ord UIntL -> (UIntL -> Rational) -> Real UIntL
UIntL -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: UIntL -> Rational
$ctoRational :: UIntL -> Rational
Real, Int -> UIntL
UIntL -> Int
UIntL -> [UIntL]
UIntL -> UIntL
UIntL -> UIntL -> [UIntL]
UIntL -> UIntL -> UIntL -> [UIntL]
(UIntL -> UIntL)
-> (UIntL -> UIntL)
-> (Int -> UIntL)
-> (UIntL -> Int)
-> (UIntL -> [UIntL])
-> (UIntL -> UIntL -> [UIntL])
-> (UIntL -> UIntL -> [UIntL])
-> (UIntL -> UIntL -> UIntL -> [UIntL])
-> Enum UIntL
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: UIntL -> UIntL -> UIntL -> [UIntL]
$cenumFromThenTo :: UIntL -> UIntL -> UIntL -> [UIntL]
enumFromTo :: UIntL -> UIntL -> [UIntL]
$cenumFromTo :: UIntL -> UIntL -> [UIntL]
enumFromThen :: UIntL -> UIntL -> [UIntL]
$cenumFromThen :: UIntL -> UIntL -> [UIntL]
enumFrom :: UIntL -> [UIntL]
$cenumFrom :: UIntL -> [UIntL]
fromEnum :: UIntL -> Int
$cfromEnum :: UIntL -> Int
toEnum :: Int -> UIntL
$ctoEnum :: Int -> UIntL
pred :: UIntL -> UIntL
$cpred :: UIntL -> UIntL
succ :: UIntL -> UIntL
$csucc :: UIntL -> UIntL
Enum, Eq UIntL
Eq UIntL
-> (UIntL -> UIntL -> Ordering)
-> (UIntL -> UIntL -> Bool)
-> (UIntL -> UIntL -> Bool)
-> (UIntL -> UIntL -> Bool)
-> (UIntL -> UIntL -> Bool)
-> (UIntL -> UIntL -> UIntL)
-> (UIntL -> UIntL -> UIntL)
-> Ord UIntL
UIntL -> UIntL -> Bool
UIntL -> UIntL -> Ordering
UIntL -> UIntL -> UIntL
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: UIntL -> UIntL -> UIntL
$cmin :: UIntL -> UIntL -> UIntL
max :: UIntL -> UIntL -> UIntL
$cmax :: UIntL -> UIntL -> UIntL
>= :: UIntL -> UIntL -> Bool
$c>= :: UIntL -> UIntL -> Bool
> :: UIntL -> UIntL -> Bool
$c> :: UIntL -> UIntL -> Bool
<= :: UIntL -> UIntL -> Bool
$c<= :: UIntL -> UIntL -> Bool
< :: UIntL -> UIntL -> Bool
$c< :: UIntL -> UIntL -> Bool
compare :: UIntL -> UIntL -> Ordering
$ccompare :: UIntL -> UIntL -> Ordering
Ord)

newtype IntL = IntL CLLong
  deriving (Int -> IntL -> ShowS
[IntL] -> ShowS
IntL -> String
(Int -> IntL -> ShowS)
-> (IntL -> String) -> ([IntL] -> ShowS) -> Show IntL
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [IntL] -> ShowS
$cshowList :: [IntL] -> ShowS
show :: IntL -> String
$cshow :: IntL -> String
showsPrec :: Int -> IntL -> ShowS
$cshowsPrec :: Int -> IntL -> ShowS
Show, IntL -> IntL -> Bool
(IntL -> IntL -> Bool) -> (IntL -> IntL -> Bool) -> Eq IntL
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IntL -> IntL -> Bool
$c/= :: IntL -> IntL -> Bool
== :: IntL -> IntL -> Bool
$c== :: IntL -> IntL -> Bool
Eq, Ptr IntL -> IO IntL
Ptr IntL -> Int -> IO IntL
Ptr IntL -> Int -> IntL -> IO ()
Ptr IntL -> IntL -> IO ()
IntL -> Int
(IntL -> Int)
-> (IntL -> Int)
-> (Ptr IntL -> Int -> IO IntL)
-> (Ptr IntL -> Int -> IntL -> IO ())
-> (forall b. Ptr b -> Int -> IO IntL)
-> (forall b. Ptr b -> Int -> IntL -> IO ())
-> (Ptr IntL -> IO IntL)
-> (Ptr IntL -> IntL -> IO ())
-> Storable IntL
forall b. Ptr b -> Int -> IO IntL
forall b. Ptr b -> Int -> IntL -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
poke :: Ptr IntL -> IntL -> IO ()
$cpoke :: Ptr IntL -> IntL -> IO ()
peek :: Ptr IntL -> IO IntL
$cpeek :: Ptr IntL -> IO IntL
pokeByteOff :: forall b. Ptr b -> Int -> IntL -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> IntL -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO IntL
$cpeekByteOff :: forall b. Ptr b -> Int -> IO IntL
pokeElemOff :: Ptr IntL -> Int -> IntL -> IO ()
$cpokeElemOff :: Ptr IntL -> Int -> IntL -> IO ()
peekElemOff :: Ptr IntL -> Int -> IO IntL
$cpeekElemOff :: Ptr IntL -> Int -> IO IntL
alignment :: IntL -> Int
$calignment :: IntL -> Int
sizeOf :: IntL -> Int
$csizeOf :: IntL -> Int
Storable, Integer -> IntL
IntL -> IntL
IntL -> IntL -> IntL
(IntL -> IntL -> IntL)
-> (IntL -> IntL -> IntL)
-> (IntL -> IntL -> IntL)
-> (IntL -> IntL)
-> (IntL -> IntL)
-> (IntL -> IntL)
-> (Integer -> IntL)
-> Num IntL
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> IntL
$cfromInteger :: Integer -> IntL
signum :: IntL -> IntL
$csignum :: IntL -> IntL
abs :: IntL -> IntL
$cabs :: IntL -> IntL
negate :: IntL -> IntL
$cnegate :: IntL -> IntL
* :: IntL -> IntL -> IntL
$c* :: IntL -> IntL -> IntL
- :: IntL -> IntL -> IntL
$c- :: IntL -> IntL -> IntL
+ :: IntL -> IntL -> IntL
$c+ :: IntL -> IntL -> IntL
Num, Enum IntL
Real IntL
Real IntL
-> Enum IntL
-> (IntL -> IntL -> IntL)
-> (IntL -> IntL -> IntL)
-> (IntL -> IntL -> IntL)
-> (IntL -> IntL -> IntL)
-> (IntL -> IntL -> (IntL, IntL))
-> (IntL -> IntL -> (IntL, IntL))
-> (IntL -> Integer)
-> Integral IntL
IntL -> Integer
IntL -> IntL -> (IntL, IntL)
IntL -> IntL -> IntL
forall a.
Real a
-> Enum a
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
toInteger :: IntL -> Integer
$ctoInteger :: IntL -> Integer
divMod :: IntL -> IntL -> (IntL, IntL)
$cdivMod :: IntL -> IntL -> (IntL, IntL)
quotRem :: IntL -> IntL -> (IntL, IntL)
$cquotRem :: IntL -> IntL -> (IntL, IntL)
mod :: IntL -> IntL -> IntL
$cmod :: IntL -> IntL -> IntL
div :: IntL -> IntL -> IntL
$cdiv :: IntL -> IntL -> IntL
rem :: IntL -> IntL -> IntL
$crem :: IntL -> IntL -> IntL
quot :: IntL -> IntL -> IntL
$cquot :: IntL -> IntL -> IntL
Integral, Num IntL
Ord IntL
Num IntL -> Ord IntL -> (IntL -> Rational) -> Real IntL
IntL -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: IntL -> Rational
$ctoRational :: IntL -> Rational
Real, Int -> IntL
IntL -> Int
IntL -> [IntL]
IntL -> IntL
IntL -> IntL -> [IntL]
IntL -> IntL -> IntL -> [IntL]
(IntL -> IntL)
-> (IntL -> IntL)
-> (Int -> IntL)
-> (IntL -> Int)
-> (IntL -> [IntL])
-> (IntL -> IntL -> [IntL])
-> (IntL -> IntL -> [IntL])
-> (IntL -> IntL -> IntL -> [IntL])
-> Enum IntL
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: IntL -> IntL -> IntL -> [IntL]
$cenumFromThenTo :: IntL -> IntL -> IntL -> [IntL]
enumFromTo :: IntL -> IntL -> [IntL]
$cenumFromTo :: IntL -> IntL -> [IntL]
enumFromThen :: IntL -> IntL -> [IntL]
$cenumFromThen :: IntL -> IntL -> [IntL]
enumFrom :: IntL -> [IntL]
$cenumFrom :: IntL -> [IntL]
fromEnum :: IntL -> Int
$cfromEnum :: IntL -> Int
toEnum :: Int -> IntL
$ctoEnum :: Int -> IntL
pred :: IntL -> IntL
$cpred :: IntL -> IntL
succ :: IntL -> IntL
$csucc :: IntL -> IntL
Enum, Eq IntL
Eq IntL
-> (IntL -> IntL -> Ordering)
-> (IntL -> IntL -> Bool)
-> (IntL -> IntL -> Bool)
-> (IntL -> IntL -> Bool)
-> (IntL -> IntL -> Bool)
-> (IntL -> IntL -> IntL)
-> (IntL -> IntL -> IntL)
-> Ord IntL
IntL -> IntL -> Bool
IntL -> IntL -> Ordering
IntL -> IntL -> IntL
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: IntL -> IntL -> IntL
$cmin :: IntL -> IntL -> IntL
max :: IntL -> IntL -> IntL
$cmax :: IntL -> IntL -> IntL
>= :: IntL -> IntL -> Bool
$c>= :: IntL -> IntL -> Bool
> :: IntL -> IntL -> Bool
$c> :: IntL -> IntL -> Bool
<= :: IntL -> IntL -> Bool
$c<= :: IntL -> IntL -> Bool
< :: IntL -> IntL -> Bool
$c< :: IntL -> IntL -> Bool
compare :: IntL -> IntL -> Ordering
$ccompare :: IntL -> IntL -> Ordering
Ord)

-- static const af_seq af_span = {1, 1, 0};

-- newtype AFCLPlatform = AFCLPlatform Int
--   deriving (Show, Eq)

-- #{enum AFCLPlatform, AFCLPlatform
--  , afclPlatformAMD = AFCL_PLATFORM_AMD
--  , afclPlatformApple = AFCL_PLATFORM_APPLE
--  , afclPlatformIntel = AFCL_PLATFORM_INTEL
--  , afclPlatformNVIDIA = AFCL_PLATFORM_NVIDIA
--  , afclPlatformBEIGNET = AFCL_PLATFORM_BEIGNET
--  , afclPlatformPOCL = AFCL_PLATFORM_POCL
--  , afclPlatformUnknown = AFCL_PLATFORM_UNKNOWN
-- }

-- newtype DeviceType = DeviceType Int
--   deriving (Show, Eq)

-- #{enum DeviceType, DeviceType
--  , afCLDeviceTypeCPU = AFCL_DEVICE_TYPE_CPU
--  , afCLDeviceTypeGPU = AFCL_DEVICE_TYPE_GPU
--  , afCLDeviceTypeAccel = AFCL_DEVICE_TYPE_ACCEL
--  , afCLDeviceTypeUnknown = AFCL_DEVICE_TYPE_UNKNOWN
-- }