{-# LINE 1 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
module Database.PostgreSQL.LibPQ.Enums where
import Data.Bits ((.|.))
import Data.Maybe (fromMaybe)
import Foreign.C.Types (CInt (..))
import System.IO (IOMode(..), SeekMode(..))
class ToCInt a where
toCInt :: a -> CInt
class FromCInt a where
fromCInt :: CInt -> Maybe a
data ExecStatus
= EmptyQuery
| CommandOk
| TuplesOk
| CopyOut
| CopyIn
| CopyBoth
| BadResponse
| NonfatalError
| FatalError
| SingleTuple
deriving (ExecStatus -> ExecStatus -> Bool
(ExecStatus -> ExecStatus -> Bool)
-> (ExecStatus -> ExecStatus -> Bool) -> Eq ExecStatus
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ExecStatus -> ExecStatus -> Bool
== :: ExecStatus -> ExecStatus -> Bool
$c/= :: ExecStatus -> ExecStatus -> Bool
/= :: ExecStatus -> ExecStatus -> Bool
Eq, Int -> ExecStatus -> ShowS
[ExecStatus] -> ShowS
ExecStatus -> String
(Int -> ExecStatus -> ShowS)
-> (ExecStatus -> String)
-> ([ExecStatus] -> ShowS)
-> Show ExecStatus
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ExecStatus -> ShowS
showsPrec :: Int -> ExecStatus -> ShowS
$cshow :: ExecStatus -> String
show :: ExecStatus -> String
$cshowList :: [ExecStatus] -> ShowS
showList :: [ExecStatus] -> ShowS
Show)
instance FromCInt ExecStatus where
fromCInt :: CInt -> Maybe ExecStatus
fromCInt (CInt
0) = ExecStatus -> Maybe ExecStatus
forall a. a -> Maybe a
Just ExecStatus
EmptyQuery
{-# LINE 48 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
fromCInt (1) = Just CommandOk
{-# LINE 49 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
fromCInt (2) = Just TuplesOk
{-# LINE 50 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
fromCInt (3) = Just CopyOut
{-# LINE 51 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
fromCInt (4) = Just CopyIn
{-# LINE 52 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
fromCInt (8) = Just CopyBoth
{-# LINE 53 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
fromCInt (5) = Just BadResponse
{-# LINE 54 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
fromCInt (6) = Just NonfatalError
{-# LINE 55 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
fromCInt (7) = Just FatalError
{-# LINE 56 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
fromCInt (9) = Just SingleTuple
{-# LINE 57 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
fromCInt _ = Nothing
instance ToCInt ExecStatus where
toCInt :: ExecStatus -> CInt
toCInt ExecStatus
EmptyQuery = (CInt
0)
{-# LINE 61 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
toCInt CommandOk = (1)
{-# LINE 62 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
toCInt TuplesOk = (2)
{-# LINE 63 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
toCInt CopyOut = (3)
{-# LINE 64 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
toCInt CopyIn = (4)
{-# LINE 65 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
toCInt CopyBoth = (8)
{-# LINE 66 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
toCInt BadResponse = (5)
{-# LINE 67 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
toCInt NonfatalError = (6)
{-# LINE 68 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
toCInt FatalError = (7)
{-# LINE 69 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
toCInt SingleTuple = (9)
{-# LINE 70 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
data FieldCode
= DiagSeverity
| DiagSqlstate
| DiagMessagePrimary
| DiagMessageDetail
| DiagMessageHint
| DiagStatementPosition
| DiagInternalPosition
| DiagInternalQuery
| DiagContext
| DiagSourceFile
| DiagSourceLine
| DiagSourceFunction
deriving (FieldCode -> FieldCode -> Bool
(FieldCode -> FieldCode -> Bool)
-> (FieldCode -> FieldCode -> Bool) -> Eq FieldCode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FieldCode -> FieldCode -> Bool
== :: FieldCode -> FieldCode -> Bool
$c/= :: FieldCode -> FieldCode -> Bool
/= :: FieldCode -> FieldCode -> Bool
Eq, Int -> FieldCode -> ShowS
[FieldCode] -> ShowS
FieldCode -> String
(Int -> FieldCode -> ShowS)
-> (FieldCode -> String)
-> ([FieldCode] -> ShowS)
-> Show FieldCode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FieldCode -> ShowS
showsPrec :: Int -> FieldCode -> ShowS
$cshow :: FieldCode -> String
show :: FieldCode -> String
$cshowList :: [FieldCode] -> ShowS
showList :: [FieldCode] -> ShowS
Show)
instance FromCInt FieldCode where
fromCInt :: CInt -> Maybe FieldCode
fromCInt (CInt
83) = FieldCode -> Maybe FieldCode
forall a. a -> Maybe a
Just FieldCode
DiagSeverity
{-# LINE 147 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
fromCInt (67) = Just DiagSqlstate
{-# LINE 148 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
fromCInt (77) = Just DiagMessagePrimary
{-# LINE 149 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
fromCInt (68) = Just DiagMessageDetail
{-# LINE 150 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
fromCInt (72) = Just DiagMessageHint
{-# LINE 151 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
fromCInt (80) = Just DiagStatementPosition
{-# LINE 152 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
fromCInt (112) = Just DiagInternalPosition
{-# LINE 153 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
fromCInt (113) = Just DiagInternalQuery
{-# LINE 154 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
fromCInt (87) = Just DiagContext
{-# LINE 155 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
fromCInt (70) = Just DiagSourceFile
{-# LINE 156 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
fromCInt (76) = Just DiagSourceLine
{-# LINE 157 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
fromCInt (82) = Just DiagSourceFunction
{-# LINE 158 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
fromCInt _ = Nothing
instance ToCInt FieldCode where
toCInt :: FieldCode -> CInt
toCInt FieldCode
DiagSeverity = (CInt
83)
{-# LINE 162 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
toCInt DiagSqlstate = (67)
{-# LINE 163 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
toCInt DiagMessagePrimary = (77)
{-# LINE 164 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
toCInt DiagMessageDetail = (68)
{-# LINE 165 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
toCInt DiagMessageHint = (72)
{-# LINE 166 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
toCInt DiagStatementPosition = (80)
{-# LINE 167 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
toCInt DiagInternalPosition = (112)
{-# LINE 168 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
toCInt DiagInternalQuery = (113)
{-# LINE 169 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
toCInt DiagContext = (87)
{-# LINE 170 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
toCInt DiagSourceFile = (70)
{-# LINE 171 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
toCInt DiagSourceLine = (76)
{-# LINE 172 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
toCInt DiagSourceFunction = (82)
{-# LINE 173 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
data Verbosity
= ErrorsTerse
| ErrorsDefault
| ErrorsVerbose
deriving (Verbosity -> Verbosity -> Bool
(Verbosity -> Verbosity -> Bool)
-> (Verbosity -> Verbosity -> Bool) -> Eq Verbosity
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Verbosity -> Verbosity -> Bool
== :: Verbosity -> Verbosity -> Bool
$c/= :: Verbosity -> Verbosity -> Bool
/= :: Verbosity -> Verbosity -> Bool
Eq, Int -> Verbosity -> ShowS
[Verbosity] -> ShowS
Verbosity -> String
(Int -> Verbosity -> ShowS)
-> (Verbosity -> String)
-> ([Verbosity] -> ShowS)
-> Show Verbosity
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Verbosity -> ShowS
showsPrec :: Int -> Verbosity -> ShowS
$cshow :: Verbosity -> String
show :: Verbosity -> String
$cshowList :: [Verbosity] -> ShowS
showList :: [Verbosity] -> ShowS
Show)
instance FromCInt Verbosity where
fromCInt :: CInt -> Maybe Verbosity
fromCInt (CInt
0) = Verbosity -> Maybe Verbosity
forall a. a -> Maybe a
Just Verbosity
ErrorsTerse
{-# LINE 183 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
fromCInt (1) = Just ErrorsDefault
{-# LINE 184 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
fromCInt (2) = Just ErrorsVerbose
{-# LINE 185 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
fromCInt _ = Nothing
instance ToCInt Verbosity where
toCInt :: Verbosity -> CInt
toCInt Verbosity
ErrorsTerse = (CInt
0)
{-# LINE 189 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
toCInt ErrorsDefault = (1)
{-# LINE 190 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
toCInt ErrorsVerbose = (2)
{-# LINE 191 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
data PollingStatus
= PollingFailed
| PollingReading
| PollingWriting
| PollingOk
deriving (PollingStatus -> PollingStatus -> Bool
(PollingStatus -> PollingStatus -> Bool)
-> (PollingStatus -> PollingStatus -> Bool) -> Eq PollingStatus
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PollingStatus -> PollingStatus -> Bool
== :: PollingStatus -> PollingStatus -> Bool
$c/= :: PollingStatus -> PollingStatus -> Bool
/= :: PollingStatus -> PollingStatus -> Bool
Eq, Int -> PollingStatus -> ShowS
[PollingStatus] -> ShowS
PollingStatus -> String
(Int -> PollingStatus -> ShowS)
-> (PollingStatus -> String)
-> ([PollingStatus] -> ShowS)
-> Show PollingStatus
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PollingStatus -> ShowS
showsPrec :: Int -> PollingStatus -> ShowS
$cshow :: PollingStatus -> String
show :: PollingStatus -> String
$cshowList :: [PollingStatus] -> ShowS
showList :: [PollingStatus] -> ShowS
Show)
instance FromCInt PollingStatus where
fromCInt :: CInt -> Maybe PollingStatus
fromCInt (CInt
1) = PollingStatus -> Maybe PollingStatus
forall a. a -> Maybe a
forall (m :: * -> *) a. Monad m => a -> m a
return PollingStatus
PollingReading
{-# LINE 202 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
fromCInt (3) = return PollingOk
{-# LINE 203 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
fromCInt (2) = return PollingWriting
{-# LINE 204 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
fromCInt (0) = return PollingFailed
{-# LINE 205 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
fromCInt _ = Nothing
data ConnStatus
= ConnectionOk
| ConnectionBad
| ConnectionStarted
| ConnectionMade
| ConnectionAwaitingResponse
| ConnectionAuthOk
| ConnectionSetEnv
| ConnectionSSLStartup
deriving (ConnStatus -> ConnStatus -> Bool
(ConnStatus -> ConnStatus -> Bool)
-> (ConnStatus -> ConnStatus -> Bool) -> Eq ConnStatus
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ConnStatus -> ConnStatus -> Bool
== :: ConnStatus -> ConnStatus -> Bool
$c/= :: ConnStatus -> ConnStatus -> Bool
/= :: ConnStatus -> ConnStatus -> Bool
Eq, Int -> ConnStatus -> ShowS
[ConnStatus] -> ShowS
ConnStatus -> String
(Int -> ConnStatus -> ShowS)
-> (ConnStatus -> String)
-> ([ConnStatus] -> ShowS)
-> Show ConnStatus
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ConnStatus -> ShowS
showsPrec :: Int -> ConnStatus -> ShowS
$cshow :: ConnStatus -> String
show :: ConnStatus -> String
$cshowList :: [ConnStatus] -> ShowS
showList :: [ConnStatus] -> ShowS
Show)
instance FromCInt ConnStatus where
fromCInt :: CInt -> Maybe ConnStatus
fromCInt (CInt
0) = ConnStatus -> Maybe ConnStatus
forall a. a -> Maybe a
forall (m :: * -> *) a. Monad m => a -> m a
return ConnStatus
ConnectionOk
{-# LINE 224 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
fromCInt (1) = return ConnectionBad
{-# LINE 225 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
fromCInt (2) = return ConnectionStarted
{-# LINE 226 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
fromCInt (3) = return ConnectionMade
{-# LINE 227 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
fromCInt (4) = return ConnectionAwaitingResponse
{-# LINE 228 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
fromCInt (5) = return ConnectionAuthOk
{-# LINE 229 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
fromCInt (6) = return ConnectionSetEnv
{-# LINE 230 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
fromCInt (7) = return ConnectionSSLStartup
{-# LINE 231 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
fromCInt CInt
_ = Maybe ConnStatus
forall a. Maybe a
Nothing
data TransactionStatus
= TransIdle
| TransActive
| TransInTrans
| TransInError
| TransUnknown
deriving (TransactionStatus -> TransactionStatus -> Bool
(TransactionStatus -> TransactionStatus -> Bool)
-> (TransactionStatus -> TransactionStatus -> Bool)
-> Eq TransactionStatus
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TransactionStatus -> TransactionStatus -> Bool
== :: TransactionStatus -> TransactionStatus -> Bool
$c/= :: TransactionStatus -> TransactionStatus -> Bool
/= :: TransactionStatus -> TransactionStatus -> Bool
Eq, Int -> TransactionStatus -> ShowS
[TransactionStatus] -> ShowS
TransactionStatus -> String
(Int -> TransactionStatus -> ShowS)
-> (TransactionStatus -> String)
-> ([TransactionStatus] -> ShowS)
-> Show TransactionStatus
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TransactionStatus -> ShowS
showsPrec :: Int -> TransactionStatus -> ShowS
$cshow :: TransactionStatus -> String
show :: TransactionStatus -> String
$cshowList :: [TransactionStatus] -> ShowS
showList :: [TransactionStatus] -> ShowS
Show)
instance FromCInt TransactionStatus where
fromCInt :: CInt -> Maybe TransactionStatus
fromCInt (CInt
0) = TransactionStatus -> Maybe TransactionStatus
forall a. a -> Maybe a
forall (m :: * -> *) a. Monad m => a -> m a
return TransactionStatus
TransIdle
{-# LINE 245 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
fromCInt (1) = return TransActive
{-# LINE 246 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
fromCInt (2) = return TransInTrans
{-# LINE 247 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
fromCInt (3) = return TransInError
{-# LINE 248 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
fromCInt (4) = return TransUnknown
{-# LINE 249 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
fromCInt _ = Nothing
data Format
= Text
| Binary
deriving (Format -> Format -> Bool
(Format -> Format -> Bool)
-> (Format -> Format -> Bool) -> Eq Format
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Format -> Format -> Bool
== :: Format -> Format -> Bool
$c/= :: Format -> Format -> Bool
/= :: Format -> Format -> Bool
Eq, Eq Format
Eq Format =>
(Format -> Format -> Ordering)
-> (Format -> Format -> Bool)
-> (Format -> Format -> Bool)
-> (Format -> Format -> Bool)
-> (Format -> Format -> Bool)
-> (Format -> Format -> Format)
-> (Format -> Format -> Format)
-> Ord Format
Format -> Format -> Bool
Format -> Format -> Ordering
Format -> Format -> Format
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
$ccompare :: Format -> Format -> Ordering
compare :: Format -> Format -> Ordering
$c< :: Format -> Format -> Bool
< :: Format -> Format -> Bool
$c<= :: Format -> Format -> Bool
<= :: Format -> Format -> Bool
$c> :: Format -> Format -> Bool
> :: Format -> Format -> Bool
$c>= :: Format -> Format -> Bool
>= :: Format -> Format -> Bool
$cmax :: Format -> Format -> Format
max :: Format -> Format -> Format
$cmin :: Format -> Format -> Format
min :: Format -> Format -> Format
Ord, Int -> Format -> ShowS
[Format] -> ShowS
Format -> String
(Int -> Format -> ShowS)
-> (Format -> String) -> ([Format] -> ShowS) -> Show Format
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Format -> ShowS
showsPrec :: Int -> Format -> ShowS
$cshow :: Format -> String
show :: Format -> String
$cshowList :: [Format] -> ShowS
showList :: [Format] -> ShowS
Show, Int -> Format
Format -> Int
Format -> [Format]
Format -> Format
Format -> Format -> [Format]
Format -> Format -> Format -> [Format]
(Format -> Format)
-> (Format -> Format)
-> (Int -> Format)
-> (Format -> Int)
-> (Format -> [Format])
-> (Format -> Format -> [Format])
-> (Format -> Format -> [Format])
-> (Format -> Format -> Format -> [Format])
-> Enum Format
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: Format -> Format
succ :: Format -> Format
$cpred :: Format -> Format
pred :: Format -> Format
$ctoEnum :: Int -> Format
toEnum :: Int -> Format
$cfromEnum :: Format -> Int
fromEnum :: Format -> Int
$cenumFrom :: Format -> [Format]
enumFrom :: Format -> [Format]
$cenumFromThen :: Format -> Format -> [Format]
enumFromThen :: Format -> Format -> [Format]
$cenumFromTo :: Format -> Format -> [Format]
enumFromTo :: Format -> Format -> [Format]
$cenumFromThenTo :: Format -> Format -> Format -> [Format]
enumFromThenTo :: Format -> Format -> Format -> [Format]
Enum)
instance ToCInt Format where
toCInt :: Format -> CInt
toCInt Format
Text = CInt
0
toCInt Format
Binary = CInt
1
instance FromCInt Format where
fromCInt :: CInt -> Maybe Format
fromCInt CInt
0 = Format -> Maybe Format
forall a. a -> Maybe a
Just Format
Text
fromCInt CInt
1 = Format -> Maybe Format
forall a. a -> Maybe a
Just Format
Binary
fromCInt CInt
_ = Maybe Format
forall a. Maybe a
Nothing
instance ToCInt IOMode where
toCInt :: IOMode -> CInt
toCInt IOMode
ReadMode = (CInt
262144)
{-# LINE 272 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
toCInt WriteMode = (131072)
{-# LINE 273 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
toCInt ReadWriteMode = (262144) .|. (131072)
{-# LINE 274 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
toCInt AppendMode = (131072)
{-# LINE 275 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
instance ToCInt SeekMode where
toCInt :: SeekMode -> CInt
toCInt SeekMode
AbsoluteSeek = CInt
0
{-# LINE 278 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
toCInt RelativeSeek = 1
{-# LINE 279 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
toCInt SeekFromEnd = 2
{-# LINE 280 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}
instance ToCInt Bool where
toCInt :: Bool -> CInt
toCInt Bool
False = CInt
0
toCInt Bool
True = CInt
1
instance FromCInt Bool where
fromCInt :: CInt -> Maybe Bool
fromCInt CInt
0 = Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
False
fromCInt CInt
1 = Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
True
fromCInt CInt
_ = Maybe Bool
forall a. Maybe a
Nothing
instance Enum ExecStatus where
toEnum :: Int -> ExecStatus
toEnum = ExecStatus -> Maybe ExecStatus -> ExecStatus
forall a. a -> Maybe a -> a
fromMaybe (String -> ExecStatus
forall a. HasCallStack => String -> a
error String
"toEnum @Database.PostgreSQL.LibPQ.ExecStatus") (Maybe ExecStatus -> ExecStatus)
-> (Int -> Maybe ExecStatus) -> Int -> ExecStatus
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CInt -> Maybe ExecStatus
forall a. FromCInt a => CInt -> Maybe a
fromCInt (CInt -> Maybe ExecStatus)
-> (Int -> CInt) -> Int -> Maybe ExecStatus
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> CInt
forall a. Enum a => Int -> a
toEnum
fromEnum :: ExecStatus -> Int
fromEnum = CInt -> Int
forall a. Enum a => a -> Int
fromEnum (CInt -> Int) -> (ExecStatus -> CInt) -> ExecStatus -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ExecStatus -> CInt
forall a. ToCInt a => a -> CInt
toCInt
instance Enum FieldCode where
toEnum :: Int -> FieldCode
toEnum = FieldCode -> Maybe FieldCode -> FieldCode
forall a. a -> Maybe a -> a
fromMaybe (String -> FieldCode
forall a. HasCallStack => String -> a
error String
"toEnum @Database.PostgreSQL.LibPQ.FieldCode") (Maybe FieldCode -> FieldCode)
-> (Int -> Maybe FieldCode) -> Int -> FieldCode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CInt -> Maybe FieldCode
forall a. FromCInt a => CInt -> Maybe a
fromCInt (CInt -> Maybe FieldCode)
-> (Int -> CInt) -> Int -> Maybe FieldCode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> CInt
forall a. Enum a => Int -> a
toEnum
fromEnum :: FieldCode -> Int
fromEnum = CInt -> Int
forall a. Enum a => a -> Int
fromEnum (CInt -> Int) -> (FieldCode -> CInt) -> FieldCode -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FieldCode -> CInt
forall a. ToCInt a => a -> CInt
toCInt
instance Enum Verbosity where
toEnum :: Int -> Verbosity
toEnum = Verbosity -> Maybe Verbosity -> Verbosity
forall a. a -> Maybe a -> a
fromMaybe (String -> Verbosity
forall a. HasCallStack => String -> a
error String
"toEnum @Database.PostgreSQL.LibPQ.Verbosity") (Maybe Verbosity -> Verbosity)
-> (Int -> Maybe Verbosity) -> Int -> Verbosity
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CInt -> Maybe Verbosity
forall a. FromCInt a => CInt -> Maybe a
fromCInt (CInt -> Maybe Verbosity)
-> (Int -> CInt) -> Int -> Maybe Verbosity
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> CInt
forall a. Enum a => Int -> a
toEnum
fromEnum :: Verbosity -> Int
fromEnum = CInt -> Int
forall a. Enum a => a -> Int
fromEnum (CInt -> Int) -> (Verbosity -> CInt) -> Verbosity -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Verbosity -> CInt
forall a. ToCInt a => a -> CInt
toCInt