{-# LINE 1 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}moduleDatabase.PostgreSQL.LibPQ.EnumswhereimportData.Bits((.|.))importData.Maybe(fromMaybe)importForeign.C.Types(CInt(..))importSystem.IO(IOMode(..),SeekMode(..))--------------------------------------------------------------------------------- Type classes-------------------------------------------------------------------------------classToCInt a wheretoCInt ::a ->CIntclassFromCInt a wherefromCInt ::CInt->Maybea --------------------------------------------------------------------------------- Enumerations-------------------------------------------------------------------------------dataExecStatus =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)instanceFromCInt ExecStatus wherefromCInt :: CInt -> Maybe ExecStatus fromCInt (CInt 0)=forall a. a -> Maybe a JustExecStatus EmptyQuery {-# LINE 48 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}fromCInt(1)=JustCommandOk{-# LINE 49 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}fromCInt(2)=JustTuplesOk{-# LINE 50 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}fromCInt(3)=JustCopyOut{-# LINE 51 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}fromCInt(4)=JustCopyIn{-# LINE 52 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}fromCInt(8)=JustCopyBoth{-# LINE 53 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}fromCInt(5)=JustBadResponse{-# LINE 54 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}fromCInt(6)=JustNonfatalError{-# LINE 55 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}fromCInt(7)=JustFatalError{-# LINE 56 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}fromCInt(9)=JustSingleTuple{-# LINE 57 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}fromCInt_=NothinginstanceToCInt ExecStatus wheretoCInt :: ExecStatus -> CInt toCInt ExecStatus EmptyQuery =(CInt 0){-# LINE 61 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}toCIntCommandOk=(1){-# LINE 62 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}toCIntTuplesOk=(2){-# LINE 63 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}toCIntCopyOut=(3){-# LINE 64 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}toCIntCopyIn=(4){-# LINE 65 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}toCIntCopyBoth=(8){-# LINE 66 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}toCIntBadResponse=(5){-# LINE 67 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}toCIntNonfatalError=(6){-# LINE 68 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}toCIntFatalError=(7){-# LINE 69 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}toCIntSingleTuple=(9){-# LINE 70 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}dataFieldCode =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)instanceFromCInt FieldCode wherefromCInt :: CInt -> Maybe FieldCode fromCInt (CInt 83)=forall a. a -> Maybe a JustFieldCode DiagSeverity {-# LINE 147 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}fromCInt(67)=JustDiagSqlstate{-# LINE 148 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}fromCInt(77)=JustDiagMessagePrimary{-# LINE 149 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}fromCInt(68)=JustDiagMessageDetail{-# LINE 150 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}fromCInt(72)=JustDiagMessageHint{-# LINE 151 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}fromCInt(80)=JustDiagStatementPosition{-# LINE 152 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}fromCInt(112)=JustDiagInternalPosition{-# LINE 153 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}fromCInt(113)=JustDiagInternalQuery{-# LINE 154 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}fromCInt(87)=JustDiagContext{-# LINE 155 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}fromCInt(70)=JustDiagSourceFile{-# LINE 156 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}fromCInt(76)=JustDiagSourceLine{-# LINE 157 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}fromCInt(82)=JustDiagSourceFunction{-# LINE 158 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}fromCInt_=NothinginstanceToCInt FieldCode wheretoCInt :: FieldCode -> CInt toCInt FieldCode DiagSeverity =(CInt 83){-# LINE 162 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}toCIntDiagSqlstate=(67){-# LINE 163 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}toCIntDiagMessagePrimary=(77){-# LINE 164 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}toCIntDiagMessageDetail=(68){-# LINE 165 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}toCIntDiagMessageHint=(72){-# LINE 166 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}toCIntDiagStatementPosition=(80){-# LINE 167 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}toCIntDiagInternalPosition=(112){-# LINE 168 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}toCIntDiagInternalQuery=(113){-# LINE 169 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}toCIntDiagContext=(87){-# LINE 170 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}toCIntDiagSourceFile=(70){-# LINE 171 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}toCIntDiagSourceLine=(76){-# LINE 172 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}toCIntDiagSourceFunction=(82){-# LINE 173 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}dataVerbosity =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)instanceFromCInt Verbosity wherefromCInt :: CInt -> Maybe Verbosity fromCInt (CInt 0)=forall a. a -> Maybe a JustVerbosity ErrorsTerse {-# LINE 183 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}fromCInt(1)=JustErrorsDefault{-# LINE 184 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}fromCInt(2)=JustErrorsVerbose{-# LINE 185 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}fromCInt_=NothinginstanceToCInt Verbosity wheretoCInt :: Verbosity -> CInt toCInt Verbosity ErrorsTerse =(CInt 0){-# LINE 189 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}toCIntErrorsDefault=(1){-# LINE 190 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}toCIntErrorsVerbose=(2){-# LINE 191 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}dataPollingStatus =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)instanceFromCInt PollingStatus wherefromCInt :: CInt -> Maybe PollingStatus fromCInt (CInt 1)=forall (m :: * -> *) a. Monad m => a -> m a returnPollingStatus PollingReading {-# LINE 202 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}fromCInt(3)=returnPollingOk{-# LINE 203 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}fromCInt(2)=returnPollingWriting{-# LINE 204 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}fromCInt(0)=returnPollingFailed{-# LINE 205 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}fromCInt_=NothingdataConnStatus =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)instanceFromCInt ConnStatus wherefromCInt :: CInt -> Maybe ConnStatus fromCInt (CInt 0)=forall (m :: * -> *) a. Monad m => a -> m a returnConnStatus ConnectionOk {-# LINE 224 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}fromCInt(1)=returnConnectionBad{-# LINE 225 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}fromCInt(2)=returnConnectionStarted{-# LINE 226 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}fromCInt(3)=returnConnectionMade{-# LINE 227 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}fromCInt(4)=returnConnectionAwaitingResponse{-# LINE 228 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}fromCInt(5)=returnConnectionAuthOk{-# LINE 229 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}fromCInt(6)=returnConnectionSetEnv{-# LINE 230 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}fromCInt(7)=returnConnectionSSLStartup{-# LINE 231 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}-- fromCInt (#const CONNECTION_NEEDED) = return ConnectionNeededfromCInt CInt _=forall a. Maybe a NothingdataTransactionStatus =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 badderiving(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)instanceFromCInt TransactionStatus wherefromCInt :: CInt -> Maybe TransactionStatus fromCInt (CInt 0)=forall (m :: * -> *) a. Monad m => a -> m a returnTransactionStatus TransIdle {-# LINE 245 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}fromCInt(1)=returnTransActive{-# LINE 246 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}fromCInt(2)=returnTransInTrans{-# LINE 247 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}fromCInt(3)=returnTransInError{-# LINE 248 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}fromCInt(4)=returnTransUnknown{-# LINE 249 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}fromCInt_=NothingdataFormat =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)instanceToCInt Format wheretoCInt :: Format -> CInt toCInt Format Text =CInt 0toCInt Format Binary =CInt 1instanceFromCInt Format wherefromCInt :: CInt -> Maybe Format fromCInt CInt 0=forall a. a -> Maybe a JustFormat Text fromCInt CInt 1=forall a. a -> Maybe a JustFormat Binary fromCInt CInt _=forall a. Maybe a Nothing--------------------------------------------------------------------------------- System.IO enumerations-------------------------------------------------------------------------------instanceToCInt IOModewheretoCInt :: IOMode -> CInt toCInt IOMode ReadMode=(CInt 262144){-# LINE 272 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}toCIntWriteMode=(131072){-# LINE 273 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}toCIntReadWriteMode=(262144).|.(131072){-# LINE 274 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}toCIntAppendMode=(131072){-# LINE 275 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}instanceToCInt SeekModewheretoCInt :: SeekMode -> CInt toCInt SeekMode AbsoluteSeek=CInt 0{-# LINE 278 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}toCIntRelativeSeek=1{-# LINE 279 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}toCIntSeekFromEnd=2{-# LINE 280 "src/Database/PostgreSQL/LibPQ/Enums.hsc" #-}--------------------------------------------------------------------------------- Prelude-------------------------------------------------------------------------------instanceToCInt BoolwheretoCInt :: Bool -> CInt toCInt Bool False=CInt 0toCInt Bool True=CInt 1instanceFromCInt BoolwherefromCInt :: CInt -> Maybe Bool fromCInt CInt 0=forall a. a -> Maybe a JustBool FalsefromCInt CInt 1=forall a. a -> Maybe a JustBool TruefromCInt CInt _=forall a. Maybe a Nothing--------------------------------------------------------------------------------- Enum instances (for backwards compatibility)-------------------------------------------------------------------------------instanceEnumExecStatus wheretoEnum :: Int -> ExecStatus toEnum=forall a. a -> Maybe a -> a fromMaybe(forall a. HasCallStack => String -> a errorString "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 toEnumfromEnum :: ExecStatus -> Int fromEnum=forall a. Enum a => a -> Int fromEnumforall b c a. (b -> c) -> (a -> b) -> a -> c .forall a. ToCInt a => a -> CInt toCInt instanceEnumFieldCode wheretoEnum :: Int -> FieldCode toEnum =forall a. a -> Maybe a -> a fromMaybe(forall a. HasCallStack => String -> a errorString "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 toEnumfromEnum :: FieldCode -> Int fromEnum =forall a. Enum a => a -> Int fromEnumforall b c a. (b -> c) -> (a -> b) -> a -> c .forall a. ToCInt a => a -> CInt toCInt instanceEnumVerbosity wheretoEnum :: Int -> Verbosity toEnum =forall a. a -> Maybe a -> a fromMaybe(forall a. HasCallStack => String -> a errorString "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 toEnumfromEnum :: Verbosity -> Int fromEnum =forall a. Enum a => a -> Int fromEnumforall b c a. (b -> c) -> (a -> b) -> a -> c .forall a. ToCInt a => a -> CInt toCInt