{-# 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(..))

-------------------------------------------------------------------------------
-- Type classes
-------------------------------------------------------------------------------

class ToCInt a where
  toCInt   :: a -> CInt

class FromCInt a where
  fromCInt :: CInt -> Maybe a

-------------------------------------------------------------------------------
-- Enumerations
-------------------------------------------------------------------------------

data ExecStatus
    = EmptyQuery    -- ^ The string sent to the server was empty.
    | CommandOk     -- ^ Successful completion of a
                    -- command returning no data.
    | TuplesOk      -- ^ Successful completion of a
                    -- command returning data (such as a
                    -- SELECT or SHOW).
    | CopyOut       -- ^ Copy Out (from server) data
                    -- transfer started.
    | CopyIn        -- ^ Copy In (to server) data transfer
                    -- started.
    | CopyBoth      -- ^ Copy In/Out data transfer started.
    | BadResponse   -- ^ The server's response was not understood.
    | NonfatalError -- ^ A nonfatal error (a notice or
                    -- warning) occurred.
    | FatalError    -- ^ A fatal error occurred.
    | SingleTuple   -- ^ The PGresult contains a single result tuple
                    -- from the current command. This status occurs
                    -- only when single-row mode has been selected
                    -- for the query.
  deriving (ExecStatus -> ExecStatus -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ExecStatus -> ExecStatus -> Bool
$c/= :: ExecStatus -> ExecStatus -> Bool
== :: ExecStatus -> ExecStatus -> Bool
$c== :: ExecStatus -> ExecStatus -> Bool
Eq, Int -> ExecStatus -> ShowS
[ExecStatus] -> ShowS
ExecStatus -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ExecStatus] -> ShowS
$cshowList :: [ExecStatus] -> ShowS
show :: ExecStatus -> String
$cshow :: ExecStatus -> String
showsPrec :: Int -> ExecStatus -> ShowS
$cshowsPrec :: Int -> ExecStatus -> ShowS
Show)

instance FromCInt ExecStatus where
    fromCInt :: CInt -> Maybe ExecStatus
fromCInt (CInt
0)    = 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
    -- ^ The severity; the field contents are ERROR, FATAL,
    -- or PANIC (in an error message), or WARNING, NOTICE,
    -- DEBUG, INFO, or LOG (in a notice message), or a
    -- localized translation of one of these. Always
    -- present.

    | DiagSqlstate
    -- ^ The SQLSTATE code for the error. The SQLSTATE code
    -- identifies the type of error that has occurred; it
    -- can be used by front-end applications to perform
    -- specific operations (such as error handling) in
    -- response to a particular database error. For a list
    -- of the possible SQLSTATE codes, see Appendix A. This
    -- field is not localizable, and is always present.

    | DiagMessagePrimary
    -- ^ The primary human-readable error message
    -- (typically one line). Always present.

    | DiagMessageDetail
    -- ^ Detail: an optional secondary error message
    -- carrying more detail about the problem. Might run to
    -- multiple lines.

    | DiagMessageHint
    -- ^ Hint: an optional suggestion what to do about the
    -- problem. This is intended to differ from detail in
    -- that it offers advice (potentially inappropriate)
    -- rather than hard facts. Might run to multiple lines.

    | DiagStatementPosition
    -- ^ A string containing a decimal integer indicating
    -- an error cursor position as an index into the
    -- original statement string. The first character has
    -- index 1, and positions are measured in characters
    -- not bytes.

    | DiagInternalPosition
    -- ^ This is defined the same as the
    -- 'DiagStatementPosition' field, but it is used when
    -- the cursor position refers to an internally
    -- generated command rather than the one submitted by
    -- the client. The 'DiagInternalQuery' field will
    -- always appear when this field appears.

    | DiagInternalQuery
    -- ^ The text of a failed internally-generated
    -- command. This could be, for example, a SQL query
    -- issued by a PL/pgSQL function.

    | DiagContext
    -- ^ An indication of the context in which the error
    -- occurred. Presently this includes a call stack
    -- traceback of active procedural language functions
    -- and internally-generated queries. The trace is one
    -- entry per line, most recent first.

    | DiagSourceFile
    -- ^ The file name of the source-code location where
    -- the error was reported.

    | DiagSourceLine
    -- ^ The line number of the source-code location where
    -- the error was reported.

    | DiagSourceFunction
    -- ^ The name of the source-code function reporting the
    -- error.

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

instance FromCInt FieldCode where
    fromCInt :: CInt -> Maybe FieldCode
fromCInt (CInt
83)           = 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
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Verbosity -> Verbosity -> Bool
$c/= :: Verbosity -> Verbosity -> Bool
== :: Verbosity -> Verbosity -> Bool
$c== :: Verbosity -> Verbosity -> Bool
Eq, Int -> Verbosity -> ShowS
[Verbosity] -> ShowS
Verbosity -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Verbosity] -> ShowS
$cshowList :: [Verbosity] -> ShowS
show :: Verbosity -> String
$cshow :: Verbosity -> String
showsPrec :: Int -> Verbosity -> ShowS
$cshowsPrec :: Int -> Verbosity -> ShowS
Show)

instance FromCInt Verbosity where
    fromCInt :: CInt -> Maybe Verbosity
fromCInt (CInt
0)   = 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
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PollingStatus -> PollingStatus -> Bool
$c/= :: PollingStatus -> PollingStatus -> Bool
== :: PollingStatus -> PollingStatus -> Bool
$c== :: PollingStatus -> PollingStatus -> Bool
Eq, Int -> PollingStatus -> ShowS
[PollingStatus] -> ShowS
PollingStatus -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PollingStatus] -> ShowS
$cshowList :: [PollingStatus] -> ShowS
show :: PollingStatus -> String
$cshow :: PollingStatus -> String
showsPrec :: Int -> PollingStatus -> ShowS
$cshowsPrec :: Int -> PollingStatus -> ShowS
Show)

instance FromCInt PollingStatus where
    fromCInt :: CInt -> Maybe PollingStatus
fromCInt (CInt
1) = 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                 -- ^ The 'Connection' is ready.
    | ConnectionBad                -- ^ The connection procedure has failed.
    | ConnectionStarted            -- ^ Waiting for connection to be made.
    | ConnectionMade               -- ^ Connection OK; waiting to send.
    | ConnectionAwaitingResponse   -- ^ Waiting for a response from the server.
    | ConnectionAuthOk             -- ^ Received authentication;
                                   -- waiting for backend start-up to
                                   -- finish.
    | ConnectionSetEnv             -- ^ Negotiating environment-driven
                                   -- parameter settings.
    | ConnectionSSLStartup         -- ^ Negotiating SSL encryption.
  deriving (ConnStatus -> ConnStatus -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ConnStatus -> ConnStatus -> Bool
$c/= :: ConnStatus -> ConnStatus -> Bool
== :: ConnStatus -> ConnStatus -> Bool
$c== :: ConnStatus -> ConnStatus -> Bool
Eq, Int -> ConnStatus -> ShowS
[ConnStatus] -> ShowS
ConnStatus -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ConnStatus] -> ShowS
$cshowList :: [ConnStatus] -> ShowS
show :: ConnStatus -> String
$cshow :: ConnStatus -> String
showsPrec :: Int -> ConnStatus -> ShowS
$cshowsPrec :: Int -> ConnStatus -> ShowS
Show)

instance FromCInt ConnStatus where
    fromCInt :: CInt -> Maybe ConnStatus
fromCInt (CInt
0)                = 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 (#const CONNECTION_NEEDED)         = return ConnectionNeeded
    fromCInt CInt
_ = forall a. Maybe a
Nothing
    

data TransactionStatus
    = TransIdle    -- ^ currently idle
    | TransActive  -- ^ a command is in progress
    | TransInTrans -- ^ idle, in a valid transaction block
    | TransInError -- ^ idle, in a failed transaction block
    | TransUnknown -- ^ the connection is bad
  deriving (TransactionStatus -> TransactionStatus -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TransactionStatus -> TransactionStatus -> Bool
$c/= :: TransactionStatus -> TransactionStatus -> Bool
== :: TransactionStatus -> TransactionStatus -> Bool
$c== :: TransactionStatus -> TransactionStatus -> Bool
Eq, Int -> TransactionStatus -> ShowS
[TransactionStatus] -> ShowS
TransactionStatus -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TransactionStatus] -> ShowS
$cshowList :: [TransactionStatus] -> ShowS
show :: TransactionStatus -> String
$cshow :: TransactionStatus -> String
showsPrec :: Int -> TransactionStatus -> ShowS
$cshowsPrec :: Int -> TransactionStatus -> ShowS
Show)

instance FromCInt TransactionStatus where
    fromCInt :: CInt -> Maybe TransactionStatus
fromCInt (CInt
0)    = 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
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Format -> Format -> Bool
$c/= :: Format -> Format -> Bool
== :: Format -> Format -> Bool
$c== :: Format -> Format -> Bool
Eq, Eq 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
min :: Format -> Format -> Format
$cmin :: Format -> Format -> Format
max :: Format -> Format -> Format
$cmax :: Format -> Format -> Format
>= :: Format -> Format -> Bool
$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
compare :: Format -> Format -> Ordering
$ccompare :: Format -> Format -> Ordering
Ord, Int -> Format -> ShowS
[Format] -> ShowS
Format -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Format] -> ShowS
$cshowList :: [Format] -> ShowS
show :: Format -> String
$cshow :: Format -> String
showsPrec :: Int -> Format -> ShowS
$cshowsPrec :: Int -> Format -> ShowS
Show, Int -> Format
Format -> Int
Format -> [Format]
Format -> Format
Format -> Format -> [Format]
Format -> Format -> Format -> [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
enumFromThenTo :: Format -> Format -> Format -> [Format]
$cenumFromThenTo :: Format -> Format -> Format -> [Format]
enumFromTo :: Format -> Format -> [Format]
$cenumFromTo :: Format -> Format -> [Format]
enumFromThen :: Format -> Format -> [Format]
$cenumFromThen :: Format -> Format -> [Format]
enumFrom :: Format -> [Format]
$cenumFrom :: Format -> [Format]
fromEnum :: Format -> Int
$cfromEnum :: Format -> Int
toEnum :: Int -> Format
$ctoEnum :: Int -> Format
pred :: Format -> Format
$cpred :: Format -> Format
succ :: Format -> Format
$csucc :: 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 = forall a. a -> Maybe a
Just Format
Text
    fromCInt CInt
1 = forall a. a -> Maybe a
Just Format
Binary
    fromCInt CInt
_ = forall a. Maybe a
Nothing

-------------------------------------------------------------------------------
-- System.IO enumerations
-------------------------------------------------------------------------------

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" #-}

-------------------------------------------------------------------------------
-- Prelude
-------------------------------------------------------------------------------

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 = forall a. a -> Maybe a
Just Bool
False
    fromCInt CInt
1 = forall a. a -> Maybe a
Just Bool
True
    fromCInt CInt
_ = forall a. Maybe a
Nothing

-------------------------------------------------------------------------------
-- Enum instances (for backwards compatibility)
-------------------------------------------------------------------------------

instance Enum ExecStatus where
    toEnum :: Int -> ExecStatus
toEnum   = forall a. a -> Maybe a -> a
fromMaybe (forall a. HasCallStack => String -> a
error String
"toEnum @Database.PostgreSQL.LibPQ.ExecStatus") forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. FromCInt a => CInt -> Maybe a
fromCInt forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Enum a => Int -> a
toEnum
    fromEnum :: ExecStatus -> Int
fromEnum = forall a. Enum a => a -> Int
fromEnum forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ToCInt a => a -> CInt
toCInt

instance Enum FieldCode where
    toEnum :: Int -> FieldCode
toEnum   = forall a. a -> Maybe a -> a
fromMaybe (forall a. HasCallStack => String -> a
error String
"toEnum @Database.PostgreSQL.LibPQ.FieldCode") forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. FromCInt a => CInt -> Maybe a
fromCInt forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Enum a => Int -> a
toEnum
    fromEnum :: FieldCode -> Int
fromEnum = forall a. Enum a => a -> Int
fromEnum forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ToCInt a => a -> CInt
toCInt

instance Enum Verbosity where
    toEnum :: Int -> Verbosity
toEnum   = forall a. a -> Maybe a -> a
fromMaybe (forall a. HasCallStack => String -> a
error String
"toEnum @Database.PostgreSQL.LibPQ.Verbosity") forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. FromCInt a => CInt -> Maybe a
fromCInt forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Enum a => Int -> a
toEnum
    fromEnum :: Verbosity -> Int
fromEnum = forall a. Enum a => a -> Int
fromEnum forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ToCInt a => a -> CInt
toCInt