{-# 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
{ AFSeq -> Double
afSeqBegin :: {-# UNPACK #-} !Double
, AFSeq -> Double
afSeqEnd :: {-# UNPACK #-} !Double
, AFSeq -> Double
afSeqStep :: {-# UNPACK #-} !Double
} deriving (Int -> AFSeq -> ShowS
[AFSeq] -> ShowS
AFSeq -> String
(Int -> AFSeq -> ShowS)
-> (AFSeq -> String) -> ([AFSeq] -> ShowS) -> Show AFSeq
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AFSeq] -> ShowS
$cshowList :: [AFSeq] -> ShowS
show :: AFSeq -> String
$cshow :: AFSeq -> String
showsPrec :: Int -> AFSeq -> ShowS
$cshowsPrec :: Int -> AFSeq -> ShowS
Show, AFSeq -> AFSeq -> Bool
(AFSeq -> AFSeq -> Bool) -> (AFSeq -> AFSeq -> Bool) -> Eq AFSeq
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AFSeq -> AFSeq -> Bool
$c/= :: AFSeq -> AFSeq -> Bool
== :: AFSeq -> AFSeq -> Bool
$c== :: AFSeq -> AFSeq -> Bool
Eq)
instance Storable AFSeq where
sizeOf :: AFSeq -> Int
sizeOf AFSeq
_ = (Int
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 -> AFSeq -> IO ()
poke Ptr AFSeq
ptr AFSeq{Double
afSeqStep :: Double
afSeqEnd :: Double
afSeqBegin :: Double
afSeqStep :: AFSeq -> Double
afSeqEnd :: AFSeq -> Double
afSeqBegin :: AFSeq -> Double
..} = do
(\Ptr AFSeq
hsc_ptr -> Ptr AFSeq -> Int -> Double -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr AFSeq
hsc_ptr Int
0) Ptr AFSeq
ptr Double
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
{ AFIndex -> Either AFArray AFSeq
afIdx :: !(Either AFArray AFSeq)
, AFIndex -> Bool
afIsSeq :: !Bool
, AFIndex -> Bool
afIsBatch :: !Bool
}
instance Storable AFIndex where
sizeOf :: AFIndex -> Int
sizeOf AFIndex
_ = (Int
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 -> AFIndex -> IO ()
poke Ptr AFIndex
ptr AFIndex{Bool
Either AFArray AFSeq
afIsBatch :: Bool
afIsSeq :: Bool
afIdx :: Either AFArray AFSeq
afIsBatch :: AFIndex -> Bool
afIsSeq :: AFIndex -> Bool
afIdx :: AFIndex -> Either AFArray AFSeq
..} = do
case Either AFArray AFSeq
afIdx of
Left AFArray
afarr -> (\Ptr AFIndex
hsc_ptr -> Ptr AFIndex -> Int -> AFArray -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr AFIndex
hsc_ptr Int
0) Ptr AFIndex
ptr AFArray
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
{ AFCFloat -> Float
afcReal :: {-# UNPACK #-} !Float
, AFCFloat -> Float
afcImag :: {-# UNPACK #-} !Float
} deriving (AFCFloat -> AFCFloat -> Bool
(AFCFloat -> AFCFloat -> Bool)
-> (AFCFloat -> AFCFloat -> Bool) -> Eq AFCFloat
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AFCFloat -> AFCFloat -> Bool
$c/= :: AFCFloat -> AFCFloat -> Bool
== :: AFCFloat -> AFCFloat -> Bool
$c== :: AFCFloat -> AFCFloat -> Bool
Eq, Int -> AFCFloat -> ShowS
[AFCFloat] -> ShowS
AFCFloat -> String
(Int -> AFCFloat -> ShowS)
-> (AFCFloat -> String) -> ([AFCFloat] -> ShowS) -> Show AFCFloat
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AFCFloat] -> ShowS
$cshowList :: [AFCFloat] -> ShowS
show :: AFCFloat -> String
$cshow :: AFCFloat -> String
showsPrec :: Int -> AFCFloat -> ShowS
$cshowsPrec :: Int -> AFCFloat -> ShowS
Show)
instance Storable AFCFloat where
sizeOf :: AFCFloat -> Int
sizeOf AFCFloat
_ = (Int
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 -> AFCFloat -> IO ()
poke Ptr AFCFloat
ptr AFCFloat{Float
afcImag :: Float
afcReal :: Float
afcImag :: AFCFloat -> Float
afcReal :: AFCFloat -> Float
..} = do
(\Ptr AFCFloat
hsc_ptr -> Ptr AFCFloat -> Int -> Float -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr AFCFloat
hsc_ptr Int
0) Ptr AFCFloat
ptr Float
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
{ AFCell -> Int
afCellRow :: {-# UNPACK #-} !Int
, AFCell -> Int
afCellCol :: {-# UNPACK #-} !Int
, AFCell -> CString
afCellTitle :: {-# UNPACK #-} !CString
, AFCell -> AFColorMap
afCellColorMap :: {-# UNPACK #-} !AFColorMap
} deriving (Int -> AFCell -> ShowS
[AFCell] -> ShowS
AFCell -> String
(Int -> AFCell -> ShowS)
-> (AFCell -> String) -> ([AFCell] -> ShowS) -> Show AFCell
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AFCell] -> ShowS
$cshowList :: [AFCell] -> ShowS
show :: AFCell -> String
$cshow :: AFCell -> String
showsPrec :: Int -> AFCell -> ShowS
$cshowsPrec :: Int -> AFCell -> ShowS
Show, AFCell -> AFCell -> Bool
(AFCell -> AFCell -> Bool)
-> (AFCell -> AFCell -> Bool) -> Eq AFCell
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AFCell -> AFCell -> Bool
$c/= :: AFCell -> AFCell -> Bool
== :: AFCell -> AFCell -> Bool
$c== :: AFCell -> AFCell -> Bool
Eq)
instance Storable AFCell where
sizeOf :: AFCell -> Int
sizeOf AFCell
_ = (Int
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 -> AFCell -> IO ()
poke Ptr AFCell
ptr AFCell{Int
CString
AFColorMap
afCellColorMap :: AFColorMap
afCellTitle :: CString
afCellCol :: Int
afCellRow :: Int
afCellColorMap :: AFCell -> AFColorMap
afCellTitle :: AFCell -> CString
afCellCol :: AFCell -> Int
afCellRow :: AFCell -> Int
..} = do
(\Ptr AFCell
hsc_ptr -> Ptr AFCell -> Int -> Int -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr AFCell
hsc_ptr Int
0) Ptr AFCell
ptr Int
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 Double -> AFDtype
afType Proxy Double
Proxy = AFDtype
f64
instance AFType Float where
afType :: Proxy Float -> AFDtype
afType Proxy Float
Proxy = AFDtype
f32
instance AFType (Complex Double) where
afType :: Proxy (Complex Double) -> AFDtype
afType Proxy (Complex Double)
Proxy = AFDtype
c64
instance AFType (Complex Float) where
afType :: Proxy (Complex Float) -> AFDtype
afType Proxy (Complex Float)
Proxy = AFDtype
c32
instance AFType CBool where
afType :: Proxy CBool -> AFDtype
afType Proxy CBool
Proxy = AFDtype
b8
instance AFType Int32 where
afType :: Proxy Int32 -> AFDtype
afType Proxy Int32
Proxy = AFDtype
s32
instance AFType Word32 where
afType :: Proxy Word32 -> AFDtype
afType Proxy Word32
Proxy = AFDtype
u32
instance AFType Word8 where
afType :: Proxy Word8 -> AFDtype
afType Proxy Word8
Proxy = AFDtype
u8
instance AFType Int64 where
afType :: Proxy Int64 -> AFDtype
afType Proxy Int64
Proxy = AFDtype
s64
instance AFType Int where
afType :: Proxy Int -> AFDtype
afType Proxy Int
Proxy = AFDtype
s64
instance AFType Int16 where
afType :: Proxy Int16 -> AFDtype
afType Proxy Int16
Proxy = AFDtype
s16
instance AFType Word16 where
afType :: Proxy Word16 -> AFDtype
afType Proxy Word16
Proxy = AFDtype
u16
instance AFType Word64 where
afType :: Proxy Word64 -> AFDtype
afType Proxy Word64
Proxy = AFDtype
u64
instance AFType Word where
afType :: Proxy Word -> AFDtype
afType Proxy Word
Proxy = AFDtype
u64
data Backend
= Default
| CPU
| CUDA
| OpenCL
deriving (Int -> Backend -> ShowS
[Backend] -> ShowS
Backend -> String
(Int -> Backend -> ShowS)
-> (Backend -> String) -> ([Backend] -> ShowS) -> Show Backend
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Backend] -> ShowS
$cshowList :: [Backend] -> ShowS
show :: Backend -> String
$cshow :: Backend -> String
showsPrec :: Int -> Backend -> ShowS
$cshowsPrec :: Int -> Backend -> ShowS
Show, Backend -> Backend -> Bool
(Backend -> Backend -> Bool)
-> (Backend -> Backend -> Bool) -> Eq Backend
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Backend -> Backend -> Bool
$c/= :: Backend -> Backend -> Bool
== :: Backend -> Backend -> Bool
$c== :: Backend -> Backend -> Bool
Eq, Eq Backend
Eq Backend
-> (Backend -> Backend -> Ordering)
-> (Backend -> Backend -> Bool)
-> (Backend -> Backend -> Bool)
-> (Backend -> Backend -> Bool)
-> (Backend -> Backend -> Bool)
-> (Backend -> Backend -> Backend)
-> (Backend -> Backend -> Backend)
-> Ord Backend
Backend -> Backend -> Bool
Backend -> Backend -> Ordering
Backend -> Backend -> Backend
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 :: Backend -> Backend -> Backend
$cmin :: Backend -> Backend -> Backend
max :: Backend -> Backend -> Backend
$cmax :: Backend -> Backend -> Backend
>= :: Backend -> Backend -> Bool
$c>= :: Backend -> Backend -> Bool
> :: Backend -> Backend -> Bool
$c> :: Backend -> Backend -> Bool
<= :: Backend -> Backend -> Bool
$c<= :: Backend -> Backend -> Bool
< :: Backend -> Backend -> Bool
$c< :: Backend -> Backend -> Bool
compare :: Backend -> Backend -> Ordering
$ccompare :: Backend -> Backend -> Ordering
Ord)
toBackend :: AFBackend -> Backend
toBackend :: AFBackend -> Backend
toBackend (AFBackend CInt
0) = Backend
Default
toBackend (AFBackend CInt
1) = Backend
CPU
toBackend (AFBackend CInt
2) = Backend
CUDA
toBackend (AFBackend CInt
4) = Backend
OpenCL
toBackend (AFBackend CInt
x) = String -> Backend
forall a. HasCallStack => String -> a
error (String -> Backend) -> String -> Backend
forall a b. (a -> b) -> a -> b
$ String
"Invalid backend: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> CInt -> String
forall a. Show a => a -> String
show CInt
x
toAFBackend :: Backend -> AFBackend
toAFBackend :: Backend -> AFBackend
toAFBackend Backend
Default = (CInt -> AFBackend
AFBackend CInt
0)
toAFBackend Backend
CPU = (CInt -> AFBackend
AFBackend CInt
1)
toAFBackend Backend
CUDA = (CInt -> AFBackend
AFBackend CInt
2)
toAFBackend Backend
OpenCL = (CInt -> AFBackend
AFBackend CInt
4)
toBackends :: Int -> [Backend]
toBackends :: Int -> [Backend]
toBackends Int
1 = [Backend
CPU]
toBackends Int
2 = [Backend
CUDA]
toBackends Int
3 = [Backend
CPU,Backend
CUDA]
toBackends Int
4 = [Backend
OpenCL]
toBackends Int
5 = [Backend
CPU,Backend
OpenCL]
toBackends Int
6 = [Backend
CUDA,Backend
OpenCL]
toBackends Int
7 = [Backend
CPU,Backend
CUDA,Backend
OpenCL]
toBackends Int
_ = []
data MatProp
= None
| Trans
| CTrans
| Conj
| Upper
| Lower
| DiagUnit
| Sym
| PosDef
| Orthog
| TriDiag
| BlockDiag
deriving (Int -> MatProp -> ShowS
[MatProp] -> ShowS
MatProp -> String
(Int -> MatProp -> ShowS)
-> (MatProp -> String) -> ([MatProp] -> ShowS) -> Show MatProp
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MatProp] -> ShowS
$cshowList :: [MatProp] -> ShowS
show :: MatProp -> String
$cshow :: MatProp -> String
showsPrec :: Int -> MatProp -> ShowS
$cshowsPrec :: Int -> MatProp -> ShowS
Show, MatProp -> MatProp -> Bool
(MatProp -> MatProp -> Bool)
-> (MatProp -> MatProp -> Bool) -> Eq MatProp
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MatProp -> MatProp -> Bool
$c/= :: MatProp -> MatProp -> Bool
== :: MatProp -> MatProp -> Bool
$c== :: MatProp -> MatProp -> Bool
Eq, Eq MatProp
Eq MatProp
-> (MatProp -> MatProp -> Ordering)
-> (MatProp -> MatProp -> Bool)
-> (MatProp -> MatProp -> Bool)
-> (MatProp -> MatProp -> Bool)
-> (MatProp -> MatProp -> Bool)
-> (MatProp -> MatProp -> MatProp)
-> (MatProp -> MatProp -> MatProp)
-> Ord MatProp
MatProp -> MatProp -> Bool
MatProp -> MatProp -> Ordering
MatProp -> MatProp -> MatProp
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 :: MatProp -> MatProp -> MatProp
$cmin :: MatProp -> MatProp -> MatProp
max :: MatProp -> MatProp -> MatProp
$cmax :: MatProp -> MatProp -> MatProp
>= :: MatProp -> MatProp -> Bool
$c>= :: MatProp -> MatProp -> Bool
> :: MatProp -> MatProp -> Bool
$c> :: MatProp -> MatProp -> Bool
<= :: MatProp -> MatProp -> Bool
$c<= :: MatProp -> MatProp -> Bool
< :: MatProp -> MatProp -> Bool
$c< :: MatProp -> MatProp -> Bool
compare :: MatProp -> MatProp -> Ordering
$ccompare :: MatProp -> MatProp -> Ordering
Ord)
fromMatProp
:: AFMatProp
-> MatProp
fromMatProp :: AFMatProp -> MatProp
fromMatProp (AFMatProp Int
0) = MatProp
None
fromMatProp (AFMatProp Int
1) = MatProp
Trans
fromMatProp (AFMatProp Int
2) = MatProp
CTrans
fromMatProp (AFMatProp Int
4) = MatProp
Conj
fromMatProp (AFMatProp Int
32) = MatProp
Upper
fromMatProp (AFMatProp Int
64) = MatProp
Lower
fromMatProp (AFMatProp Int
128) = MatProp
DiagUnit
fromMatProp (AFMatProp Int
512) = MatProp
Sym
fromMatProp (AFMatProp Int
1024) = MatProp
PosDef
fromMatProp (AFMatProp Int
2048) = MatProp
Orthog
fromMatProp (AFMatProp Int
4096) = MatProp
TriDiag
fromMatProp (AFMatProp Int
8192) = MatProp
BlockDiag
fromMatProp AFMatProp
x = String -> MatProp
forall a. HasCallStack => String -> a
error (String -> MatProp) -> String -> MatProp
forall a b. (a -> b) -> a -> b
$ String
"Invalid AFMatProp value: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> AFMatProp -> String
forall a. Show a => a -> String
show AFMatProp
x
toMatProp
:: MatProp
-> AFMatProp
toMatProp :: MatProp -> AFMatProp
toMatProp MatProp
None = (Int -> AFMatProp
AFMatProp Int
0)
toMatProp MatProp
Trans = (Int -> AFMatProp
AFMatProp Int
1)
toMatProp MatProp
CTrans = (Int -> AFMatProp
AFMatProp Int
2)
toMatProp MatProp
Conj = (Int -> AFMatProp
AFMatProp Int
4)
toMatProp MatProp
Upper = (Int -> AFMatProp
AFMatProp Int
32)
toMatProp MatProp
Lower = (Int -> AFMatProp
AFMatProp Int
64)
toMatProp MatProp
DiagUnit = (Int -> AFMatProp
AFMatProp Int
128)
toMatProp MatProp
Sym = (Int -> AFMatProp
AFMatProp Int
512)
toMatProp MatProp
PosDef = (Int -> AFMatProp
AFMatProp Int
1024)
toMatProp MatProp
Orthog = (Int -> AFMatProp
AFMatProp Int
2048)
toMatProp MatProp
TriDiag = (Int -> AFMatProp
AFMatProp Int
4096)
toMatProp MatProp
BlockDiag = (Int -> AFMatProp
AFMatProp Int
8192)
data BinaryOp
= Add
| Mul
| Min
| Max
deriving (Int -> BinaryOp -> ShowS
[BinaryOp] -> ShowS
BinaryOp -> String
(Int -> BinaryOp -> ShowS)
-> (BinaryOp -> String) -> ([BinaryOp] -> ShowS) -> Show BinaryOp
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BinaryOp] -> ShowS
$cshowList :: [BinaryOp] -> ShowS
show :: BinaryOp -> String
$cshow :: BinaryOp -> String
showsPrec :: Int -> BinaryOp -> ShowS
$cshowsPrec :: Int -> BinaryOp -> ShowS
Show, BinaryOp -> BinaryOp -> Bool
(BinaryOp -> BinaryOp -> Bool)
-> (BinaryOp -> BinaryOp -> Bool) -> Eq BinaryOp
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BinaryOp -> BinaryOp -> Bool
$c/= :: BinaryOp -> BinaryOp -> Bool
== :: BinaryOp -> BinaryOp -> Bool
$c== :: BinaryOp -> BinaryOp -> Bool
Eq, Eq BinaryOp
Eq BinaryOp
-> (BinaryOp -> BinaryOp -> Ordering)
-> (BinaryOp -> BinaryOp -> Bool)
-> (BinaryOp -> BinaryOp -> Bool)
-> (BinaryOp -> BinaryOp -> Bool)
-> (BinaryOp -> BinaryOp -> Bool)
-> (BinaryOp -> BinaryOp -> BinaryOp)
-> (BinaryOp -> BinaryOp -> BinaryOp)
-> Ord BinaryOp
BinaryOp -> BinaryOp -> Bool
BinaryOp -> BinaryOp -> Ordering
BinaryOp -> BinaryOp -> BinaryOp
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 :: BinaryOp -> BinaryOp -> BinaryOp
$cmin :: BinaryOp -> BinaryOp -> BinaryOp
max :: BinaryOp -> BinaryOp -> BinaryOp
$cmax :: BinaryOp -> BinaryOp -> BinaryOp
>= :: BinaryOp -> BinaryOp -> Bool
$c>= :: BinaryOp -> BinaryOp -> Bool
> :: BinaryOp -> BinaryOp -> Bool
$c> :: BinaryOp -> BinaryOp -> Bool
<= :: BinaryOp -> BinaryOp -> Bool
$c<= :: BinaryOp -> BinaryOp -> Bool
< :: BinaryOp -> BinaryOp -> Bool
$c< :: BinaryOp -> BinaryOp -> Bool
compare :: BinaryOp -> BinaryOp -> Ordering
$ccompare :: BinaryOp -> BinaryOp -> Ordering
Ord)
toBinaryOp :: BinaryOp -> AFBinaryOp
toBinaryOp :: BinaryOp -> AFBinaryOp
toBinaryOp BinaryOp
Add = CInt -> AFBinaryOp
AFBinaryOp CInt
0
toBinaryOp BinaryOp
Mul = CInt -> AFBinaryOp
AFBinaryOp CInt
1
toBinaryOp BinaryOp
Min = CInt -> AFBinaryOp
AFBinaryOp CInt
2
toBinaryOp BinaryOp
Max = CInt -> AFBinaryOp
AFBinaryOp CInt
3
fromBinaryOp :: AFBinaryOp -> BinaryOp
fromBinaryOp :: AFBinaryOp -> BinaryOp
fromBinaryOp (AFBinaryOp CInt
0) = BinaryOp
Add
fromBinaryOp (AFBinaryOp CInt
1) = BinaryOp
Mul
fromBinaryOp (AFBinaryOp CInt
2) = BinaryOp
Min
fromBinaryOp (AFBinaryOp CInt
3) = BinaryOp
Max
fromBinaryOp AFBinaryOp
x = String -> BinaryOp
forall a. HasCallStack => String -> a
error (String
"Invalid Binary Op: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> AFBinaryOp -> String
forall a. Show a => a -> String
show AFBinaryOp
x)
data Storage
= Dense
| CSR
| CSC
| COO
deriving (Int -> Storage -> ShowS
[Storage] -> ShowS
Storage -> String
(Int -> Storage -> ShowS)
-> (Storage -> String) -> ([Storage] -> ShowS) -> Show Storage
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Storage] -> ShowS
$cshowList :: [Storage] -> ShowS
show :: Storage -> String
$cshow :: Storage -> String
showsPrec :: Int -> Storage -> ShowS
$cshowsPrec :: Int -> Storage -> ShowS
Show, Storage -> Storage -> Bool
(Storage -> Storage -> Bool)
-> (Storage -> Storage -> Bool) -> Eq Storage
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Storage -> Storage -> Bool
$c/= :: Storage -> Storage -> Bool
== :: Storage -> Storage -> Bool
$c== :: Storage -> Storage -> Bool
Eq, Eq Storage
Eq Storage
-> (Storage -> Storage -> Ordering)
-> (Storage -> Storage -> Bool)
-> (Storage -> Storage -> Bool)
-> (Storage -> Storage -> Bool)
-> (Storage -> Storage -> Bool)
-> (Storage -> Storage -> Storage)
-> (Storage -> Storage -> Storage)
-> Ord Storage
Storage -> Storage -> Bool
Storage -> Storage -> Ordering
Storage -> Storage -> Storage
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 :: Storage -> Storage -> Storage
$cmin :: Storage -> Storage -> Storage
max :: Storage -> Storage -> Storage
$cmax :: Storage -> Storage -> Storage
>= :: Storage -> Storage -> Bool
$c>= :: Storage -> Storage -> Bool
> :: Storage -> Storage -> Bool
$c> :: Storage -> Storage -> Bool
<= :: Storage -> Storage -> Bool
$c<= :: Storage -> Storage -> Bool
< :: Storage -> Storage -> Bool
$c< :: Storage -> Storage -> Bool
compare :: Storage -> Storage -> Ordering
$ccompare :: Storage -> Storage -> Ordering
Ord, Int -> Storage
Storage -> Int
Storage -> [Storage]
Storage -> Storage
Storage -> Storage -> [Storage]
Storage -> Storage -> Storage -> [Storage]
(Storage -> Storage)
-> (Storage -> Storage)
-> (Int -> Storage)
-> (Storage -> Int)
-> (Storage -> [Storage])
-> (Storage -> Storage -> [Storage])
-> (Storage -> Storage -> [Storage])
-> (Storage -> Storage -> Storage -> [Storage])
-> Enum Storage
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 :: Storage -> Storage -> Storage -> [Storage]
$cenumFromThenTo :: Storage -> Storage -> Storage -> [Storage]
enumFromTo :: Storage -> Storage -> [Storage]
$cenumFromTo :: Storage -> Storage -> [Storage]
enumFromThen :: Storage -> Storage -> [Storage]
$cenumFromThen :: Storage -> Storage -> [Storage]
enumFrom :: Storage -> [Storage]
$cenumFrom :: Storage -> [Storage]
fromEnum :: Storage -> Int
$cfromEnum :: Storage -> Int
toEnum :: Int -> Storage
$ctoEnum :: Int -> Storage
pred :: Storage -> Storage
$cpred :: Storage -> Storage
succ :: Storage -> Storage
$csucc :: Storage -> Storage
Enum)
toStorage :: Storage -> AFStorage
toStorage :: Storage -> AFStorage
toStorage = CInt -> AFStorage
AFStorage (CInt -> AFStorage) -> (Storage -> CInt) -> Storage -> AFStorage
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Storage -> Int) -> Storage -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Storage -> Int
forall a. Enum a => a -> Int
fromEnum
fromStorage :: AFStorage -> Storage
fromStorage :: AFStorage -> Storage
fromStorage (AFStorage (CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral -> Int
x))
| Int
x Int -> [Int] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Int
0..Int
3] = Int -> Storage
forall a. Enum a => Int -> a
toEnum Int
x
| Bool
otherwise = String -> Storage
forall a. HasCallStack => String -> a
error (String -> Storage) -> String -> Storage
forall a b. (a -> b) -> a -> b
$ String
"Invalid Storage " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> (Int -> String
forall a. Show a => a -> String
show Int
x)
data RandomEngineType
= Philox
| ThreeFry
| Mersenne
deriving (RandomEngineType -> RandomEngineType -> Bool
(RandomEngineType -> RandomEngineType -> Bool)
-> (RandomEngineType -> RandomEngineType -> Bool)
-> Eq RandomEngineType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RandomEngineType -> RandomEngineType -> Bool
$c/= :: RandomEngineType -> RandomEngineType -> Bool
== :: RandomEngineType -> RandomEngineType -> Bool
$c== :: RandomEngineType -> RandomEngineType -> Bool
Eq, Int -> RandomEngineType -> ShowS
[RandomEngineType] -> ShowS
RandomEngineType -> String
(Int -> RandomEngineType -> ShowS)
-> (RandomEngineType -> String)
-> ([RandomEngineType] -> ShowS)
-> Show RandomEngineType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RandomEngineType] -> ShowS
$cshowList :: [RandomEngineType] -> ShowS
show :: RandomEngineType -> String
$cshow :: RandomEngineType -> String
showsPrec :: Int -> RandomEngineType -> ShowS
$cshowsPrec :: Int -> RandomEngineType -> ShowS
Show)
toRandomEngine :: AFRandomEngineType -> RandomEngineType
toRandomEngine :: AFRandomEngineType -> RandomEngineType
toRandomEngine (AFRandomEngineType CInt
100) = RandomEngineType
Philox
toRandomEngine (AFRandomEngineType CInt
200) = RandomEngineType
ThreeFry
toRandomEngine (AFRandomEngineType CInt
300) = RandomEngineType
Mersenne
toRandomEngine (AFRandomEngineType CInt
x) =
String -> RandomEngineType
forall a. HasCallStack => String -> a
error (String
"Invalid random engine: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> CInt -> String
forall a. Show a => a -> String
show CInt
x)
fromRandomEngine :: RandomEngineType -> AFRandomEngineType
fromRandomEngine :: RandomEngineType -> AFRandomEngineType
fromRandomEngine RandomEngineType
Philox = (CInt -> AFRandomEngineType
AFRandomEngineType CInt
100)
fromRandomEngine RandomEngineType
ThreeFry = (CInt -> AFRandomEngineType
AFRandomEngineType CInt
200)
fromRandomEngine RandomEngineType
Mersenne = (CInt -> AFRandomEngineType
AFRandomEngineType CInt
300)
data InterpType
= Nearest
| Linear
| Bilinear
| Cubic
| LowerInterp
| LinearCosine
| BilinearCosine
| Bicubic
| CubicSpline
| BicubicSpline
deriving (Int -> InterpType -> ShowS
[InterpType] -> ShowS
InterpType -> String
(Int -> InterpType -> ShowS)
-> (InterpType -> String)
-> ([InterpType] -> ShowS)
-> Show InterpType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InterpType] -> ShowS
$cshowList :: [InterpType] -> ShowS
show :: InterpType -> String
$cshow :: InterpType -> String
showsPrec :: Int -> InterpType -> ShowS
$cshowsPrec :: Int -> InterpType -> ShowS
Show, InterpType -> InterpType -> Bool
(InterpType -> InterpType -> Bool)
-> (InterpType -> InterpType -> Bool) -> Eq InterpType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InterpType -> InterpType -> Bool
$c/= :: InterpType -> InterpType -> Bool
== :: InterpType -> InterpType -> Bool
$c== :: InterpType -> InterpType -> Bool
Eq, Eq InterpType
Eq InterpType
-> (InterpType -> InterpType -> Ordering)
-> (InterpType -> InterpType -> Bool)
-> (InterpType -> InterpType -> Bool)
-> (InterpType -> InterpType -> Bool)
-> (InterpType -> InterpType -> Bool)
-> (InterpType -> InterpType -> InterpType)
-> (InterpType -> InterpType -> InterpType)
-> Ord InterpType
InterpType -> InterpType -> Bool
InterpType -> InterpType -> Ordering
InterpType -> InterpType -> InterpType
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 :: InterpType -> InterpType -> InterpType
$cmin :: InterpType -> InterpType -> InterpType
max :: InterpType -> InterpType -> InterpType
$cmax :: InterpType -> InterpType -> InterpType
>= :: InterpType -> InterpType -> Bool
$c>= :: InterpType -> InterpType -> Bool
> :: InterpType -> InterpType -> Bool
$c> :: InterpType -> InterpType -> Bool
<= :: InterpType -> InterpType -> Bool
$c<= :: InterpType -> InterpType -> Bool
< :: InterpType -> InterpType -> Bool
$c< :: InterpType -> InterpType -> Bool
compare :: InterpType -> InterpType -> Ordering
$ccompare :: InterpType -> InterpType -> Ordering
Ord, Int -> InterpType
InterpType -> Int
InterpType -> [InterpType]
InterpType -> InterpType
InterpType -> InterpType -> [InterpType]
InterpType -> InterpType -> InterpType -> [InterpType]
(InterpType -> InterpType)
-> (InterpType -> InterpType)
-> (Int -> InterpType)
-> (InterpType -> Int)
-> (InterpType -> [InterpType])
-> (InterpType -> InterpType -> [InterpType])
-> (InterpType -> InterpType -> [InterpType])
-> (InterpType -> InterpType -> InterpType -> [InterpType])
-> Enum InterpType
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 :: InterpType -> InterpType -> InterpType -> [InterpType]
$cenumFromThenTo :: InterpType -> InterpType -> InterpType -> [InterpType]
enumFromTo :: InterpType -> InterpType -> [InterpType]
$cenumFromTo :: InterpType -> InterpType -> [InterpType]
enumFromThen :: InterpType -> InterpType -> [InterpType]
$cenumFromThen :: InterpType -> InterpType -> [InterpType]
enumFrom :: InterpType -> [InterpType]
$cenumFrom :: InterpType -> [InterpType]
fromEnum :: InterpType -> Int
$cfromEnum :: InterpType -> Int
toEnum :: Int -> InterpType
$ctoEnum :: Int -> InterpType
pred :: InterpType -> InterpType
$cpred :: InterpType -> InterpType
succ :: InterpType -> InterpType
$csucc :: InterpType -> InterpType
Enum)
toInterpType :: AFInterpType -> InterpType
toInterpType :: AFInterpType -> InterpType
toInterpType (AFInterpType (CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral -> Int
x)) = Int -> InterpType
forall a. Enum a => Int -> a
toEnum Int
x
fromInterpType :: InterpType -> AFInterpType
fromInterpType :: InterpType -> AFInterpType
fromInterpType = CInt -> AFInterpType
AFInterpType (CInt -> AFInterpType)
-> (InterpType -> CInt) -> InterpType -> AFInterpType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (InterpType -> Int) -> InterpType -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. InterpType -> Int
forall a. Enum a => a -> Int
fromEnum
data BorderType
= PadZero
| PadSym
deriving (Int -> BorderType -> ShowS
[BorderType] -> ShowS
BorderType -> String
(Int -> BorderType -> ShowS)
-> (BorderType -> String)
-> ([BorderType] -> ShowS)
-> Show BorderType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BorderType] -> ShowS
$cshowList :: [BorderType] -> ShowS
show :: BorderType -> String
$cshow :: BorderType -> String
showsPrec :: Int -> BorderType -> ShowS
$cshowsPrec :: Int -> BorderType -> ShowS
Show, Eq BorderType
Eq BorderType
-> (BorderType -> BorderType -> Ordering)
-> (BorderType -> BorderType -> Bool)
-> (BorderType -> BorderType -> Bool)
-> (BorderType -> BorderType -> Bool)
-> (BorderType -> BorderType -> Bool)
-> (BorderType -> BorderType -> BorderType)
-> (BorderType -> BorderType -> BorderType)
-> Ord BorderType
BorderType -> BorderType -> Bool
BorderType -> BorderType -> Ordering
BorderType -> BorderType -> BorderType
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 :: BorderType -> BorderType -> BorderType
$cmin :: BorderType -> BorderType -> BorderType
max :: BorderType -> BorderType -> BorderType
$cmax :: BorderType -> BorderType -> BorderType
>= :: BorderType -> BorderType -> Bool
$c>= :: BorderType -> BorderType -> Bool
> :: BorderType -> BorderType -> Bool
$c> :: BorderType -> BorderType -> Bool
<= :: BorderType -> BorderType -> Bool
$c<= :: BorderType -> BorderType -> Bool
< :: BorderType -> BorderType -> Bool
$c< :: BorderType -> BorderType -> Bool
compare :: BorderType -> BorderType -> Ordering
$ccompare :: BorderType -> BorderType -> Ordering
Ord, Int -> BorderType
BorderType -> Int
BorderType -> [BorderType]
BorderType -> BorderType
BorderType -> BorderType -> [BorderType]
BorderType -> BorderType -> BorderType -> [BorderType]
(BorderType -> BorderType)
-> (BorderType -> BorderType)
-> (Int -> BorderType)
-> (BorderType -> Int)
-> (BorderType -> [BorderType])
-> (BorderType -> BorderType -> [BorderType])
-> (BorderType -> BorderType -> [BorderType])
-> (BorderType -> BorderType -> BorderType -> [BorderType])
-> Enum BorderType
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 :: BorderType -> BorderType -> BorderType -> [BorderType]
$cenumFromThenTo :: BorderType -> BorderType -> BorderType -> [BorderType]
enumFromTo :: BorderType -> BorderType -> [BorderType]
$cenumFromTo :: BorderType -> BorderType -> [BorderType]
enumFromThen :: BorderType -> BorderType -> [BorderType]
$cenumFromThen :: BorderType -> BorderType -> [BorderType]
enumFrom :: BorderType -> [BorderType]
$cenumFrom :: BorderType -> [BorderType]
fromEnum :: BorderType -> Int
$cfromEnum :: BorderType -> Int
toEnum :: Int -> BorderType
$ctoEnum :: Int -> BorderType
pred :: BorderType -> BorderType
$cpred :: BorderType -> BorderType
succ :: BorderType -> BorderType
$csucc :: BorderType -> BorderType
Enum, BorderType -> BorderType -> Bool
(BorderType -> BorderType -> Bool)
-> (BorderType -> BorderType -> Bool) -> Eq BorderType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BorderType -> BorderType -> Bool
$c/= :: BorderType -> BorderType -> Bool
== :: BorderType -> BorderType -> Bool
$c== :: BorderType -> BorderType -> Bool
Eq)
toBorderType :: AFBorderType -> BorderType
toBorderType :: AFBorderType -> BorderType
toBorderType (AFBorderType (CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral -> Int
x)) = Int -> BorderType
forall a. Enum a => Int -> a
toEnum Int
x
fromBorderType :: BorderType -> AFBorderType
fromBorderType :: BorderType -> AFBorderType
fromBorderType = CInt -> AFBorderType
AFBorderType (CInt -> AFBorderType)
-> (BorderType -> CInt) -> BorderType -> AFBorderType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (BorderType -> Int) -> BorderType -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BorderType -> Int
forall a. Enum a => a -> Int
fromEnum
data Connectivity
= Conn4
| Conn8
deriving (Int -> Connectivity -> ShowS
[Connectivity] -> ShowS
Connectivity -> String
(Int -> Connectivity -> ShowS)
-> (Connectivity -> String)
-> ([Connectivity] -> ShowS)
-> Show Connectivity
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Connectivity] -> ShowS
$cshowList :: [Connectivity] -> ShowS
show :: Connectivity -> String
$cshow :: Connectivity -> String
showsPrec :: Int -> Connectivity -> ShowS
$cshowsPrec :: Int -> Connectivity -> ShowS
Show, Eq Connectivity
Eq Connectivity
-> (Connectivity -> Connectivity -> Ordering)
-> (Connectivity -> Connectivity -> Bool)
-> (Connectivity -> Connectivity -> Bool)
-> (Connectivity -> Connectivity -> Bool)
-> (Connectivity -> Connectivity -> Bool)
-> (Connectivity -> Connectivity -> Connectivity)
-> (Connectivity -> Connectivity -> Connectivity)
-> Ord Connectivity
Connectivity -> Connectivity -> Bool
Connectivity -> Connectivity -> Ordering
Connectivity -> Connectivity -> Connectivity
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 :: Connectivity -> Connectivity -> Connectivity
$cmin :: Connectivity -> Connectivity -> Connectivity
max :: Connectivity -> Connectivity -> Connectivity
$cmax :: Connectivity -> Connectivity -> Connectivity
>= :: Connectivity -> Connectivity -> Bool
$c>= :: Connectivity -> Connectivity -> Bool
> :: Connectivity -> Connectivity -> Bool
$c> :: Connectivity -> Connectivity -> Bool
<= :: Connectivity -> Connectivity -> Bool
$c<= :: Connectivity -> Connectivity -> Bool
< :: Connectivity -> Connectivity -> Bool
$c< :: Connectivity -> Connectivity -> Bool
compare :: Connectivity -> Connectivity -> Ordering
$ccompare :: Connectivity -> Connectivity -> Ordering
Ord, Int -> Connectivity
Connectivity -> Int
Connectivity -> [Connectivity]
Connectivity -> Connectivity
Connectivity -> Connectivity -> [Connectivity]
Connectivity -> Connectivity -> Connectivity -> [Connectivity]
(Connectivity -> Connectivity)
-> (Connectivity -> Connectivity)
-> (Int -> Connectivity)
-> (Connectivity -> Int)
-> (Connectivity -> [Connectivity])
-> (Connectivity -> Connectivity -> [Connectivity])
-> (Connectivity -> Connectivity -> [Connectivity])
-> (Connectivity -> Connectivity -> Connectivity -> [Connectivity])
-> Enum Connectivity
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 :: Connectivity -> Connectivity -> Connectivity -> [Connectivity]
$cenumFromThenTo :: Connectivity -> Connectivity -> Connectivity -> [Connectivity]
enumFromTo :: Connectivity -> Connectivity -> [Connectivity]
$cenumFromTo :: Connectivity -> Connectivity -> [Connectivity]
enumFromThen :: Connectivity -> Connectivity -> [Connectivity]
$cenumFromThen :: Connectivity -> Connectivity -> [Connectivity]
enumFrom :: Connectivity -> [Connectivity]
$cenumFrom :: Connectivity -> [Connectivity]
fromEnum :: Connectivity -> Int
$cfromEnum :: Connectivity -> Int
toEnum :: Int -> Connectivity
$ctoEnum :: Int -> Connectivity
pred :: Connectivity -> Connectivity
$cpred :: Connectivity -> Connectivity
succ :: Connectivity -> Connectivity
$csucc :: Connectivity -> Connectivity
Enum, Connectivity -> Connectivity -> Bool
(Connectivity -> Connectivity -> Bool)
-> (Connectivity -> Connectivity -> Bool) -> Eq Connectivity
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Connectivity -> Connectivity -> Bool
$c/= :: Connectivity -> Connectivity -> Bool
== :: Connectivity -> Connectivity -> Bool
$c== :: Connectivity -> Connectivity -> Bool
Eq)
toConnectivity :: AFConnectivity -> Connectivity
toConnectivity :: AFConnectivity -> Connectivity
toConnectivity (AFConnectivity CInt
4) = Connectivity
Conn4
toConnectivity (AFConnectivity CInt
8) = Connectivity
Conn4
toConnectivity (AFConnectivity CInt
x) = String -> Connectivity
forall a. HasCallStack => String -> a
error (String
"Unknown connectivity option: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> CInt -> String
forall a. Show a => a -> String
show CInt
x)
fromConnectivity :: Connectivity -> AFConnectivity
fromConnectivity :: Connectivity -> AFConnectivity
fromConnectivity Connectivity
Conn4 = CInt -> AFConnectivity
AFConnectivity CInt
4
fromConnectivity Connectivity
Conn8 = CInt -> AFConnectivity
AFConnectivity CInt
8
data CSpace
= Gray
| RGB
| HSV
| YCBCR
deriving (Int -> CSpace -> ShowS
[CSpace] -> ShowS
CSpace -> String
(Int -> CSpace -> ShowS)
-> (CSpace -> String) -> ([CSpace] -> ShowS) -> Show CSpace
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CSpace] -> ShowS
$cshowList :: [CSpace] -> ShowS
show :: CSpace -> String
$cshow :: CSpace -> String
showsPrec :: Int -> CSpace -> ShowS
$cshowsPrec :: Int -> CSpace -> ShowS
Show, CSpace -> CSpace -> Bool
(CSpace -> CSpace -> Bool)
-> (CSpace -> CSpace -> Bool) -> Eq CSpace
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CSpace -> CSpace -> Bool
$c/= :: CSpace -> CSpace -> Bool
== :: CSpace -> CSpace -> Bool
$c== :: CSpace -> CSpace -> Bool
Eq, Eq CSpace
Eq CSpace
-> (CSpace -> CSpace -> Ordering)
-> (CSpace -> CSpace -> Bool)
-> (CSpace -> CSpace -> Bool)
-> (CSpace -> CSpace -> Bool)
-> (CSpace -> CSpace -> Bool)
-> (CSpace -> CSpace -> CSpace)
-> (CSpace -> CSpace -> CSpace)
-> Ord CSpace
CSpace -> CSpace -> Bool
CSpace -> CSpace -> Ordering
CSpace -> CSpace -> CSpace
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 :: CSpace -> CSpace -> CSpace
$cmin :: CSpace -> CSpace -> CSpace
max :: CSpace -> CSpace -> CSpace
$cmax :: CSpace -> CSpace -> CSpace
>= :: CSpace -> CSpace -> Bool
$c>= :: CSpace -> CSpace -> Bool
> :: CSpace -> CSpace -> Bool
$c> :: CSpace -> CSpace -> Bool
<= :: CSpace -> CSpace -> Bool
$c<= :: CSpace -> CSpace -> Bool
< :: CSpace -> CSpace -> Bool
$c< :: CSpace -> CSpace -> Bool
compare :: CSpace -> CSpace -> Ordering
$ccompare :: CSpace -> CSpace -> Ordering
Ord, Int -> CSpace
CSpace -> Int
CSpace -> [CSpace]
CSpace -> CSpace
CSpace -> CSpace -> [CSpace]
CSpace -> CSpace -> CSpace -> [CSpace]
(CSpace -> CSpace)
-> (CSpace -> CSpace)
-> (Int -> CSpace)
-> (CSpace -> Int)
-> (CSpace -> [CSpace])
-> (CSpace -> CSpace -> [CSpace])
-> (CSpace -> CSpace -> [CSpace])
-> (CSpace -> CSpace -> CSpace -> [CSpace])
-> Enum CSpace
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 :: CSpace -> CSpace -> CSpace -> [CSpace]
$cenumFromThenTo :: CSpace -> CSpace -> CSpace -> [CSpace]
enumFromTo :: CSpace -> CSpace -> [CSpace]
$cenumFromTo :: CSpace -> CSpace -> [CSpace]
enumFromThen :: CSpace -> CSpace -> [CSpace]
$cenumFromThen :: CSpace -> CSpace -> [CSpace]
enumFrom :: CSpace -> [CSpace]
$cenumFrom :: CSpace -> [CSpace]
fromEnum :: CSpace -> Int
$cfromEnum :: CSpace -> Int
toEnum :: Int -> CSpace
$ctoEnum :: Int -> CSpace
pred :: CSpace -> CSpace
$cpred :: CSpace -> CSpace
succ :: CSpace -> CSpace
$csucc :: CSpace -> CSpace
Enum)
toCSpace :: AFCSpace -> CSpace
toCSpace :: AFCSpace -> CSpace
toCSpace (AFCSpace (Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral -> Int
x)) = Int -> CSpace
forall a. Enum a => Int -> a
toEnum Int
x
fromCSpace :: CSpace -> AFCSpace
fromCSpace :: CSpace -> AFCSpace
fromCSpace = Int -> AFCSpace
AFCSpace (Int -> AFCSpace) -> (CSpace -> Int) -> CSpace -> AFCSpace
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Int) -> (CSpace -> Int) -> CSpace -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CSpace -> Int
forall a. Enum a => a -> Int
fromEnum
data YccStd
= Ycc601
| Ycc709
| Ycc2020
deriving (Int -> YccStd -> ShowS
[YccStd] -> ShowS
YccStd -> String
(Int -> YccStd -> ShowS)
-> (YccStd -> String) -> ([YccStd] -> ShowS) -> Show YccStd
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [YccStd] -> ShowS
$cshowList :: [YccStd] -> ShowS
show :: YccStd -> String
$cshow :: YccStd -> String
showsPrec :: Int -> YccStd -> ShowS
$cshowsPrec :: Int -> YccStd -> ShowS
Show, YccStd -> YccStd -> Bool
(YccStd -> YccStd -> Bool)
-> (YccStd -> YccStd -> Bool) -> Eq YccStd
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: YccStd -> YccStd -> Bool
$c/= :: YccStd -> YccStd -> Bool
== :: YccStd -> YccStd -> Bool
$c== :: YccStd -> YccStd -> Bool
Eq, Eq YccStd
Eq YccStd
-> (YccStd -> YccStd -> Ordering)
-> (YccStd -> YccStd -> Bool)
-> (YccStd -> YccStd -> Bool)
-> (YccStd -> YccStd -> Bool)
-> (YccStd -> YccStd -> Bool)
-> (YccStd -> YccStd -> YccStd)
-> (YccStd -> YccStd -> YccStd)
-> Ord YccStd
YccStd -> YccStd -> Bool
YccStd -> YccStd -> Ordering
YccStd -> YccStd -> YccStd
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 :: YccStd -> YccStd -> YccStd
$cmin :: YccStd -> YccStd -> YccStd
max :: YccStd -> YccStd -> YccStd
$cmax :: YccStd -> YccStd -> YccStd
>= :: YccStd -> YccStd -> Bool
$c>= :: YccStd -> YccStd -> Bool
> :: YccStd -> YccStd -> Bool
$c> :: YccStd -> YccStd -> Bool
<= :: YccStd -> YccStd -> Bool
$c<= :: YccStd -> YccStd -> Bool
< :: YccStd -> YccStd -> Bool
$c< :: YccStd -> YccStd -> Bool
compare :: YccStd -> YccStd -> Ordering
$ccompare :: YccStd -> YccStd -> Ordering
Ord)
toAFYccStd :: AFYccStd -> YccStd
toAFYccStd :: AFYccStd -> YccStd
toAFYccStd (AFYccStd Int
601) = YccStd
Ycc601
toAFYccStd (AFYccStd Int
709) = YccStd
Ycc709
toAFYccStd (AFYccStd Int
2020) = YccStd
Ycc2020
toAFYccStd (AFYccStd Int
x) = String -> YccStd
forall a. HasCallStack => String -> a
error (String
"Unknown AFYccStd option: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Int -> String
forall a. Show a => a -> String
show Int
x)
fromAFYccStd :: YccStd -> AFYccStd
fromAFYccStd :: YccStd -> AFYccStd
fromAFYccStd YccStd
Ycc601 = AFYccStd
afYcc601
fromAFYccStd YccStd
Ycc709 = AFYccStd
afYcc709
fromAFYccStd YccStd
Ycc2020 = AFYccStd
afYcc2020
data MomentType
= M00
| M01
| M10
| M11
| FirstOrder
deriving (Int -> MomentType -> ShowS
[MomentType] -> ShowS
MomentType -> String
(Int -> MomentType -> ShowS)
-> (MomentType -> String)
-> ([MomentType] -> ShowS)
-> Show MomentType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MomentType] -> ShowS
$cshowList :: [MomentType] -> ShowS
show :: MomentType -> String
$cshow :: MomentType -> String
showsPrec :: Int -> MomentType -> ShowS
$cshowsPrec :: Int -> MomentType -> ShowS
Show, MomentType -> MomentType -> Bool
(MomentType -> MomentType -> Bool)
-> (MomentType -> MomentType -> Bool) -> Eq MomentType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MomentType -> MomentType -> Bool
$c/= :: MomentType -> MomentType -> Bool
== :: MomentType -> MomentType -> Bool
$c== :: MomentType -> MomentType -> Bool
Eq, Eq MomentType
Eq MomentType
-> (MomentType -> MomentType -> Ordering)
-> (MomentType -> MomentType -> Bool)
-> (MomentType -> MomentType -> Bool)
-> (MomentType -> MomentType -> Bool)
-> (MomentType -> MomentType -> Bool)
-> (MomentType -> MomentType -> MomentType)
-> (MomentType -> MomentType -> MomentType)
-> Ord MomentType
MomentType -> MomentType -> Bool
MomentType -> MomentType -> Ordering
MomentType -> MomentType -> MomentType
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 :: MomentType -> MomentType -> MomentType
$cmin :: MomentType -> MomentType -> MomentType
max :: MomentType -> MomentType -> MomentType
$cmax :: MomentType -> MomentType -> MomentType
>= :: MomentType -> MomentType -> Bool
$c>= :: MomentType -> MomentType -> Bool
> :: MomentType -> MomentType -> Bool
$c> :: MomentType -> MomentType -> Bool
<= :: MomentType -> MomentType -> Bool
$c<= :: MomentType -> MomentType -> Bool
< :: MomentType -> MomentType -> Bool
$c< :: MomentType -> MomentType -> Bool
compare :: MomentType -> MomentType -> Ordering
$ccompare :: MomentType -> MomentType -> Ordering
Ord)
toMomentType :: AFMomentType -> MomentType
toMomentType :: AFMomentType -> MomentType
toMomentType AFMomentType
x
| AFMomentType
x AFMomentType -> AFMomentType -> Bool
forall a. Eq a => a -> a -> Bool
== AFMomentType
afMomentM00 = MomentType
M00
| AFMomentType
x AFMomentType -> AFMomentType -> Bool
forall a. Eq a => a -> a -> Bool
== AFMomentType
afMomentM01 = MomentType
M01
| AFMomentType
x AFMomentType -> AFMomentType -> Bool
forall a. Eq a => a -> a -> Bool
== AFMomentType
afMomentM10 = MomentType
M10
| AFMomentType
x AFMomentType -> AFMomentType -> Bool
forall a. Eq a => a -> a -> Bool
== AFMomentType
afMomentM11 = MomentType
M11
| AFMomentType
x AFMomentType -> AFMomentType -> Bool
forall a. Eq a => a -> a -> Bool
== AFMomentType
afMomentFirstOrder = MomentType
FirstOrder
| Bool
otherwise = String -> MomentType
forall a. HasCallStack => String -> a
error (String
"Unknown moment type: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> AFMomentType -> String
forall a. Show a => a -> String
show AFMomentType
x)
fromMomentType :: MomentType -> AFMomentType
fromMomentType :: MomentType -> AFMomentType
fromMomentType MomentType
M00 = AFMomentType
afMomentM00
fromMomentType MomentType
M01 = AFMomentType
afMomentM01
fromMomentType MomentType
M10 = AFMomentType
afMomentM10
fromMomentType MomentType
M11 = AFMomentType
afMomentM11
fromMomentType MomentType
FirstOrder = AFMomentType
afMomentFirstOrder
data CannyThreshold
= Manual
| AutoOtsu
deriving (Int -> CannyThreshold -> ShowS
[CannyThreshold] -> ShowS
CannyThreshold -> String
(Int -> CannyThreshold -> ShowS)
-> (CannyThreshold -> String)
-> ([CannyThreshold] -> ShowS)
-> Show CannyThreshold
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CannyThreshold] -> ShowS
$cshowList :: [CannyThreshold] -> ShowS
show :: CannyThreshold -> String
$cshow :: CannyThreshold -> String
showsPrec :: Int -> CannyThreshold -> ShowS
$cshowsPrec :: Int -> CannyThreshold -> ShowS
Show, CannyThreshold -> CannyThreshold -> Bool
(CannyThreshold -> CannyThreshold -> Bool)
-> (CannyThreshold -> CannyThreshold -> Bool) -> Eq CannyThreshold
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CannyThreshold -> CannyThreshold -> Bool
$c/= :: CannyThreshold -> CannyThreshold -> Bool
== :: CannyThreshold -> CannyThreshold -> Bool
$c== :: CannyThreshold -> CannyThreshold -> Bool
Eq, Eq CannyThreshold
Eq CannyThreshold
-> (CannyThreshold -> CannyThreshold -> Ordering)
-> (CannyThreshold -> CannyThreshold -> Bool)
-> (CannyThreshold -> CannyThreshold -> Bool)
-> (CannyThreshold -> CannyThreshold -> Bool)
-> (CannyThreshold -> CannyThreshold -> Bool)
-> (CannyThreshold -> CannyThreshold -> CannyThreshold)
-> (CannyThreshold -> CannyThreshold -> CannyThreshold)
-> Ord CannyThreshold
CannyThreshold -> CannyThreshold -> Bool
CannyThreshold -> CannyThreshold -> Ordering
CannyThreshold -> CannyThreshold -> CannyThreshold
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 :: CannyThreshold -> CannyThreshold -> CannyThreshold
$cmin :: CannyThreshold -> CannyThreshold -> CannyThreshold
max :: CannyThreshold -> CannyThreshold -> CannyThreshold
$cmax :: CannyThreshold -> CannyThreshold -> CannyThreshold
>= :: CannyThreshold -> CannyThreshold -> Bool
$c>= :: CannyThreshold -> CannyThreshold -> Bool
> :: CannyThreshold -> CannyThreshold -> Bool
$c> :: CannyThreshold -> CannyThreshold -> Bool
<= :: CannyThreshold -> CannyThreshold -> Bool
$c<= :: CannyThreshold -> CannyThreshold -> Bool
< :: CannyThreshold -> CannyThreshold -> Bool
$c< :: CannyThreshold -> CannyThreshold -> Bool
compare :: CannyThreshold -> CannyThreshold -> Ordering
$ccompare :: CannyThreshold -> CannyThreshold -> Ordering
Ord, Int -> CannyThreshold
CannyThreshold -> Int
CannyThreshold -> [CannyThreshold]
CannyThreshold -> CannyThreshold
CannyThreshold -> CannyThreshold -> [CannyThreshold]
CannyThreshold
-> CannyThreshold -> CannyThreshold -> [CannyThreshold]
(CannyThreshold -> CannyThreshold)
-> (CannyThreshold -> CannyThreshold)
-> (Int -> CannyThreshold)
-> (CannyThreshold -> Int)
-> (CannyThreshold -> [CannyThreshold])
-> (CannyThreshold -> CannyThreshold -> [CannyThreshold])
-> (CannyThreshold -> CannyThreshold -> [CannyThreshold])
-> (CannyThreshold
-> CannyThreshold -> CannyThreshold -> [CannyThreshold])
-> Enum CannyThreshold
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 :: CannyThreshold
-> CannyThreshold -> CannyThreshold -> [CannyThreshold]
$cenumFromThenTo :: CannyThreshold
-> CannyThreshold -> CannyThreshold -> [CannyThreshold]
enumFromTo :: CannyThreshold -> CannyThreshold -> [CannyThreshold]
$cenumFromTo :: CannyThreshold -> CannyThreshold -> [CannyThreshold]
enumFromThen :: CannyThreshold -> CannyThreshold -> [CannyThreshold]
$cenumFromThen :: CannyThreshold -> CannyThreshold -> [CannyThreshold]
enumFrom :: CannyThreshold -> [CannyThreshold]
$cenumFrom :: CannyThreshold -> [CannyThreshold]
fromEnum :: CannyThreshold -> Int
$cfromEnum :: CannyThreshold -> Int
toEnum :: Int -> CannyThreshold
$ctoEnum :: Int -> CannyThreshold
pred :: CannyThreshold -> CannyThreshold
$cpred :: CannyThreshold -> CannyThreshold
succ :: CannyThreshold -> CannyThreshold
$csucc :: CannyThreshold -> CannyThreshold
Enum)
toCannyThreshold :: AFCannyThreshold -> CannyThreshold
toCannyThreshold :: AFCannyThreshold -> CannyThreshold
toCannyThreshold (AFCannyThreshold (CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral -> Int
x)) = Int -> CannyThreshold
forall a. Enum a => Int -> a
toEnum Int
x
fromCannyThreshold :: CannyThreshold -> AFCannyThreshold
fromCannyThreshold :: CannyThreshold -> AFCannyThreshold
fromCannyThreshold = CInt -> AFCannyThreshold
AFCannyThreshold (CInt -> AFCannyThreshold)
-> (CannyThreshold -> CInt) -> CannyThreshold -> AFCannyThreshold
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (CannyThreshold -> Int) -> CannyThreshold -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CannyThreshold -> Int
forall a. Enum a => a -> Int
fromEnum
data FluxFunction
= FluxDefault
| FluxQuadratic
| FluxExponential
deriving (Int -> FluxFunction -> ShowS
[FluxFunction] -> ShowS
FluxFunction -> String
(Int -> FluxFunction -> ShowS)
-> (FluxFunction -> String)
-> ([FluxFunction] -> ShowS)
-> Show FluxFunction
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FluxFunction] -> ShowS
$cshowList :: [FluxFunction] -> ShowS
show :: FluxFunction -> String
$cshow :: FluxFunction -> String
showsPrec :: Int -> FluxFunction -> ShowS
$cshowsPrec :: Int -> FluxFunction -> ShowS
Show, FluxFunction -> FluxFunction -> Bool
(FluxFunction -> FluxFunction -> Bool)
-> (FluxFunction -> FluxFunction -> Bool) -> Eq FluxFunction
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FluxFunction -> FluxFunction -> Bool
$c/= :: FluxFunction -> FluxFunction -> Bool
== :: FluxFunction -> FluxFunction -> Bool
$c== :: FluxFunction -> FluxFunction -> Bool
Eq, Eq FluxFunction
Eq FluxFunction
-> (FluxFunction -> FluxFunction -> Ordering)
-> (FluxFunction -> FluxFunction -> Bool)
-> (FluxFunction -> FluxFunction -> Bool)
-> (FluxFunction -> FluxFunction -> Bool)
-> (FluxFunction -> FluxFunction -> Bool)
-> (FluxFunction -> FluxFunction -> FluxFunction)
-> (FluxFunction -> FluxFunction -> FluxFunction)
-> Ord FluxFunction
FluxFunction -> FluxFunction -> Bool
FluxFunction -> FluxFunction -> Ordering
FluxFunction -> FluxFunction -> FluxFunction
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 :: FluxFunction -> FluxFunction -> FluxFunction
$cmin :: FluxFunction -> FluxFunction -> FluxFunction
max :: FluxFunction -> FluxFunction -> FluxFunction
$cmax :: FluxFunction -> FluxFunction -> FluxFunction
>= :: FluxFunction -> FluxFunction -> Bool
$c>= :: FluxFunction -> FluxFunction -> Bool
> :: FluxFunction -> FluxFunction -> Bool
$c> :: FluxFunction -> FluxFunction -> Bool
<= :: FluxFunction -> FluxFunction -> Bool
$c<= :: FluxFunction -> FluxFunction -> Bool
< :: FluxFunction -> FluxFunction -> Bool
$c< :: FluxFunction -> FluxFunction -> Bool
compare :: FluxFunction -> FluxFunction -> Ordering
$ccompare :: FluxFunction -> FluxFunction -> Ordering
Ord, Int -> FluxFunction
FluxFunction -> Int
FluxFunction -> [FluxFunction]
FluxFunction -> FluxFunction
FluxFunction -> FluxFunction -> [FluxFunction]
FluxFunction -> FluxFunction -> FluxFunction -> [FluxFunction]
(FluxFunction -> FluxFunction)
-> (FluxFunction -> FluxFunction)
-> (Int -> FluxFunction)
-> (FluxFunction -> Int)
-> (FluxFunction -> [FluxFunction])
-> (FluxFunction -> FluxFunction -> [FluxFunction])
-> (FluxFunction -> FluxFunction -> [FluxFunction])
-> (FluxFunction -> FluxFunction -> FluxFunction -> [FluxFunction])
-> Enum FluxFunction
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 :: FluxFunction -> FluxFunction -> FluxFunction -> [FluxFunction]
$cenumFromThenTo :: FluxFunction -> FluxFunction -> FluxFunction -> [FluxFunction]
enumFromTo :: FluxFunction -> FluxFunction -> [FluxFunction]
$cenumFromTo :: FluxFunction -> FluxFunction -> [FluxFunction]
enumFromThen :: FluxFunction -> FluxFunction -> [FluxFunction]
$cenumFromThen :: FluxFunction -> FluxFunction -> [FluxFunction]
enumFrom :: FluxFunction -> [FluxFunction]
$cenumFrom :: FluxFunction -> [FluxFunction]
fromEnum :: FluxFunction -> Int
$cfromEnum :: FluxFunction -> Int
toEnum :: Int -> FluxFunction
$ctoEnum :: Int -> FluxFunction
pred :: FluxFunction -> FluxFunction
$cpred :: FluxFunction -> FluxFunction
succ :: FluxFunction -> FluxFunction
$csucc :: FluxFunction -> FluxFunction
Enum)
toFluxFunction :: AFFluxFunction -> FluxFunction
toFluxFunction :: AFFluxFunction -> FluxFunction
toFluxFunction (AFFluxFunction (CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral -> Int
x)) = Int -> FluxFunction
forall a. Enum a => Int -> a
toEnum Int
x
fromFluxFunction :: FluxFunction -> AFFluxFunction
fromFluxFunction :: FluxFunction -> AFFluxFunction
fromFluxFunction = CInt -> AFFluxFunction
AFFluxFunction (CInt -> AFFluxFunction)
-> (FluxFunction -> CInt) -> FluxFunction -> AFFluxFunction
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (FluxFunction -> Int) -> FluxFunction -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FluxFunction -> Int
forall a. Enum a => a -> Int
fromEnum
data DiffusionEq
= DiffusionDefault
| DiffusionGrad
| DiffusionMCDE
deriving (Int -> DiffusionEq -> ShowS
[DiffusionEq] -> ShowS
DiffusionEq -> String
(Int -> DiffusionEq -> ShowS)
-> (DiffusionEq -> String)
-> ([DiffusionEq] -> ShowS)
-> Show DiffusionEq
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DiffusionEq] -> ShowS
$cshowList :: [DiffusionEq] -> ShowS
show :: DiffusionEq -> String
$cshow :: DiffusionEq -> String
showsPrec :: Int -> DiffusionEq -> ShowS
$cshowsPrec :: Int -> DiffusionEq -> ShowS
Show, DiffusionEq -> DiffusionEq -> Bool
(DiffusionEq -> DiffusionEq -> Bool)
-> (DiffusionEq -> DiffusionEq -> Bool) -> Eq DiffusionEq
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DiffusionEq -> DiffusionEq -> Bool
$c/= :: DiffusionEq -> DiffusionEq -> Bool
== :: DiffusionEq -> DiffusionEq -> Bool
$c== :: DiffusionEq -> DiffusionEq -> Bool
Eq, Eq DiffusionEq
Eq DiffusionEq
-> (DiffusionEq -> DiffusionEq -> Ordering)
-> (DiffusionEq -> DiffusionEq -> Bool)
-> (DiffusionEq -> DiffusionEq -> Bool)
-> (DiffusionEq -> DiffusionEq -> Bool)
-> (DiffusionEq -> DiffusionEq -> Bool)
-> (DiffusionEq -> DiffusionEq -> DiffusionEq)
-> (DiffusionEq -> DiffusionEq -> DiffusionEq)
-> Ord DiffusionEq
DiffusionEq -> DiffusionEq -> Bool
DiffusionEq -> DiffusionEq -> Ordering
DiffusionEq -> DiffusionEq -> DiffusionEq
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 :: DiffusionEq -> DiffusionEq -> DiffusionEq
$cmin :: DiffusionEq -> DiffusionEq -> DiffusionEq
max :: DiffusionEq -> DiffusionEq -> DiffusionEq
$cmax :: DiffusionEq -> DiffusionEq -> DiffusionEq
>= :: DiffusionEq -> DiffusionEq -> Bool
$c>= :: DiffusionEq -> DiffusionEq -> Bool
> :: DiffusionEq -> DiffusionEq -> Bool
$c> :: DiffusionEq -> DiffusionEq -> Bool
<= :: DiffusionEq -> DiffusionEq -> Bool
$c<= :: DiffusionEq -> DiffusionEq -> Bool
< :: DiffusionEq -> DiffusionEq -> Bool
$c< :: DiffusionEq -> DiffusionEq -> Bool
compare :: DiffusionEq -> DiffusionEq -> Ordering
$ccompare :: DiffusionEq -> DiffusionEq -> Ordering
Ord, Int -> DiffusionEq
DiffusionEq -> Int
DiffusionEq -> [DiffusionEq]
DiffusionEq -> DiffusionEq
DiffusionEq -> DiffusionEq -> [DiffusionEq]
DiffusionEq -> DiffusionEq -> DiffusionEq -> [DiffusionEq]
(DiffusionEq -> DiffusionEq)
-> (DiffusionEq -> DiffusionEq)
-> (Int -> DiffusionEq)
-> (DiffusionEq -> Int)
-> (DiffusionEq -> [DiffusionEq])
-> (DiffusionEq -> DiffusionEq -> [DiffusionEq])
-> (DiffusionEq -> DiffusionEq -> [DiffusionEq])
-> (DiffusionEq -> DiffusionEq -> DiffusionEq -> [DiffusionEq])
-> Enum DiffusionEq
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 :: DiffusionEq -> DiffusionEq -> DiffusionEq -> [DiffusionEq]
$cenumFromThenTo :: DiffusionEq -> DiffusionEq -> DiffusionEq -> [DiffusionEq]
enumFromTo :: DiffusionEq -> DiffusionEq -> [DiffusionEq]
$cenumFromTo :: DiffusionEq -> DiffusionEq -> [DiffusionEq]
enumFromThen :: DiffusionEq -> DiffusionEq -> [DiffusionEq]
$cenumFromThen :: DiffusionEq -> DiffusionEq -> [DiffusionEq]
enumFrom :: DiffusionEq -> [DiffusionEq]
$cenumFrom :: DiffusionEq -> [DiffusionEq]
fromEnum :: DiffusionEq -> Int
$cfromEnum :: DiffusionEq -> Int
toEnum :: Int -> DiffusionEq
$ctoEnum :: Int -> DiffusionEq
pred :: DiffusionEq -> DiffusionEq
$cpred :: DiffusionEq -> DiffusionEq
succ :: DiffusionEq -> DiffusionEq
$csucc :: DiffusionEq -> DiffusionEq
Enum)
toDiffusionEq :: AFDiffusionEq -> DiffusionEq
toDiffusionEq :: AFDiffusionEq -> DiffusionEq
toDiffusionEq (AFDiffusionEq (CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral -> Int
x)) = Int -> DiffusionEq
forall a. Enum a => Int -> a
toEnum Int
x
fromDiffusionEq :: DiffusionEq -> AFDiffusionEq
fromDiffusionEq :: DiffusionEq -> AFDiffusionEq
fromDiffusionEq = CInt -> AFDiffusionEq
AFDiffusionEq (CInt -> AFDiffusionEq)
-> (DiffusionEq -> CInt) -> DiffusionEq -> AFDiffusionEq
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (DiffusionEq -> Int) -> DiffusionEq -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DiffusionEq -> Int
forall a. Enum a => a -> Int
fromEnum
data IterativeDeconvAlgo
= DeconvDefault
| DeconvLandweber
| DeconvRichardsonLucy
deriving (Int -> IterativeDeconvAlgo -> ShowS
[IterativeDeconvAlgo] -> ShowS
IterativeDeconvAlgo -> String
(Int -> IterativeDeconvAlgo -> ShowS)
-> (IterativeDeconvAlgo -> String)
-> ([IterativeDeconvAlgo] -> ShowS)
-> Show IterativeDeconvAlgo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [IterativeDeconvAlgo] -> ShowS
$cshowList :: [IterativeDeconvAlgo] -> ShowS
show :: IterativeDeconvAlgo -> String
$cshow :: IterativeDeconvAlgo -> String
showsPrec :: Int -> IterativeDeconvAlgo -> ShowS
$cshowsPrec :: Int -> IterativeDeconvAlgo -> ShowS
Show, IterativeDeconvAlgo -> IterativeDeconvAlgo -> Bool
(IterativeDeconvAlgo -> IterativeDeconvAlgo -> Bool)
-> (IterativeDeconvAlgo -> IterativeDeconvAlgo -> Bool)
-> Eq IterativeDeconvAlgo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IterativeDeconvAlgo -> IterativeDeconvAlgo -> Bool
$c/= :: IterativeDeconvAlgo -> IterativeDeconvAlgo -> Bool
== :: IterativeDeconvAlgo -> IterativeDeconvAlgo -> Bool
$c== :: IterativeDeconvAlgo -> IterativeDeconvAlgo -> Bool
Eq, Eq IterativeDeconvAlgo
Eq IterativeDeconvAlgo
-> (IterativeDeconvAlgo -> IterativeDeconvAlgo -> Ordering)
-> (IterativeDeconvAlgo -> IterativeDeconvAlgo -> Bool)
-> (IterativeDeconvAlgo -> IterativeDeconvAlgo -> Bool)
-> (IterativeDeconvAlgo -> IterativeDeconvAlgo -> Bool)
-> (IterativeDeconvAlgo -> IterativeDeconvAlgo -> Bool)
-> (IterativeDeconvAlgo
-> IterativeDeconvAlgo -> IterativeDeconvAlgo)
-> (IterativeDeconvAlgo
-> IterativeDeconvAlgo -> IterativeDeconvAlgo)
-> Ord IterativeDeconvAlgo
IterativeDeconvAlgo -> IterativeDeconvAlgo -> Bool
IterativeDeconvAlgo -> IterativeDeconvAlgo -> Ordering
IterativeDeconvAlgo -> IterativeDeconvAlgo -> IterativeDeconvAlgo
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 :: IterativeDeconvAlgo -> IterativeDeconvAlgo -> IterativeDeconvAlgo
$cmin :: IterativeDeconvAlgo -> IterativeDeconvAlgo -> IterativeDeconvAlgo
max :: IterativeDeconvAlgo -> IterativeDeconvAlgo -> IterativeDeconvAlgo
$cmax :: IterativeDeconvAlgo -> IterativeDeconvAlgo -> IterativeDeconvAlgo
>= :: IterativeDeconvAlgo -> IterativeDeconvAlgo -> Bool
$c>= :: IterativeDeconvAlgo -> IterativeDeconvAlgo -> Bool
> :: IterativeDeconvAlgo -> IterativeDeconvAlgo -> Bool
$c> :: IterativeDeconvAlgo -> IterativeDeconvAlgo -> Bool
<= :: IterativeDeconvAlgo -> IterativeDeconvAlgo -> Bool
$c<= :: IterativeDeconvAlgo -> IterativeDeconvAlgo -> Bool
< :: IterativeDeconvAlgo -> IterativeDeconvAlgo -> Bool
$c< :: IterativeDeconvAlgo -> IterativeDeconvAlgo -> Bool
compare :: IterativeDeconvAlgo -> IterativeDeconvAlgo -> Ordering
$ccompare :: IterativeDeconvAlgo -> IterativeDeconvAlgo -> Ordering
Ord, Int -> IterativeDeconvAlgo
IterativeDeconvAlgo -> Int
IterativeDeconvAlgo -> [IterativeDeconvAlgo]
IterativeDeconvAlgo -> IterativeDeconvAlgo
IterativeDeconvAlgo -> IterativeDeconvAlgo -> [IterativeDeconvAlgo]
IterativeDeconvAlgo
-> IterativeDeconvAlgo
-> IterativeDeconvAlgo
-> [IterativeDeconvAlgo]
(IterativeDeconvAlgo -> IterativeDeconvAlgo)
-> (IterativeDeconvAlgo -> IterativeDeconvAlgo)
-> (Int -> IterativeDeconvAlgo)
-> (IterativeDeconvAlgo -> Int)
-> (IterativeDeconvAlgo -> [IterativeDeconvAlgo])
-> (IterativeDeconvAlgo
-> IterativeDeconvAlgo -> [IterativeDeconvAlgo])
-> (IterativeDeconvAlgo
-> IterativeDeconvAlgo -> [IterativeDeconvAlgo])
-> (IterativeDeconvAlgo
-> IterativeDeconvAlgo
-> IterativeDeconvAlgo
-> [IterativeDeconvAlgo])
-> Enum IterativeDeconvAlgo
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 :: IterativeDeconvAlgo
-> IterativeDeconvAlgo
-> IterativeDeconvAlgo
-> [IterativeDeconvAlgo]
$cenumFromThenTo :: IterativeDeconvAlgo
-> IterativeDeconvAlgo
-> IterativeDeconvAlgo
-> [IterativeDeconvAlgo]
enumFromTo :: IterativeDeconvAlgo -> IterativeDeconvAlgo -> [IterativeDeconvAlgo]
$cenumFromTo :: IterativeDeconvAlgo -> IterativeDeconvAlgo -> [IterativeDeconvAlgo]
enumFromThen :: IterativeDeconvAlgo -> IterativeDeconvAlgo -> [IterativeDeconvAlgo]
$cenumFromThen :: IterativeDeconvAlgo -> IterativeDeconvAlgo -> [IterativeDeconvAlgo]
enumFrom :: IterativeDeconvAlgo -> [IterativeDeconvAlgo]
$cenumFrom :: IterativeDeconvAlgo -> [IterativeDeconvAlgo]
fromEnum :: IterativeDeconvAlgo -> Int
$cfromEnum :: IterativeDeconvAlgo -> Int
toEnum :: Int -> IterativeDeconvAlgo
$ctoEnum :: Int -> IterativeDeconvAlgo
pred :: IterativeDeconvAlgo -> IterativeDeconvAlgo
$cpred :: IterativeDeconvAlgo -> IterativeDeconvAlgo
succ :: IterativeDeconvAlgo -> IterativeDeconvAlgo
$csucc :: IterativeDeconvAlgo -> IterativeDeconvAlgo
Enum)
toIterativeDeconvAlgo :: AFIterativeDeconvAlgo -> IterativeDeconvAlgo
toIterativeDeconvAlgo :: AFIterativeDeconvAlgo -> IterativeDeconvAlgo
toIterativeDeconvAlgo (AFIterativeDeconvAlgo (CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral -> Int
x)) = Int -> IterativeDeconvAlgo
forall a. Enum a => Int -> a
toEnum Int
x
fromIterativeDeconvAlgo :: IterativeDeconvAlgo -> AFIterativeDeconvAlgo
fromIterativeDeconvAlgo :: IterativeDeconvAlgo -> AFIterativeDeconvAlgo
fromIterativeDeconvAlgo = CInt -> AFIterativeDeconvAlgo
AFIterativeDeconvAlgo (CInt -> AFIterativeDeconvAlgo)
-> (IterativeDeconvAlgo -> CInt)
-> IterativeDeconvAlgo
-> AFIterativeDeconvAlgo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt)
-> (IterativeDeconvAlgo -> Int) -> IterativeDeconvAlgo -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IterativeDeconvAlgo -> Int
forall a. Enum a => a -> Int
fromEnum
data InverseDeconvAlgo
= InverseDeconvDefault
| InverseDeconvTikhonov
deriving (Int -> InverseDeconvAlgo -> ShowS
[InverseDeconvAlgo] -> ShowS
InverseDeconvAlgo -> String
(Int -> InverseDeconvAlgo -> ShowS)
-> (InverseDeconvAlgo -> String)
-> ([InverseDeconvAlgo] -> ShowS)
-> Show InverseDeconvAlgo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InverseDeconvAlgo] -> ShowS
$cshowList :: [InverseDeconvAlgo] -> ShowS
show :: InverseDeconvAlgo -> String
$cshow :: InverseDeconvAlgo -> String
showsPrec :: Int -> InverseDeconvAlgo -> ShowS
$cshowsPrec :: Int -> InverseDeconvAlgo -> ShowS
Show, InverseDeconvAlgo -> InverseDeconvAlgo -> Bool
(InverseDeconvAlgo -> InverseDeconvAlgo -> Bool)
-> (InverseDeconvAlgo -> InverseDeconvAlgo -> Bool)
-> Eq InverseDeconvAlgo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InverseDeconvAlgo -> InverseDeconvAlgo -> Bool
$c/= :: InverseDeconvAlgo -> InverseDeconvAlgo -> Bool
== :: InverseDeconvAlgo -> InverseDeconvAlgo -> Bool
$c== :: InverseDeconvAlgo -> InverseDeconvAlgo -> Bool
Eq, Eq InverseDeconvAlgo
Eq InverseDeconvAlgo
-> (InverseDeconvAlgo -> InverseDeconvAlgo -> Ordering)
-> (InverseDeconvAlgo -> InverseDeconvAlgo -> Bool)
-> (InverseDeconvAlgo -> InverseDeconvAlgo -> Bool)
-> (InverseDeconvAlgo -> InverseDeconvAlgo -> Bool)
-> (InverseDeconvAlgo -> InverseDeconvAlgo -> Bool)
-> (InverseDeconvAlgo -> InverseDeconvAlgo -> InverseDeconvAlgo)
-> (InverseDeconvAlgo -> InverseDeconvAlgo -> InverseDeconvAlgo)
-> Ord InverseDeconvAlgo
InverseDeconvAlgo -> InverseDeconvAlgo -> Bool
InverseDeconvAlgo -> InverseDeconvAlgo -> Ordering
InverseDeconvAlgo -> InverseDeconvAlgo -> InverseDeconvAlgo
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 :: InverseDeconvAlgo -> InverseDeconvAlgo -> InverseDeconvAlgo
$cmin :: InverseDeconvAlgo -> InverseDeconvAlgo -> InverseDeconvAlgo
max :: InverseDeconvAlgo -> InverseDeconvAlgo -> InverseDeconvAlgo
$cmax :: InverseDeconvAlgo -> InverseDeconvAlgo -> InverseDeconvAlgo
>= :: InverseDeconvAlgo -> InverseDeconvAlgo -> Bool
$c>= :: InverseDeconvAlgo -> InverseDeconvAlgo -> Bool
> :: InverseDeconvAlgo -> InverseDeconvAlgo -> Bool
$c> :: InverseDeconvAlgo -> InverseDeconvAlgo -> Bool
<= :: InverseDeconvAlgo -> InverseDeconvAlgo -> Bool
$c<= :: InverseDeconvAlgo -> InverseDeconvAlgo -> Bool
< :: InverseDeconvAlgo -> InverseDeconvAlgo -> Bool
$c< :: InverseDeconvAlgo -> InverseDeconvAlgo -> Bool
compare :: InverseDeconvAlgo -> InverseDeconvAlgo -> Ordering
$ccompare :: InverseDeconvAlgo -> InverseDeconvAlgo -> Ordering
Ord, Int -> InverseDeconvAlgo
InverseDeconvAlgo -> Int
InverseDeconvAlgo -> [InverseDeconvAlgo]
InverseDeconvAlgo -> InverseDeconvAlgo
InverseDeconvAlgo -> InverseDeconvAlgo -> [InverseDeconvAlgo]
InverseDeconvAlgo
-> InverseDeconvAlgo -> InverseDeconvAlgo -> [InverseDeconvAlgo]
(InverseDeconvAlgo -> InverseDeconvAlgo)
-> (InverseDeconvAlgo -> InverseDeconvAlgo)
-> (Int -> InverseDeconvAlgo)
-> (InverseDeconvAlgo -> Int)
-> (InverseDeconvAlgo -> [InverseDeconvAlgo])
-> (InverseDeconvAlgo -> InverseDeconvAlgo -> [InverseDeconvAlgo])
-> (InverseDeconvAlgo -> InverseDeconvAlgo -> [InverseDeconvAlgo])
-> (InverseDeconvAlgo
-> InverseDeconvAlgo -> InverseDeconvAlgo -> [InverseDeconvAlgo])
-> Enum InverseDeconvAlgo
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 :: InverseDeconvAlgo
-> InverseDeconvAlgo -> InverseDeconvAlgo -> [InverseDeconvAlgo]
$cenumFromThenTo :: InverseDeconvAlgo
-> InverseDeconvAlgo -> InverseDeconvAlgo -> [InverseDeconvAlgo]
enumFromTo :: InverseDeconvAlgo -> InverseDeconvAlgo -> [InverseDeconvAlgo]
$cenumFromTo :: InverseDeconvAlgo -> InverseDeconvAlgo -> [InverseDeconvAlgo]
enumFromThen :: InverseDeconvAlgo -> InverseDeconvAlgo -> [InverseDeconvAlgo]
$cenumFromThen :: InverseDeconvAlgo -> InverseDeconvAlgo -> [InverseDeconvAlgo]
enumFrom :: InverseDeconvAlgo -> [InverseDeconvAlgo]
$cenumFrom :: InverseDeconvAlgo -> [InverseDeconvAlgo]
fromEnum :: InverseDeconvAlgo -> Int
$cfromEnum :: InverseDeconvAlgo -> Int
toEnum :: Int -> InverseDeconvAlgo
$ctoEnum :: Int -> InverseDeconvAlgo
pred :: InverseDeconvAlgo -> InverseDeconvAlgo
$cpred :: InverseDeconvAlgo -> InverseDeconvAlgo
succ :: InverseDeconvAlgo -> InverseDeconvAlgo
$csucc :: InverseDeconvAlgo -> InverseDeconvAlgo
Enum)
toInverseDeconvAlgo :: AFInverseDeconvAlgo -> InverseDeconvAlgo
toInverseDeconvAlgo :: AFInverseDeconvAlgo -> InverseDeconvAlgo
toInverseDeconvAlgo (AFInverseDeconvAlgo (CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral -> Int
x)) = Int -> InverseDeconvAlgo
forall a. Enum a => Int -> a
toEnum Int
x
fromInverseDeconvAlgo :: InverseDeconvAlgo -> AFInverseDeconvAlgo
fromInverseDeconvAlgo :: InverseDeconvAlgo -> AFInverseDeconvAlgo
fromInverseDeconvAlgo = CInt -> AFInverseDeconvAlgo
AFInverseDeconvAlgo (CInt -> AFInverseDeconvAlgo)
-> (InverseDeconvAlgo -> CInt)
-> InverseDeconvAlgo
-> AFInverseDeconvAlgo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt)
-> (InverseDeconvAlgo -> Int) -> InverseDeconvAlgo -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. InverseDeconvAlgo -> Int
forall a. Enum a => a -> Int
fromEnum
data Cell
= Cell
{ Cell -> Int
cellRow :: Int
, Cell -> Int
cellCol :: Int
, Cell -> String
cellTitle :: String
, Cell -> ColorMap
cellColorMap :: ColorMap
} deriving (Int -> Cell -> ShowS
[Cell] -> ShowS
Cell -> String
(Int -> Cell -> ShowS)
-> (Cell -> String) -> ([Cell] -> ShowS) -> Show Cell
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Cell] -> ShowS
$cshowList :: [Cell] -> ShowS
show :: Cell -> String
$cshow :: Cell -> String
showsPrec :: Int -> Cell -> ShowS
$cshowsPrec :: Int -> Cell -> ShowS
Show, Cell -> Cell -> Bool
(Cell -> Cell -> Bool) -> (Cell -> Cell -> Bool) -> Eq Cell
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Cell -> Cell -> Bool
$c/= :: Cell -> Cell -> Bool
== :: Cell -> Cell -> Bool
$c== :: Cell -> Cell -> Bool
Eq)
cellToAFCell :: Cell -> IO AFCell
cellToAFCell :: Cell -> IO AFCell
cellToAFCell Cell {Int
String
ColorMap
cellColorMap :: ColorMap
cellTitle :: String
cellCol :: Int
cellRow :: Int
cellColorMap :: Cell -> ColorMap
cellTitle :: Cell -> String
cellCol :: Cell -> Int
cellRow :: Cell -> Int
..} =
String -> (CString -> IO AFCell) -> IO AFCell
forall a. String -> (CString -> IO a) -> IO a
withCString String
cellTitle ((CString -> IO AFCell) -> IO AFCell)
-> (CString -> IO AFCell) -> IO AFCell
forall a b. (a -> b) -> a -> b
$ \CString
cstr ->
AFCell -> IO AFCell
forall (f :: * -> *) a. Applicative f => a -> f a
pure AFCell :: Int -> Int -> CString -> AFColorMap -> AFCell
AFCell { afCellRow :: Int
afCellRow = Int
cellRow
, afCellCol :: Int
afCellCol = Int
cellCol
, afCellTitle :: CString
afCellTitle = CString
cstr
, afCellColorMap :: AFColorMap
afCellColorMap = ColorMap -> AFColorMap
fromColorMap ColorMap
cellColorMap
}
data ColorMap
= ColorMapDefault
| ColorMapSpectrum
| ColorMapColors
| ColorMapRed
| ColorMapMood
| ColorMapHeat
| ColorMapBlue
| ColorMapInferno
| ColorMapMagma
| ColorMapPlasma
| ColorMapViridis
deriving (Int -> ColorMap -> ShowS
[ColorMap] -> ShowS
ColorMap -> String
(Int -> ColorMap -> ShowS)
-> (ColorMap -> String) -> ([ColorMap] -> ShowS) -> Show ColorMap
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ColorMap] -> ShowS
$cshowList :: [ColorMap] -> ShowS
show :: ColorMap -> String
$cshow :: ColorMap -> String
showsPrec :: Int -> ColorMap -> ShowS
$cshowsPrec :: Int -> ColorMap -> ShowS
Show, ColorMap -> ColorMap -> Bool
(ColorMap -> ColorMap -> Bool)
-> (ColorMap -> ColorMap -> Bool) -> Eq ColorMap
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ColorMap -> ColorMap -> Bool
$c/= :: ColorMap -> ColorMap -> Bool
== :: ColorMap -> ColorMap -> Bool
$c== :: ColorMap -> ColorMap -> Bool
Eq, Eq ColorMap
Eq ColorMap
-> (ColorMap -> ColorMap -> Ordering)
-> (ColorMap -> ColorMap -> Bool)
-> (ColorMap -> ColorMap -> Bool)
-> (ColorMap -> ColorMap -> Bool)
-> (ColorMap -> ColorMap -> Bool)
-> (ColorMap -> ColorMap -> ColorMap)
-> (ColorMap -> ColorMap -> ColorMap)
-> Ord ColorMap
ColorMap -> ColorMap -> Bool
ColorMap -> ColorMap -> Ordering
ColorMap -> ColorMap -> ColorMap
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 :: ColorMap -> ColorMap -> ColorMap
$cmin :: ColorMap -> ColorMap -> ColorMap
max :: ColorMap -> ColorMap -> ColorMap
$cmax :: ColorMap -> ColorMap -> ColorMap
>= :: ColorMap -> ColorMap -> Bool
$c>= :: ColorMap -> ColorMap -> Bool
> :: ColorMap -> ColorMap -> Bool
$c> :: ColorMap -> ColorMap -> Bool
<= :: ColorMap -> ColorMap -> Bool
$c<= :: ColorMap -> ColorMap -> Bool
< :: ColorMap -> ColorMap -> Bool
$c< :: ColorMap -> ColorMap -> Bool
compare :: ColorMap -> ColorMap -> Ordering
$ccompare :: ColorMap -> ColorMap -> Ordering
Ord, Int -> ColorMap
ColorMap -> Int
ColorMap -> [ColorMap]
ColorMap -> ColorMap
ColorMap -> ColorMap -> [ColorMap]
ColorMap -> ColorMap -> ColorMap -> [ColorMap]
(ColorMap -> ColorMap)
-> (ColorMap -> ColorMap)
-> (Int -> ColorMap)
-> (ColorMap -> Int)
-> (ColorMap -> [ColorMap])
-> (ColorMap -> ColorMap -> [ColorMap])
-> (ColorMap -> ColorMap -> [ColorMap])
-> (ColorMap -> ColorMap -> ColorMap -> [ColorMap])
-> Enum ColorMap
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 :: ColorMap -> ColorMap -> ColorMap -> [ColorMap]
$cenumFromThenTo :: ColorMap -> ColorMap -> ColorMap -> [ColorMap]
enumFromTo :: ColorMap -> ColorMap -> [ColorMap]
$cenumFromTo :: ColorMap -> ColorMap -> [ColorMap]
enumFromThen :: ColorMap -> ColorMap -> [ColorMap]
$cenumFromThen :: ColorMap -> ColorMap -> [ColorMap]
enumFrom :: ColorMap -> [ColorMap]
$cenumFrom :: ColorMap -> [ColorMap]
fromEnum :: ColorMap -> Int
$cfromEnum :: ColorMap -> Int
toEnum :: Int -> ColorMap
$ctoEnum :: Int -> ColorMap
pred :: ColorMap -> ColorMap
$cpred :: ColorMap -> ColorMap
succ :: ColorMap -> ColorMap
$csucc :: ColorMap -> ColorMap
Enum)
fromColorMap :: ColorMap -> AFColorMap
fromColorMap :: ColorMap -> AFColorMap
fromColorMap = CInt -> AFColorMap
AFColorMap (CInt -> AFColorMap)
-> (ColorMap -> CInt) -> ColorMap -> AFColorMap
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (ColorMap -> Int) -> ColorMap -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ColorMap -> Int
forall a. Enum a => a -> Int
fromEnum
toColorMap :: AFColorMap -> ColorMap
toColorMap :: AFColorMap -> ColorMap
toColorMap (AFColorMap (CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral -> Int
x)) = Int -> ColorMap
forall a. Enum a => Int -> a
toEnum Int
x
data MarkerType
= MarkerTypeNone
| MarkerTypePoint
| MarkerTypeCircle
| MarkerTypeSquare
| MarkerTypeTriangle
| MarkerTypeCross
| MarkerTypePlus
| MarkerTypeStar
deriving (Int -> MarkerType -> ShowS
[MarkerType] -> ShowS
MarkerType -> String
(Int -> MarkerType -> ShowS)
-> (MarkerType -> String)
-> ([MarkerType] -> ShowS)
-> Show MarkerType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MarkerType] -> ShowS
$cshowList :: [MarkerType] -> ShowS
show :: MarkerType -> String
$cshow :: MarkerType -> String
showsPrec :: Int -> MarkerType -> ShowS
$cshowsPrec :: Int -> MarkerType -> ShowS
Show, MarkerType -> MarkerType -> Bool
(MarkerType -> MarkerType -> Bool)
-> (MarkerType -> MarkerType -> Bool) -> Eq MarkerType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MarkerType -> MarkerType -> Bool
$c/= :: MarkerType -> MarkerType -> Bool
== :: MarkerType -> MarkerType -> Bool
$c== :: MarkerType -> MarkerType -> Bool
Eq, Eq MarkerType
Eq MarkerType
-> (MarkerType -> MarkerType -> Ordering)
-> (MarkerType -> MarkerType -> Bool)
-> (MarkerType -> MarkerType -> Bool)
-> (MarkerType -> MarkerType -> Bool)
-> (MarkerType -> MarkerType -> Bool)
-> (MarkerType -> MarkerType -> MarkerType)
-> (MarkerType -> MarkerType -> MarkerType)
-> Ord MarkerType
MarkerType -> MarkerType -> Bool
MarkerType -> MarkerType -> Ordering
MarkerType -> MarkerType -> MarkerType
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 :: MarkerType -> MarkerType -> MarkerType
$cmin :: MarkerType -> MarkerType -> MarkerType
max :: MarkerType -> MarkerType -> MarkerType
$cmax :: MarkerType -> MarkerType -> MarkerType
>= :: MarkerType -> MarkerType -> Bool
$c>= :: MarkerType -> MarkerType -> Bool
> :: MarkerType -> MarkerType -> Bool
$c> :: MarkerType -> MarkerType -> Bool
<= :: MarkerType -> MarkerType -> Bool
$c<= :: MarkerType -> MarkerType -> Bool
< :: MarkerType -> MarkerType -> Bool
$c< :: MarkerType -> MarkerType -> Bool
compare :: MarkerType -> MarkerType -> Ordering
$ccompare :: MarkerType -> MarkerType -> Ordering
Ord, Int -> MarkerType
MarkerType -> Int
MarkerType -> [MarkerType]
MarkerType -> MarkerType
MarkerType -> MarkerType -> [MarkerType]
MarkerType -> MarkerType -> MarkerType -> [MarkerType]
(MarkerType -> MarkerType)
-> (MarkerType -> MarkerType)
-> (Int -> MarkerType)
-> (MarkerType -> Int)
-> (MarkerType -> [MarkerType])
-> (MarkerType -> MarkerType -> [MarkerType])
-> (MarkerType -> MarkerType -> [MarkerType])
-> (MarkerType -> MarkerType -> MarkerType -> [MarkerType])
-> Enum MarkerType
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 :: MarkerType -> MarkerType -> MarkerType -> [MarkerType]
$cenumFromThenTo :: MarkerType -> MarkerType -> MarkerType -> [MarkerType]
enumFromTo :: MarkerType -> MarkerType -> [MarkerType]
$cenumFromTo :: MarkerType -> MarkerType -> [MarkerType]
enumFromThen :: MarkerType -> MarkerType -> [MarkerType]
$cenumFromThen :: MarkerType -> MarkerType -> [MarkerType]
enumFrom :: MarkerType -> [MarkerType]
$cenumFrom :: MarkerType -> [MarkerType]
fromEnum :: MarkerType -> Int
$cfromEnum :: MarkerType -> Int
toEnum :: Int -> MarkerType
$ctoEnum :: Int -> MarkerType
pred :: MarkerType -> MarkerType
$cpred :: MarkerType -> MarkerType
succ :: MarkerType -> MarkerType
$csucc :: MarkerType -> MarkerType
Enum)
fromMarkerType :: MarkerType -> AFMarkerType
fromMarkerType :: MarkerType -> AFMarkerType
fromMarkerType = CInt -> AFMarkerType
AFMarkerType (CInt -> AFMarkerType)
-> (MarkerType -> CInt) -> MarkerType -> AFMarkerType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (MarkerType -> Int) -> MarkerType -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MarkerType -> Int
forall a. Enum a => a -> Int
fromEnum
toMarkerType :: AFMarkerType -> MarkerType
toMarkerType :: AFMarkerType -> MarkerType
toMarkerType (AFMarkerType (CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral -> Int
x)) = Int -> MarkerType
forall a. Enum a => Int -> a
toEnum Int
x
data MatchType
= MatchTypeSAD
| MatchTypeZSAD
| MatchTypeLSAD
| MatchTypeSSD
| MatchTypeZSSD
| MatchTypeLSSD
| MatchTypeNCC
| MatchTypeZNCC
| MatchTypeSHD
deriving (Int -> MatchType -> ShowS
[MatchType] -> ShowS
MatchType -> String
(Int -> MatchType -> ShowS)
-> (MatchType -> String)
-> ([MatchType] -> ShowS)
-> Show MatchType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MatchType] -> ShowS
$cshowList :: [MatchType] -> ShowS
show :: MatchType -> String
$cshow :: MatchType -> String
showsPrec :: Int -> MatchType -> ShowS
$cshowsPrec :: Int -> MatchType -> ShowS
Show, MatchType -> MatchType -> Bool
(MatchType -> MatchType -> Bool)
-> (MatchType -> MatchType -> Bool) -> Eq MatchType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MatchType -> MatchType -> Bool
$c/= :: MatchType -> MatchType -> Bool
== :: MatchType -> MatchType -> Bool
$c== :: MatchType -> MatchType -> Bool
Eq, Eq MatchType
Eq MatchType
-> (MatchType -> MatchType -> Ordering)
-> (MatchType -> MatchType -> Bool)
-> (MatchType -> MatchType -> Bool)
-> (MatchType -> MatchType -> Bool)
-> (MatchType -> MatchType -> Bool)
-> (MatchType -> MatchType -> MatchType)
-> (MatchType -> MatchType -> MatchType)
-> Ord MatchType
MatchType -> MatchType -> Bool
MatchType -> MatchType -> Ordering
MatchType -> MatchType -> MatchType
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 :: MatchType -> MatchType -> MatchType
$cmin :: MatchType -> MatchType -> MatchType
max :: MatchType -> MatchType -> MatchType
$cmax :: MatchType -> MatchType -> MatchType
>= :: MatchType -> MatchType -> Bool
$c>= :: MatchType -> MatchType -> Bool
> :: MatchType -> MatchType -> Bool
$c> :: MatchType -> MatchType -> Bool
<= :: MatchType -> MatchType -> Bool
$c<= :: MatchType -> MatchType -> Bool
< :: MatchType -> MatchType -> Bool
$c< :: MatchType -> MatchType -> Bool
compare :: MatchType -> MatchType -> Ordering
$ccompare :: MatchType -> MatchType -> Ordering
Ord, Int -> MatchType
MatchType -> Int
MatchType -> [MatchType]
MatchType -> MatchType
MatchType -> MatchType -> [MatchType]
MatchType -> MatchType -> MatchType -> [MatchType]
(MatchType -> MatchType)
-> (MatchType -> MatchType)
-> (Int -> MatchType)
-> (MatchType -> Int)
-> (MatchType -> [MatchType])
-> (MatchType -> MatchType -> [MatchType])
-> (MatchType -> MatchType -> [MatchType])
-> (MatchType -> MatchType -> MatchType -> [MatchType])
-> Enum MatchType
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 :: MatchType -> MatchType -> MatchType -> [MatchType]
$cenumFromThenTo :: MatchType -> MatchType -> MatchType -> [MatchType]
enumFromTo :: MatchType -> MatchType -> [MatchType]
$cenumFromTo :: MatchType -> MatchType -> [MatchType]
enumFromThen :: MatchType -> MatchType -> [MatchType]
$cenumFromThen :: MatchType -> MatchType -> [MatchType]
enumFrom :: MatchType -> [MatchType]
$cenumFrom :: MatchType -> [MatchType]
fromEnum :: MatchType -> Int
$cfromEnum :: MatchType -> Int
toEnum :: Int -> MatchType
$ctoEnum :: Int -> MatchType
pred :: MatchType -> MatchType
$cpred :: MatchType -> MatchType
succ :: MatchType -> MatchType
$csucc :: MatchType -> MatchType
Enum)
fromMatchType :: MatchType -> AFMatchType
fromMatchType :: MatchType -> AFMatchType
fromMatchType = CInt -> AFMatchType
AFMatchType (CInt -> AFMatchType)
-> (MatchType -> CInt) -> MatchType -> AFMatchType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (MatchType -> Int) -> MatchType -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MatchType -> Int
forall a. Enum a => a -> Int
fromEnum
toMatchType :: AFMatchType -> MatchType
toMatchType :: AFMatchType -> MatchType
toMatchType (AFMatchType (CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral -> Int
x)) = Int -> MatchType
forall a. Enum a => Int -> a
toEnum Int
x
data TopK
= TopKDefault
| TopKMin
| TopKMax
deriving (Int -> TopK -> ShowS
[TopK] -> ShowS
TopK -> String
(Int -> TopK -> ShowS)
-> (TopK -> String) -> ([TopK] -> ShowS) -> Show TopK
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TopK] -> ShowS
$cshowList :: [TopK] -> ShowS
show :: TopK -> String
$cshow :: TopK -> String
showsPrec :: Int -> TopK -> ShowS
$cshowsPrec :: Int -> TopK -> ShowS
Show, TopK -> TopK -> Bool
(TopK -> TopK -> Bool) -> (TopK -> TopK -> Bool) -> Eq TopK
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TopK -> TopK -> Bool
$c/= :: TopK -> TopK -> Bool
== :: TopK -> TopK -> Bool
$c== :: TopK -> TopK -> Bool
Eq, Eq TopK
Eq TopK
-> (TopK -> TopK -> Ordering)
-> (TopK -> TopK -> Bool)
-> (TopK -> TopK -> Bool)
-> (TopK -> TopK -> Bool)
-> (TopK -> TopK -> Bool)
-> (TopK -> TopK -> TopK)
-> (TopK -> TopK -> TopK)
-> Ord TopK
TopK -> TopK -> Bool
TopK -> TopK -> Ordering
TopK -> TopK -> TopK
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 :: TopK -> TopK -> TopK
$cmin :: TopK -> TopK -> TopK
max :: TopK -> TopK -> TopK
$cmax :: TopK -> TopK -> TopK
>= :: TopK -> TopK -> Bool
$c>= :: TopK -> TopK -> Bool
> :: TopK -> TopK -> Bool
$c> :: TopK -> TopK -> Bool
<= :: TopK -> TopK -> Bool
$c<= :: TopK -> TopK -> Bool
< :: TopK -> TopK -> Bool
$c< :: TopK -> TopK -> Bool
compare :: TopK -> TopK -> Ordering
$ccompare :: TopK -> TopK -> Ordering
Ord, Int -> TopK
TopK -> Int
TopK -> [TopK]
TopK -> TopK
TopK -> TopK -> [TopK]
TopK -> TopK -> TopK -> [TopK]
(TopK -> TopK)
-> (TopK -> TopK)
-> (Int -> TopK)
-> (TopK -> Int)
-> (TopK -> [TopK])
-> (TopK -> TopK -> [TopK])
-> (TopK -> TopK -> [TopK])
-> (TopK -> TopK -> TopK -> [TopK])
-> Enum TopK
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 :: TopK -> TopK -> TopK -> [TopK]
$cenumFromThenTo :: TopK -> TopK -> TopK -> [TopK]
enumFromTo :: TopK -> TopK -> [TopK]
$cenumFromTo :: TopK -> TopK -> [TopK]
enumFromThen :: TopK -> TopK -> [TopK]
$cenumFromThen :: TopK -> TopK -> [TopK]
enumFrom :: TopK -> [TopK]
$cenumFrom :: TopK -> [TopK]
fromEnum :: TopK -> Int
$cfromEnum :: TopK -> Int
toEnum :: Int -> TopK
$ctoEnum :: Int -> TopK
pred :: TopK -> TopK
$cpred :: TopK -> TopK
succ :: TopK -> TopK
$csucc :: TopK -> TopK
Enum)
fromTopK :: TopK -> AFTopkFunction
fromTopK :: TopK -> AFTopkFunction
fromTopK = CInt -> AFTopkFunction
AFTopkFunction (CInt -> AFTopkFunction)
-> (TopK -> CInt) -> TopK -> AFTopkFunction
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (TopK -> Int) -> TopK -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TopK -> Int
forall a. Enum a => a -> Int
fromEnum
toTopK :: AFTopkFunction -> TopK
toTopK :: AFTopkFunction -> TopK
toTopK (AFTopkFunction (CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral -> Int
x)) = Int -> TopK
forall a. Enum a => Int -> a
toEnum Int
x
data HomographyType
= RANSAC
| LMEDS
deriving (Int -> HomographyType -> ShowS
[HomographyType] -> ShowS
HomographyType -> String
(Int -> HomographyType -> ShowS)
-> (HomographyType -> String)
-> ([HomographyType] -> ShowS)
-> Show HomographyType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [HomographyType] -> ShowS
$cshowList :: [HomographyType] -> ShowS
show :: HomographyType -> String
$cshow :: HomographyType -> String
showsPrec :: Int -> HomographyType -> ShowS
$cshowsPrec :: Int -> HomographyType -> ShowS
Show, HomographyType -> HomographyType -> Bool
(HomographyType -> HomographyType -> Bool)
-> (HomographyType -> HomographyType -> Bool) -> Eq HomographyType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: HomographyType -> HomographyType -> Bool
$c/= :: HomographyType -> HomographyType -> Bool
== :: HomographyType -> HomographyType -> Bool
$c== :: HomographyType -> HomographyType -> Bool
Eq, Eq HomographyType
Eq HomographyType
-> (HomographyType -> HomographyType -> Ordering)
-> (HomographyType -> HomographyType -> Bool)
-> (HomographyType -> HomographyType -> Bool)
-> (HomographyType -> HomographyType -> Bool)
-> (HomographyType -> HomographyType -> Bool)
-> (HomographyType -> HomographyType -> HomographyType)
-> (HomographyType -> HomographyType -> HomographyType)
-> Ord HomographyType
HomographyType -> HomographyType -> Bool
HomographyType -> HomographyType -> Ordering
HomographyType -> HomographyType -> HomographyType
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 :: HomographyType -> HomographyType -> HomographyType
$cmin :: HomographyType -> HomographyType -> HomographyType
max :: HomographyType -> HomographyType -> HomographyType
$cmax :: HomographyType -> HomographyType -> HomographyType
>= :: HomographyType -> HomographyType -> Bool
$c>= :: HomographyType -> HomographyType -> Bool
> :: HomographyType -> HomographyType -> Bool
$c> :: HomographyType -> HomographyType -> Bool
<= :: HomographyType -> HomographyType -> Bool
$c<= :: HomographyType -> HomographyType -> Bool
< :: HomographyType -> HomographyType -> Bool
$c< :: HomographyType -> HomographyType -> Bool
compare :: HomographyType -> HomographyType -> Ordering
$ccompare :: HomographyType -> HomographyType -> Ordering
Ord, Int -> HomographyType
HomographyType -> Int
HomographyType -> [HomographyType]
HomographyType -> HomographyType
HomographyType -> HomographyType -> [HomographyType]
HomographyType
-> HomographyType -> HomographyType -> [HomographyType]
(HomographyType -> HomographyType)
-> (HomographyType -> HomographyType)
-> (Int -> HomographyType)
-> (HomographyType -> Int)
-> (HomographyType -> [HomographyType])
-> (HomographyType -> HomographyType -> [HomographyType])
-> (HomographyType -> HomographyType -> [HomographyType])
-> (HomographyType
-> HomographyType -> HomographyType -> [HomographyType])
-> Enum HomographyType
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 :: HomographyType
-> HomographyType -> HomographyType -> [HomographyType]
$cenumFromThenTo :: HomographyType
-> HomographyType -> HomographyType -> [HomographyType]
enumFromTo :: HomographyType -> HomographyType -> [HomographyType]
$cenumFromTo :: HomographyType -> HomographyType -> [HomographyType]
enumFromThen :: HomographyType -> HomographyType -> [HomographyType]
$cenumFromThen :: HomographyType -> HomographyType -> [HomographyType]
enumFrom :: HomographyType -> [HomographyType]
$cenumFrom :: HomographyType -> [HomographyType]
fromEnum :: HomographyType -> Int
$cfromEnum :: HomographyType -> Int
toEnum :: Int -> HomographyType
$ctoEnum :: Int -> HomographyType
pred :: HomographyType -> HomographyType
$cpred :: HomographyType -> HomographyType
succ :: HomographyType -> HomographyType
$csucc :: HomographyType -> HomographyType
Enum)
fromHomographyType :: HomographyType -> AFHomographyType
fromHomographyType :: HomographyType -> AFHomographyType
fromHomographyType = CInt -> AFHomographyType
AFHomographyType (CInt -> AFHomographyType)
-> (HomographyType -> CInt) -> HomographyType -> AFHomographyType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (HomographyType -> Int) -> HomographyType -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HomographyType -> Int
forall a. Enum a => a -> Int
fromEnum
toHomographyType :: AFHomographyType -> HomographyType
toHomographyType :: AFHomographyType -> HomographyType
toHomographyType (AFHomographyType (CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral -> Int
x)) = Int -> HomographyType
forall a. Enum a => Int -> a
toEnum Int
x
data Seq
= Seq
{ Seq -> Double
seqBegin :: !Double
, Seq -> Double
seqEnd :: !Double
, Seq -> Double
seqStep :: !Double
} deriving (Int -> Seq -> ShowS
[Seq] -> ShowS
Seq -> String
(Int -> Seq -> ShowS)
-> (Seq -> String) -> ([Seq] -> ShowS) -> Show Seq
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Seq] -> ShowS
$cshowList :: [Seq] -> ShowS
show :: Seq -> String
$cshow :: Seq -> String
showsPrec :: Int -> Seq -> ShowS
$cshowsPrec :: Int -> Seq -> ShowS
Show, Seq -> Seq -> Bool
(Seq -> Seq -> Bool) -> (Seq -> Seq -> Bool) -> Eq Seq
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Seq -> Seq -> Bool
$c/= :: Seq -> Seq -> Bool
== :: Seq -> Seq -> Bool
$c== :: Seq -> Seq -> Bool
Eq, Eq Seq
Eq Seq
-> (Seq -> Seq -> Ordering)
-> (Seq -> Seq -> Bool)
-> (Seq -> Seq -> Bool)
-> (Seq -> Seq -> Bool)
-> (Seq -> Seq -> Bool)
-> (Seq -> Seq -> Seq)
-> (Seq -> Seq -> Seq)
-> Ord Seq
Seq -> Seq -> Bool
Seq -> Seq -> Ordering
Seq -> Seq -> Seq
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 :: Seq -> Seq -> Seq
$cmin :: Seq -> Seq -> Seq
max :: Seq -> Seq -> Seq
$cmax :: Seq -> Seq -> Seq
>= :: Seq -> Seq -> Bool
$c>= :: Seq -> Seq -> Bool
> :: Seq -> Seq -> Bool
$c> :: Seq -> Seq -> Bool
<= :: Seq -> Seq -> Bool
$c<= :: Seq -> Seq -> Bool
< :: Seq -> Seq -> Bool
$c< :: Seq -> Seq -> Bool
compare :: Seq -> Seq -> Ordering
$ccompare :: Seq -> Seq -> Ordering
Ord)
toAFSeq :: Seq -> AFSeq
toAFSeq :: Seq -> AFSeq
toAFSeq (Seq Double
x Double
y Double
z) = (Double -> Double -> Double -> AFSeq
AFSeq Double
x Double
y Double
z)
data Index a
= Index
{ forall a. Index a -> Either (Array a) Seq
idx :: Either (Array a) Seq
, forall a. Index a -> Bool
isSeq :: !Bool
, forall a. Index a -> Bool
isBatch :: !Bool
}
seqIdx :: Seq -> Bool -> Index a
seqIdx :: forall a. Seq -> Bool -> Index a
seqIdx Seq
s = Either (Array a) Seq -> Bool -> Bool -> Index a
forall a. Either (Array a) Seq -> Bool -> Bool -> Index a
Index (Seq -> Either (Array a) Seq
forall a b. b -> Either a b
Right Seq
s) Bool
True
arrIdx :: Array a -> Bool -> Index a
arrIdx :: forall a. Array a -> Bool -> Index a
arrIdx Array a
a = Either (Array a) Seq -> Bool -> Bool -> Index a
forall a. Either (Array a) Seq -> Bool -> Bool -> Index a
Index (Array a -> Either (Array a) Seq
forall a b. a -> Either a b
Left Array a
a) Bool
False
toAFIndex :: Index a -> IO AFIndex
toAFIndex :: forall a. Index a -> IO AFIndex
toAFIndex (Index Either (Array a) Seq
a Bool
b Bool
c) = do
case Either (Array a) Seq
a of
Right Seq
s -> AFIndex -> IO AFIndex
forall (f :: * -> *) a. Applicative f => a -> f a
pure (AFIndex -> IO AFIndex) -> AFIndex -> IO AFIndex
forall a b. (a -> b) -> a -> b
$ Either AFArray AFSeq -> Bool -> Bool -> AFIndex
AFIndex (AFSeq -> Either AFArray AFSeq
forall a b. b -> Either a b
Right (Seq -> AFSeq
toAFSeq Seq
s)) Bool
b Bool
c
Left (Array ForeignPtr ()
fptr) -> do
ForeignPtr () -> (AFArray -> IO AFIndex) -> IO AFIndex
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr ()
fptr ((AFArray -> IO AFIndex) -> IO AFIndex)
-> (AFArray -> IO AFIndex) -> IO AFIndex
forall a b. (a -> b) -> a -> b
$ \AFArray
ptr ->
AFIndex -> IO AFIndex
forall (f :: * -> *) a. Applicative f => a -> f a
pure (AFIndex -> IO AFIndex) -> AFIndex -> IO AFIndex
forall a b. (a -> b) -> a -> b
$ Either AFArray AFSeq -> Bool -> Bool -> AFIndex
AFIndex (AFArray -> Either AFArray AFSeq
forall a b. a -> Either a b
Left AFArray
ptr) Bool
b Bool
c
type Version = (Int,Int,Int)
data NormType
= NormVectorOne
| NormVectorInf
| NormVector2
| NormVectorP
| NormMatrix1
| NormMatrixInf
| NormMatrix2
| NormMatrixLPQ
| NormEuclid
deriving (Int -> NormType -> ShowS
[NormType] -> ShowS
NormType -> String
(Int -> NormType -> ShowS)
-> (NormType -> String) -> ([NormType] -> ShowS) -> Show NormType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NormType] -> ShowS
$cshowList :: [NormType] -> ShowS
show :: NormType -> String
$cshow :: NormType -> String
showsPrec :: Int -> NormType -> ShowS
$cshowsPrec :: Int -> NormType -> ShowS
Show, NormType -> NormType -> Bool
(NormType -> NormType -> Bool)
-> (NormType -> NormType -> Bool) -> Eq NormType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NormType -> NormType -> Bool
$c/= :: NormType -> NormType -> Bool
== :: NormType -> NormType -> Bool
$c== :: NormType -> NormType -> Bool
Eq, Int -> NormType
NormType -> Int
NormType -> [NormType]
NormType -> NormType
NormType -> NormType -> [NormType]
NormType -> NormType -> NormType -> [NormType]
(NormType -> NormType)
-> (NormType -> NormType)
-> (Int -> NormType)
-> (NormType -> Int)
-> (NormType -> [NormType])
-> (NormType -> NormType -> [NormType])
-> (NormType -> NormType -> [NormType])
-> (NormType -> NormType -> NormType -> [NormType])
-> Enum NormType
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 :: NormType -> NormType -> NormType -> [NormType]
$cenumFromThenTo :: NormType -> NormType -> NormType -> [NormType]
enumFromTo :: NormType -> NormType -> [NormType]
$cenumFromTo :: NormType -> NormType -> [NormType]
enumFromThen :: NormType -> NormType -> [NormType]
$cenumFromThen :: NormType -> NormType -> [NormType]
enumFrom :: NormType -> [NormType]
$cenumFrom :: NormType -> [NormType]
fromEnum :: NormType -> Int
$cfromEnum :: NormType -> Int
toEnum :: Int -> NormType
$ctoEnum :: Int -> NormType
pred :: NormType -> NormType
$cpred :: NormType -> NormType
succ :: NormType -> NormType
$csucc :: NormType -> NormType
Enum)
fromNormType :: NormType -> AFNormType
fromNormType :: NormType -> AFNormType
fromNormType = Int -> AFNormType
AFNormType (Int -> AFNormType) -> (NormType -> Int) -> NormType -> AFNormType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Int) -> (NormType -> Int) -> NormType -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NormType -> Int
forall a. Enum a => a -> Int
fromEnum
toNormType :: AFNormType -> NormType
toNormType :: AFNormType -> NormType
toNormType (AFNormType (Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral -> Int
x)) = Int -> NormType
forall a. Enum a => Int -> a
toEnum Int
x
data ConvDomain
= ConvDomainAuto
| ConvDomainSpatial
| ConvDomainFreq
deriving (Int -> ConvDomain -> ShowS
[ConvDomain] -> ShowS
ConvDomain -> String
(Int -> ConvDomain -> ShowS)
-> (ConvDomain -> String)
-> ([ConvDomain] -> ShowS)
-> Show ConvDomain
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ConvDomain] -> ShowS
$cshowList :: [ConvDomain] -> ShowS
show :: ConvDomain -> String
$cshow :: ConvDomain -> String
showsPrec :: Int -> ConvDomain -> ShowS
$cshowsPrec :: Int -> ConvDomain -> ShowS
Show, ConvDomain -> ConvDomain -> Bool
(ConvDomain -> ConvDomain -> Bool)
-> (ConvDomain -> ConvDomain -> Bool) -> Eq ConvDomain
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ConvDomain -> ConvDomain -> Bool
$c/= :: ConvDomain -> ConvDomain -> Bool
== :: ConvDomain -> ConvDomain -> Bool
$c== :: ConvDomain -> ConvDomain -> Bool
Eq, Int -> ConvDomain
ConvDomain -> Int
ConvDomain -> [ConvDomain]
ConvDomain -> ConvDomain
ConvDomain -> ConvDomain -> [ConvDomain]
ConvDomain -> ConvDomain -> ConvDomain -> [ConvDomain]
(ConvDomain -> ConvDomain)
-> (ConvDomain -> ConvDomain)
-> (Int -> ConvDomain)
-> (ConvDomain -> Int)
-> (ConvDomain -> [ConvDomain])
-> (ConvDomain -> ConvDomain -> [ConvDomain])
-> (ConvDomain -> ConvDomain -> [ConvDomain])
-> (ConvDomain -> ConvDomain -> ConvDomain -> [ConvDomain])
-> Enum ConvDomain
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 :: ConvDomain -> ConvDomain -> ConvDomain -> [ConvDomain]
$cenumFromThenTo :: ConvDomain -> ConvDomain -> ConvDomain -> [ConvDomain]
enumFromTo :: ConvDomain -> ConvDomain -> [ConvDomain]
$cenumFromTo :: ConvDomain -> ConvDomain -> [ConvDomain]
enumFromThen :: ConvDomain -> ConvDomain -> [ConvDomain]
$cenumFromThen :: ConvDomain -> ConvDomain -> [ConvDomain]
enumFrom :: ConvDomain -> [ConvDomain]
$cenumFrom :: ConvDomain -> [ConvDomain]
fromEnum :: ConvDomain -> Int
$cfromEnum :: ConvDomain -> Int
toEnum :: Int -> ConvDomain
$ctoEnum :: Int -> ConvDomain
pred :: ConvDomain -> ConvDomain
$cpred :: ConvDomain -> ConvDomain
succ :: ConvDomain -> ConvDomain
$csucc :: ConvDomain -> ConvDomain
Enum)
data ConvMode
= ConvDefault
| ConvExpand
deriving (Int -> ConvMode -> ShowS
[ConvMode] -> ShowS
ConvMode -> String
(Int -> ConvMode -> ShowS)
-> (ConvMode -> String) -> ([ConvMode] -> ShowS) -> Show ConvMode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ConvMode] -> ShowS
$cshowList :: [ConvMode] -> ShowS
show :: ConvMode -> String
$cshow :: ConvMode -> String
showsPrec :: Int -> ConvMode -> ShowS
$cshowsPrec :: Int -> ConvMode -> ShowS
Show, ConvMode -> ConvMode -> Bool
(ConvMode -> ConvMode -> Bool)
-> (ConvMode -> ConvMode -> Bool) -> Eq ConvMode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ConvMode -> ConvMode -> Bool
$c/= :: ConvMode -> ConvMode -> Bool
== :: ConvMode -> ConvMode -> Bool
$c== :: ConvMode -> ConvMode -> Bool
Eq, Int -> ConvMode
ConvMode -> Int
ConvMode -> [ConvMode]
ConvMode -> ConvMode
ConvMode -> ConvMode -> [ConvMode]
ConvMode -> ConvMode -> ConvMode -> [ConvMode]
(ConvMode -> ConvMode)
-> (ConvMode -> ConvMode)
-> (Int -> ConvMode)
-> (ConvMode -> Int)
-> (ConvMode -> [ConvMode])
-> (ConvMode -> ConvMode -> [ConvMode])
-> (ConvMode -> ConvMode -> [ConvMode])
-> (ConvMode -> ConvMode -> ConvMode -> [ConvMode])
-> Enum ConvMode
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 :: ConvMode -> ConvMode -> ConvMode -> [ConvMode]
$cenumFromThenTo :: ConvMode -> ConvMode -> ConvMode -> [ConvMode]
enumFromTo :: ConvMode -> ConvMode -> [ConvMode]
$cenumFromTo :: ConvMode -> ConvMode -> [ConvMode]
enumFromThen :: ConvMode -> ConvMode -> [ConvMode]
$cenumFromThen :: ConvMode -> ConvMode -> [ConvMode]
enumFrom :: ConvMode -> [ConvMode]
$cenumFrom :: ConvMode -> [ConvMode]
fromEnum :: ConvMode -> Int
$cfromEnum :: ConvMode -> Int
toEnum :: Int -> ConvMode
$ctoEnum :: Int -> ConvMode
pred :: ConvMode -> ConvMode
$cpred :: ConvMode -> ConvMode
succ :: ConvMode -> ConvMode
$csucc :: ConvMode -> ConvMode
Enum)
fromConvDomain :: ConvDomain -> AFConvDomain
fromConvDomain :: ConvDomain -> AFConvDomain
fromConvDomain = CInt -> AFConvDomain
AFConvDomain (CInt -> AFConvDomain)
-> (ConvDomain -> CInt) -> ConvDomain -> AFConvDomain
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (ConvDomain -> Int) -> ConvDomain -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ConvDomain -> Int
forall a. Enum a => a -> Int
fromEnum
toConvDomain :: AFConvDomain -> ConvDomain
toConvDomain :: AFConvDomain -> ConvDomain
toConvDomain (AFConvDomain (CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral -> Int
x)) = Int -> ConvDomain
forall a. Enum a => Int -> a
toEnum Int
x
fromConvMode :: AFConvMode -> ConvMode
fromConvMode :: AFConvMode -> ConvMode
fromConvMode (AFConvMode (CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral -> Int
x)) = Int -> ConvMode
forall a. Enum a => Int -> a
toEnum Int
x
toConvMode :: ConvMode -> AFConvMode
toConvMode :: ConvMode -> AFConvMode
toConvMode = CInt -> AFConvMode
AFConvMode (CInt -> AFConvMode)
-> (ConvMode -> CInt) -> ConvMode -> AFConvMode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (ConvMode -> Int) -> ConvMode -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ConvMode -> Int
forall a. Enum a => a -> Int
fromEnum
data AFDType
= F32
| C32
| F64
| C64
| B8
| S32
| U32
| U8
| S64
| U64
| S16
| U16
deriving (Int -> AFDType -> ShowS
[AFDType] -> ShowS
AFDType -> String
(Int -> AFDType -> ShowS)
-> (AFDType -> String) -> ([AFDType] -> ShowS) -> Show AFDType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AFDType] -> ShowS
$cshowList :: [AFDType] -> ShowS
show :: AFDType -> String
$cshow :: AFDType -> String
showsPrec :: Int -> AFDType -> ShowS
$cshowsPrec :: Int -> AFDType -> ShowS
Show, AFDType -> AFDType -> Bool
(AFDType -> AFDType -> Bool)
-> (AFDType -> AFDType -> Bool) -> Eq AFDType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AFDType -> AFDType -> Bool
$c/= :: AFDType -> AFDType -> Bool
== :: AFDType -> AFDType -> Bool
$c== :: AFDType -> AFDType -> Bool
Eq, Int -> AFDType
AFDType -> Int
AFDType -> [AFDType]
AFDType -> AFDType
AFDType -> AFDType -> [AFDType]
AFDType -> AFDType -> AFDType -> [AFDType]
(AFDType -> AFDType)
-> (AFDType -> AFDType)
-> (Int -> AFDType)
-> (AFDType -> Int)
-> (AFDType -> [AFDType])
-> (AFDType -> AFDType -> [AFDType])
-> (AFDType -> AFDType -> [AFDType])
-> (AFDType -> AFDType -> AFDType -> [AFDType])
-> Enum AFDType
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 :: AFDType -> AFDType -> AFDType -> [AFDType]
$cenumFromThenTo :: AFDType -> AFDType -> AFDType -> [AFDType]
enumFromTo :: AFDType -> AFDType -> [AFDType]
$cenumFromTo :: AFDType -> AFDType -> [AFDType]
enumFromThen :: AFDType -> AFDType -> [AFDType]
$cenumFromThen :: AFDType -> AFDType -> [AFDType]
enumFrom :: AFDType -> [AFDType]
$cenumFrom :: AFDType -> [AFDType]
fromEnum :: AFDType -> Int
$cfromEnum :: AFDType -> Int
toEnum :: Int -> AFDType
$ctoEnum :: Int -> AFDType
pred :: AFDType -> AFDType
$cpred :: AFDType -> AFDType
succ :: AFDType -> AFDType
$csucc :: AFDType -> AFDType
Enum)
fromAFType :: AFDtype -> AFDType
fromAFType :: AFDtype -> AFDType
fromAFType (AFDtype (CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral -> Int
x)) = Int -> AFDType
forall a. Enum a => Int -> a
toEnum Int
x
toAFType :: AFDType -> AFDtype
toAFType :: AFDType -> AFDtype
toAFType = CInt -> AFDtype
AFDtype (CInt -> AFDtype) -> (AFDType -> CInt) -> AFDType -> AFDtype
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (AFDType -> Int) -> AFDType -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AFDType -> Int
forall a. Enum a => a -> Int
fromEnum