#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gio.Enums
    ( 
 
    BusType(..)                             ,
    ConverterResult(..)                     ,
    CredentialsType(..)                     ,
    DBusError(..)                           ,
    catchDBusError                          ,
    handleDBusError                         ,
    DBusMessageByteOrder(..)                ,
    DBusMessageHeaderField(..)              ,
    DBusMessageType(..)                     ,
    DataStreamByteOrder(..)                 ,
    DataStreamNewlineType(..)               ,
    DriveStartStopType(..)                  ,
    EmblemOrigin(..)                        ,
    FileAttributeStatus(..)                 ,
    FileAttributeType(..)                   ,
    FileMonitorEvent(..)                    ,
    FileType(..)                            ,
    FilesystemPreviewType(..)               ,
    IOErrorEnum(..)                         ,
    catchIOErrorEnum                        ,
    handleIOErrorEnum                       ,
    IOModuleScopeFlags(..)                  ,
    MountOperationResult(..)                ,
    NetworkConnectivity(..)                 ,
    NotificationPriority(..)                ,
    PasswordSave(..)                        ,
    PollableReturn(..)                      ,
    ResolverError(..)                       ,
    catchResolverError                      ,
    handleResolverError                     ,
    ResolverRecordType(..)                  ,
    ResourceError(..)                       ,
    catchResourceError                      ,
    handleResourceError                     ,
    SocketClientEvent(..)                   ,
    SocketFamily(..)                        ,
    SocketListenerEvent(..)                 ,
    SocketProtocol(..)                      ,
    SocketType(..)                          ,
    TlsAuthenticationMode(..)               ,
    TlsCertificateRequestFlags(..)          ,
    TlsDatabaseLookupFlags(..)              ,
    TlsError(..)                            ,
    catchTlsError                           ,
    handleTlsError                          ,
    TlsInteractionResult(..)                ,
    TlsRehandshakeMode(..)                  ,
    UnixSocketAddressType(..)               ,
    ZlibCompressorFormat(..)                ,
    ) where
import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P
import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
data ZlibCompressorFormat = 
      ZlibCompressorFormatZlib
    
    | ZlibCompressorFormatGzip
    
    | ZlibCompressorFormatRaw
    
    | AnotherZlibCompressorFormat Int
    
    deriving (Int -> ZlibCompressorFormat -> ShowS
[ZlibCompressorFormat] -> ShowS
ZlibCompressorFormat -> String
(Int -> ZlibCompressorFormat -> ShowS)
-> (ZlibCompressorFormat -> String)
-> ([ZlibCompressorFormat] -> ShowS)
-> Show ZlibCompressorFormat
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ZlibCompressorFormat] -> ShowS
$cshowList :: [ZlibCompressorFormat] -> ShowS
show :: ZlibCompressorFormat -> String
$cshow :: ZlibCompressorFormat -> String
showsPrec :: Int -> ZlibCompressorFormat -> ShowS
$cshowsPrec :: Int -> ZlibCompressorFormat -> ShowS
Show, ZlibCompressorFormat -> ZlibCompressorFormat -> Bool
(ZlibCompressorFormat -> ZlibCompressorFormat -> Bool)
-> (ZlibCompressorFormat -> ZlibCompressorFormat -> Bool)
-> Eq ZlibCompressorFormat
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ZlibCompressorFormat -> ZlibCompressorFormat -> Bool
$c/= :: ZlibCompressorFormat -> ZlibCompressorFormat -> Bool
== :: ZlibCompressorFormat -> ZlibCompressorFormat -> Bool
$c== :: ZlibCompressorFormat -> ZlibCompressorFormat -> Bool
Eq)
instance P.Enum ZlibCompressorFormat where
    fromEnum :: ZlibCompressorFormat -> Int
fromEnum ZlibCompressorFormatZlib = 0
    fromEnum ZlibCompressorFormatGzip = 1
    fromEnum ZlibCompressorFormatRaw = 2
    fromEnum (AnotherZlibCompressorFormat k :: Int
k) = Int
k
    toEnum :: Int -> ZlibCompressorFormat
toEnum 0 = ZlibCompressorFormat
ZlibCompressorFormatZlib
    toEnum 1 = ZlibCompressorFormat
ZlibCompressorFormatGzip
    toEnum 2 = ZlibCompressorFormat
ZlibCompressorFormatRaw
    toEnum k :: Int
k = Int -> ZlibCompressorFormat
AnotherZlibCompressorFormat Int
k
instance P.Ord ZlibCompressorFormat where
    compare :: ZlibCompressorFormat -> ZlibCompressorFormat -> Ordering
compare a :: ZlibCompressorFormat
a b :: ZlibCompressorFormat
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (ZlibCompressorFormat -> Int
forall a. Enum a => a -> Int
P.fromEnum ZlibCompressorFormat
a) (ZlibCompressorFormat -> Int
forall a. Enum a => a -> Int
P.fromEnum ZlibCompressorFormat
b)
foreign import ccall "g_zlib_compressor_format_get_type" c_g_zlib_compressor_format_get_type :: 
    IO GType
instance BoxedEnum ZlibCompressorFormat where
    boxedEnumType :: ZlibCompressorFormat -> IO GType
boxedEnumType _ = IO GType
c_g_zlib_compressor_format_get_type
data UnixSocketAddressType = 
      UnixSocketAddressTypeInvalid
    
    | UnixSocketAddressTypeAnonymous
    
    | UnixSocketAddressTypePath
    
    | UnixSocketAddressTypeAbstract
    
    | UnixSocketAddressTypeAbstractPadded
    
    
    | AnotherUnixSocketAddressType Int
    
    deriving (Int -> UnixSocketAddressType -> ShowS
[UnixSocketAddressType] -> ShowS
UnixSocketAddressType -> String
(Int -> UnixSocketAddressType -> ShowS)
-> (UnixSocketAddressType -> String)
-> ([UnixSocketAddressType] -> ShowS)
-> Show UnixSocketAddressType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UnixSocketAddressType] -> ShowS
$cshowList :: [UnixSocketAddressType] -> ShowS
show :: UnixSocketAddressType -> String
$cshow :: UnixSocketAddressType -> String
showsPrec :: Int -> UnixSocketAddressType -> ShowS
$cshowsPrec :: Int -> UnixSocketAddressType -> ShowS
Show, UnixSocketAddressType -> UnixSocketAddressType -> Bool
(UnixSocketAddressType -> UnixSocketAddressType -> Bool)
-> (UnixSocketAddressType -> UnixSocketAddressType -> Bool)
-> Eq UnixSocketAddressType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UnixSocketAddressType -> UnixSocketAddressType -> Bool
$c/= :: UnixSocketAddressType -> UnixSocketAddressType -> Bool
== :: UnixSocketAddressType -> UnixSocketAddressType -> Bool
$c== :: UnixSocketAddressType -> UnixSocketAddressType -> Bool
Eq)
instance P.Enum UnixSocketAddressType where
    fromEnum :: UnixSocketAddressType -> Int
fromEnum UnixSocketAddressTypeInvalid = 0
    fromEnum UnixSocketAddressTypeAnonymous = 1
    fromEnum UnixSocketAddressTypePath = 2
    fromEnum UnixSocketAddressTypeAbstract = 3
    fromEnum UnixSocketAddressTypeAbstractPadded = 4
    fromEnum (AnotherUnixSocketAddressType k :: Int
k) = Int
k
    toEnum :: Int -> UnixSocketAddressType
toEnum 0 = UnixSocketAddressType
UnixSocketAddressTypeInvalid
    toEnum 1 = UnixSocketAddressType
UnixSocketAddressTypeAnonymous
    toEnum 2 = UnixSocketAddressType
UnixSocketAddressTypePath
    toEnum 3 = UnixSocketAddressType
UnixSocketAddressTypeAbstract
    toEnum 4 = UnixSocketAddressType
UnixSocketAddressTypeAbstractPadded
    toEnum k :: Int
k = Int -> UnixSocketAddressType
AnotherUnixSocketAddressType Int
k
instance P.Ord UnixSocketAddressType where
    compare :: UnixSocketAddressType -> UnixSocketAddressType -> Ordering
compare a :: UnixSocketAddressType
a b :: UnixSocketAddressType
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (UnixSocketAddressType -> Int
forall a. Enum a => a -> Int
P.fromEnum UnixSocketAddressType
a) (UnixSocketAddressType -> Int
forall a. Enum a => a -> Int
P.fromEnum UnixSocketAddressType
b)
foreign import ccall "g_unix_socket_address_type_get_type" c_g_unix_socket_address_type_get_type :: 
    IO GType
instance BoxedEnum UnixSocketAddressType where
    boxedEnumType :: UnixSocketAddressType -> IO GType
boxedEnumType _ = IO GType
c_g_unix_socket_address_type_get_type
{-# DEPRECATED TlsRehandshakeMode ["(Since version 2.60.)","Changing the rehandshake mode is no longer","  required for compatibility. Also, rehandshaking has been removed","  from the TLS protocol in TLS 1.3."] #-}
data TlsRehandshakeMode = 
      TlsRehandshakeModeNever
    
    | TlsRehandshakeModeSafely
    
    | TlsRehandshakeModeUnsafely
    
    | AnotherTlsRehandshakeMode Int
    
    deriving (Int -> TlsRehandshakeMode -> ShowS
[TlsRehandshakeMode] -> ShowS
TlsRehandshakeMode -> String
(Int -> TlsRehandshakeMode -> ShowS)
-> (TlsRehandshakeMode -> String)
-> ([TlsRehandshakeMode] -> ShowS)
-> Show TlsRehandshakeMode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TlsRehandshakeMode] -> ShowS
$cshowList :: [TlsRehandshakeMode] -> ShowS
show :: TlsRehandshakeMode -> String
$cshow :: TlsRehandshakeMode -> String
showsPrec :: Int -> TlsRehandshakeMode -> ShowS
$cshowsPrec :: Int -> TlsRehandshakeMode -> ShowS
Show, TlsRehandshakeMode -> TlsRehandshakeMode -> Bool
(TlsRehandshakeMode -> TlsRehandshakeMode -> Bool)
-> (TlsRehandshakeMode -> TlsRehandshakeMode -> Bool)
-> Eq TlsRehandshakeMode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TlsRehandshakeMode -> TlsRehandshakeMode -> Bool
$c/= :: TlsRehandshakeMode -> TlsRehandshakeMode -> Bool
== :: TlsRehandshakeMode -> TlsRehandshakeMode -> Bool
$c== :: TlsRehandshakeMode -> TlsRehandshakeMode -> Bool
Eq)
instance P.Enum TlsRehandshakeMode where
    fromEnum :: TlsRehandshakeMode -> Int
fromEnum TlsRehandshakeModeNever = 0
    fromEnum TlsRehandshakeModeSafely = 1
    fromEnum TlsRehandshakeModeUnsafely = 2
    fromEnum (AnotherTlsRehandshakeMode k :: Int
k) = Int
k
    toEnum :: Int -> TlsRehandshakeMode
toEnum 0 = TlsRehandshakeMode
TlsRehandshakeModeNever
    toEnum 1 = TlsRehandshakeMode
TlsRehandshakeModeSafely
    toEnum 2 = TlsRehandshakeMode
TlsRehandshakeModeUnsafely
    toEnum k :: Int
k = Int -> TlsRehandshakeMode
AnotherTlsRehandshakeMode Int
k
instance P.Ord TlsRehandshakeMode where
    compare :: TlsRehandshakeMode -> TlsRehandshakeMode -> Ordering
compare a :: TlsRehandshakeMode
a b :: TlsRehandshakeMode
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (TlsRehandshakeMode -> Int
forall a. Enum a => a -> Int
P.fromEnum TlsRehandshakeMode
a) (TlsRehandshakeMode -> Int
forall a. Enum a => a -> Int
P.fromEnum TlsRehandshakeMode
b)
foreign import ccall "g_tls_rehandshake_mode_get_type" c_g_tls_rehandshake_mode_get_type :: 
    IO GType
instance BoxedEnum TlsRehandshakeMode where
    boxedEnumType :: TlsRehandshakeMode -> IO GType
boxedEnumType _ = IO GType
c_g_tls_rehandshake_mode_get_type
data TlsInteractionResult = 
      TlsInteractionResultUnhandled
    
    
    | TlsInteractionResultHandled
    
    
    | TlsInteractionResultFailed
    
    
    | AnotherTlsInteractionResult Int
    
    deriving (Int -> TlsInteractionResult -> ShowS
[TlsInteractionResult] -> ShowS
TlsInteractionResult -> String
(Int -> TlsInteractionResult -> ShowS)
-> (TlsInteractionResult -> String)
-> ([TlsInteractionResult] -> ShowS)
-> Show TlsInteractionResult
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TlsInteractionResult] -> ShowS
$cshowList :: [TlsInteractionResult] -> ShowS
show :: TlsInteractionResult -> String
$cshow :: TlsInteractionResult -> String
showsPrec :: Int -> TlsInteractionResult -> ShowS
$cshowsPrec :: Int -> TlsInteractionResult -> ShowS
Show, TlsInteractionResult -> TlsInteractionResult -> Bool
(TlsInteractionResult -> TlsInteractionResult -> Bool)
-> (TlsInteractionResult -> TlsInteractionResult -> Bool)
-> Eq TlsInteractionResult
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TlsInteractionResult -> TlsInteractionResult -> Bool
$c/= :: TlsInteractionResult -> TlsInteractionResult -> Bool
== :: TlsInteractionResult -> TlsInteractionResult -> Bool
$c== :: TlsInteractionResult -> TlsInteractionResult -> Bool
Eq)
instance P.Enum TlsInteractionResult where
    fromEnum :: TlsInteractionResult -> Int
fromEnum TlsInteractionResultUnhandled = 0
    fromEnum TlsInteractionResultHandled = 1
    fromEnum TlsInteractionResultFailed = 2
    fromEnum (AnotherTlsInteractionResult k :: Int
k) = Int
k
    toEnum :: Int -> TlsInteractionResult
toEnum 0 = TlsInteractionResult
TlsInteractionResultUnhandled
    toEnum 1 = TlsInteractionResult
TlsInteractionResultHandled
    toEnum 2 = TlsInteractionResult
TlsInteractionResultFailed
    toEnum k :: Int
k = Int -> TlsInteractionResult
AnotherTlsInteractionResult Int
k
instance P.Ord TlsInteractionResult where
    compare :: TlsInteractionResult -> TlsInteractionResult -> Ordering
compare a :: TlsInteractionResult
a b :: TlsInteractionResult
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (TlsInteractionResult -> Int
forall a. Enum a => a -> Int
P.fromEnum TlsInteractionResult
a) (TlsInteractionResult -> Int
forall a. Enum a => a -> Int
P.fromEnum TlsInteractionResult
b)
foreign import ccall "g_tls_interaction_result_get_type" c_g_tls_interaction_result_get_type :: 
    IO GType
instance BoxedEnum TlsInteractionResult where
    boxedEnumType :: TlsInteractionResult -> IO GType
boxedEnumType _ = IO GType
c_g_tls_interaction_result_get_type
data TlsError = 
      TlsErrorUnavailable
    
    | TlsErrorMisc
    
    | TlsErrorBadCertificate
    
    
    | TlsErrorNotTls
    
    
    | TlsErrorHandshake
    
    
    | TlsErrorCertificateRequired
    
    
    
    | TlsErrorEof
    
    
    
    | TlsErrorInappropriateFallback
    
    
    
    | AnotherTlsError Int
    
    deriving (Int -> TlsError -> ShowS
[TlsError] -> ShowS
TlsError -> String
(Int -> TlsError -> ShowS)
-> (TlsError -> String) -> ([TlsError] -> ShowS) -> Show TlsError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TlsError] -> ShowS
$cshowList :: [TlsError] -> ShowS
show :: TlsError -> String
$cshow :: TlsError -> String
showsPrec :: Int -> TlsError -> ShowS
$cshowsPrec :: Int -> TlsError -> ShowS
Show, TlsError -> TlsError -> Bool
(TlsError -> TlsError -> Bool)
-> (TlsError -> TlsError -> Bool) -> Eq TlsError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TlsError -> TlsError -> Bool
$c/= :: TlsError -> TlsError -> Bool
== :: TlsError -> TlsError -> Bool
$c== :: TlsError -> TlsError -> Bool
Eq)
instance P.Enum TlsError where
    fromEnum :: TlsError -> Int
fromEnum TlsErrorUnavailable = 0
    fromEnum TlsErrorMisc = 1
    fromEnum TlsErrorBadCertificate = 2
    fromEnum TlsErrorNotTls = 3
    fromEnum TlsErrorHandshake = 4
    fromEnum TlsErrorCertificateRequired = 5
    fromEnum TlsErrorEof = 6
    fromEnum TlsErrorInappropriateFallback = 7
    fromEnum (AnotherTlsError k :: Int
k) = Int
k
    toEnum :: Int -> TlsError
toEnum 0 = TlsError
TlsErrorUnavailable
    toEnum 1 = TlsError
TlsErrorMisc
    toEnum 2 = TlsError
TlsErrorBadCertificate
    toEnum 3 = TlsError
TlsErrorNotTls
    toEnum 4 = TlsError
TlsErrorHandshake
    toEnum 5 = TlsError
TlsErrorCertificateRequired
    toEnum 6 = TlsError
TlsErrorEof
    toEnum 7 = TlsError
TlsErrorInappropriateFallback
    toEnum k :: Int
k = Int -> TlsError
AnotherTlsError Int
k
instance P.Ord TlsError where
    compare :: TlsError -> TlsError -> Ordering
compare a :: TlsError
a b :: TlsError
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (TlsError -> Int
forall a. Enum a => a -> Int
P.fromEnum TlsError
a) (TlsError -> Int
forall a. Enum a => a -> Int
P.fromEnum TlsError
b)
instance GErrorClass TlsError where
    gerrorClassDomain :: TlsError -> Text
gerrorClassDomain _ = "g-tls-error-quark"
catchTlsError ::
    IO a ->
    (TlsError -> GErrorMessage -> IO a) ->
    IO a
catchTlsError :: IO a -> (TlsError -> Text -> IO a) -> IO a
catchTlsError = IO a -> (TlsError -> Text -> IO a) -> IO a
forall err a.
GErrorClass err =>
IO a -> (err -> Text -> IO a) -> IO a
catchGErrorJustDomain
handleTlsError ::
    (TlsError -> GErrorMessage -> IO a) ->
    IO a ->
    IO a
handleTlsError :: (TlsError -> Text -> IO a) -> IO a -> IO a
handleTlsError = (TlsError -> Text -> IO a) -> IO a -> IO a
forall err a.
GErrorClass err =>
(err -> Text -> IO a) -> IO a -> IO a
handleGErrorJustDomain
foreign import ccall "g_tls_error_get_type" c_g_tls_error_get_type :: 
    IO GType
instance BoxedEnum TlsError where
    boxedEnumType :: TlsError -> IO GType
boxedEnumType _ = IO GType
c_g_tls_error_get_type
data TlsDatabaseLookupFlags = 
      TlsDatabaseLookupFlagsNone
    
    | TlsDatabaseLookupFlagsKeypair
    
    
    | AnotherTlsDatabaseLookupFlags Int
    
    deriving (Int -> TlsDatabaseLookupFlags -> ShowS
[TlsDatabaseLookupFlags] -> ShowS
TlsDatabaseLookupFlags -> String
(Int -> TlsDatabaseLookupFlags -> ShowS)
-> (TlsDatabaseLookupFlags -> String)
-> ([TlsDatabaseLookupFlags] -> ShowS)
-> Show TlsDatabaseLookupFlags
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TlsDatabaseLookupFlags] -> ShowS
$cshowList :: [TlsDatabaseLookupFlags] -> ShowS
show :: TlsDatabaseLookupFlags -> String
$cshow :: TlsDatabaseLookupFlags -> String
showsPrec :: Int -> TlsDatabaseLookupFlags -> ShowS
$cshowsPrec :: Int -> TlsDatabaseLookupFlags -> ShowS
Show, TlsDatabaseLookupFlags -> TlsDatabaseLookupFlags -> Bool
(TlsDatabaseLookupFlags -> TlsDatabaseLookupFlags -> Bool)
-> (TlsDatabaseLookupFlags -> TlsDatabaseLookupFlags -> Bool)
-> Eq TlsDatabaseLookupFlags
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TlsDatabaseLookupFlags -> TlsDatabaseLookupFlags -> Bool
$c/= :: TlsDatabaseLookupFlags -> TlsDatabaseLookupFlags -> Bool
== :: TlsDatabaseLookupFlags -> TlsDatabaseLookupFlags -> Bool
$c== :: TlsDatabaseLookupFlags -> TlsDatabaseLookupFlags -> Bool
Eq)
instance P.Enum TlsDatabaseLookupFlags where
    fromEnum :: TlsDatabaseLookupFlags -> Int
fromEnum TlsDatabaseLookupFlagsNone = 0
    fromEnum TlsDatabaseLookupFlagsKeypair = 1
    fromEnum (AnotherTlsDatabaseLookupFlags k :: Int
k) = Int
k
    toEnum :: Int -> TlsDatabaseLookupFlags
toEnum 0 = TlsDatabaseLookupFlags
TlsDatabaseLookupFlagsNone
    toEnum 1 = TlsDatabaseLookupFlags
TlsDatabaseLookupFlagsKeypair
    toEnum k :: Int
k = Int -> TlsDatabaseLookupFlags
AnotherTlsDatabaseLookupFlags Int
k
instance P.Ord TlsDatabaseLookupFlags where
    compare :: TlsDatabaseLookupFlags -> TlsDatabaseLookupFlags -> Ordering
compare a :: TlsDatabaseLookupFlags
a b :: TlsDatabaseLookupFlags
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (TlsDatabaseLookupFlags -> Int
forall a. Enum a => a -> Int
P.fromEnum TlsDatabaseLookupFlags
a) (TlsDatabaseLookupFlags -> Int
forall a. Enum a => a -> Int
P.fromEnum TlsDatabaseLookupFlags
b)
foreign import ccall "g_tls_database_lookup_flags_get_type" c_g_tls_database_lookup_flags_get_type :: 
    IO GType
instance BoxedEnum TlsDatabaseLookupFlags where
    boxedEnumType :: TlsDatabaseLookupFlags -> IO GType
boxedEnumType _ = IO GType
c_g_tls_database_lookup_flags_get_type
data TlsCertificateRequestFlags = 
      TlsCertificateRequestFlagsNone
    
    | AnotherTlsCertificateRequestFlags Int
    
    deriving (Int -> TlsCertificateRequestFlags -> ShowS
[TlsCertificateRequestFlags] -> ShowS
TlsCertificateRequestFlags -> String
(Int -> TlsCertificateRequestFlags -> ShowS)
-> (TlsCertificateRequestFlags -> String)
-> ([TlsCertificateRequestFlags] -> ShowS)
-> Show TlsCertificateRequestFlags
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TlsCertificateRequestFlags] -> ShowS
$cshowList :: [TlsCertificateRequestFlags] -> ShowS
show :: TlsCertificateRequestFlags -> String
$cshow :: TlsCertificateRequestFlags -> String
showsPrec :: Int -> TlsCertificateRequestFlags -> ShowS
$cshowsPrec :: Int -> TlsCertificateRequestFlags -> ShowS
Show, TlsCertificateRequestFlags -> TlsCertificateRequestFlags -> Bool
(TlsCertificateRequestFlags -> TlsCertificateRequestFlags -> Bool)
-> (TlsCertificateRequestFlags
    -> TlsCertificateRequestFlags -> Bool)
-> Eq TlsCertificateRequestFlags
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TlsCertificateRequestFlags -> TlsCertificateRequestFlags -> Bool
$c/= :: TlsCertificateRequestFlags -> TlsCertificateRequestFlags -> Bool
== :: TlsCertificateRequestFlags -> TlsCertificateRequestFlags -> Bool
$c== :: TlsCertificateRequestFlags -> TlsCertificateRequestFlags -> Bool
Eq)
instance P.Enum TlsCertificateRequestFlags where
    fromEnum :: TlsCertificateRequestFlags -> Int
fromEnum TlsCertificateRequestFlagsNone = 0
    fromEnum (AnotherTlsCertificateRequestFlags k :: Int
k) = Int
k
    toEnum :: Int -> TlsCertificateRequestFlags
toEnum 0 = TlsCertificateRequestFlags
TlsCertificateRequestFlagsNone
    toEnum k :: Int
k = Int -> TlsCertificateRequestFlags
AnotherTlsCertificateRequestFlags Int
k
instance P.Ord TlsCertificateRequestFlags where
    compare :: TlsCertificateRequestFlags
-> TlsCertificateRequestFlags -> Ordering
compare a :: TlsCertificateRequestFlags
a b :: TlsCertificateRequestFlags
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (TlsCertificateRequestFlags -> Int
forall a. Enum a => a -> Int
P.fromEnum TlsCertificateRequestFlags
a) (TlsCertificateRequestFlags -> Int
forall a. Enum a => a -> Int
P.fromEnum TlsCertificateRequestFlags
b)
foreign import ccall "g_tls_certificate_request_flags_get_type" c_g_tls_certificate_request_flags_get_type :: 
    IO GType
instance BoxedEnum TlsCertificateRequestFlags where
    boxedEnumType :: TlsCertificateRequestFlags -> IO GType
boxedEnumType _ = IO GType
c_g_tls_certificate_request_flags_get_type
data TlsAuthenticationMode = 
      TlsAuthenticationModeNone
    
    | TlsAuthenticationModeRequested
    
    | TlsAuthenticationModeRequired
    
    | AnotherTlsAuthenticationMode Int
    
    deriving (Int -> TlsAuthenticationMode -> ShowS
[TlsAuthenticationMode] -> ShowS
TlsAuthenticationMode -> String
(Int -> TlsAuthenticationMode -> ShowS)
-> (TlsAuthenticationMode -> String)
-> ([TlsAuthenticationMode] -> ShowS)
-> Show TlsAuthenticationMode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TlsAuthenticationMode] -> ShowS
$cshowList :: [TlsAuthenticationMode] -> ShowS
show :: TlsAuthenticationMode -> String
$cshow :: TlsAuthenticationMode -> String
showsPrec :: Int -> TlsAuthenticationMode -> ShowS
$cshowsPrec :: Int -> TlsAuthenticationMode -> ShowS
Show, TlsAuthenticationMode -> TlsAuthenticationMode -> Bool
(TlsAuthenticationMode -> TlsAuthenticationMode -> Bool)
-> (TlsAuthenticationMode -> TlsAuthenticationMode -> Bool)
-> Eq TlsAuthenticationMode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TlsAuthenticationMode -> TlsAuthenticationMode -> Bool
$c/= :: TlsAuthenticationMode -> TlsAuthenticationMode -> Bool
== :: TlsAuthenticationMode -> TlsAuthenticationMode -> Bool
$c== :: TlsAuthenticationMode -> TlsAuthenticationMode -> Bool
Eq)
instance P.Enum TlsAuthenticationMode where
    fromEnum :: TlsAuthenticationMode -> Int
fromEnum TlsAuthenticationModeNone = 0
    fromEnum TlsAuthenticationModeRequested = 1
    fromEnum TlsAuthenticationModeRequired = 2
    fromEnum (AnotherTlsAuthenticationMode k :: Int
k) = Int
k
    toEnum :: Int -> TlsAuthenticationMode
toEnum 0 = TlsAuthenticationMode
TlsAuthenticationModeNone
    toEnum 1 = TlsAuthenticationMode
TlsAuthenticationModeRequested
    toEnum 2 = TlsAuthenticationMode
TlsAuthenticationModeRequired
    toEnum k :: Int
k = Int -> TlsAuthenticationMode
AnotherTlsAuthenticationMode Int
k
instance P.Ord TlsAuthenticationMode where
    compare :: TlsAuthenticationMode -> TlsAuthenticationMode -> Ordering
compare a :: TlsAuthenticationMode
a b :: TlsAuthenticationMode
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (TlsAuthenticationMode -> Int
forall a. Enum a => a -> Int
P.fromEnum TlsAuthenticationMode
a) (TlsAuthenticationMode -> Int
forall a. Enum a => a -> Int
P.fromEnum TlsAuthenticationMode
b)
foreign import ccall "g_tls_authentication_mode_get_type" c_g_tls_authentication_mode_get_type :: 
    IO GType
instance BoxedEnum TlsAuthenticationMode where
    boxedEnumType :: TlsAuthenticationMode -> IO GType
boxedEnumType _ = IO GType
c_g_tls_authentication_mode_get_type
data SocketType = 
      SocketTypeInvalid
    
    | SocketTypeStream
    
    | SocketTypeDatagram
    
    
    | SocketTypeSeqpacket
    
    
    | AnotherSocketType Int
    
    deriving (Int -> SocketType -> ShowS
[SocketType] -> ShowS
SocketType -> String
(Int -> SocketType -> ShowS)
-> (SocketType -> String)
-> ([SocketType] -> ShowS)
-> Show SocketType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SocketType] -> ShowS
$cshowList :: [SocketType] -> ShowS
show :: SocketType -> String
$cshow :: SocketType -> String
showsPrec :: Int -> SocketType -> ShowS
$cshowsPrec :: Int -> SocketType -> ShowS
Show, SocketType -> SocketType -> Bool
(SocketType -> SocketType -> Bool)
-> (SocketType -> SocketType -> Bool) -> Eq SocketType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SocketType -> SocketType -> Bool
$c/= :: SocketType -> SocketType -> Bool
== :: SocketType -> SocketType -> Bool
$c== :: SocketType -> SocketType -> Bool
Eq)
instance P.Enum SocketType where
    fromEnum :: SocketType -> Int
fromEnum SocketTypeInvalid = 0
    fromEnum SocketTypeStream = 1
    fromEnum SocketTypeDatagram = 2
    fromEnum SocketTypeSeqpacket = 3
    fromEnum (AnotherSocketType k :: Int
k) = Int
k
    toEnum :: Int -> SocketType
toEnum 0 = SocketType
SocketTypeInvalid
    toEnum 1 = SocketType
SocketTypeStream
    toEnum 2 = SocketType
SocketTypeDatagram
    toEnum 3 = SocketType
SocketTypeSeqpacket
    toEnum k :: Int
k = Int -> SocketType
AnotherSocketType Int
k
instance P.Ord SocketType where
    compare :: SocketType -> SocketType -> Ordering
compare a :: SocketType
a b :: SocketType
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (SocketType -> Int
forall a. Enum a => a -> Int
P.fromEnum SocketType
a) (SocketType -> Int
forall a. Enum a => a -> Int
P.fromEnum SocketType
b)
foreign import ccall "g_socket_type_get_type" c_g_socket_type_get_type :: 
    IO GType
instance BoxedEnum SocketType where
    boxedEnumType :: SocketType -> IO GType
boxedEnumType _ = IO GType
c_g_socket_type_get_type
data SocketProtocol = 
      SocketProtocolUnknown
    
    | SocketProtocolDefault
    
    | SocketProtocolTcp
    
    | SocketProtocolUdp
    
    | SocketProtocolSctp
    
    | AnotherSocketProtocol Int
    
    deriving (Int -> SocketProtocol -> ShowS
[SocketProtocol] -> ShowS
SocketProtocol -> String
(Int -> SocketProtocol -> ShowS)
-> (SocketProtocol -> String)
-> ([SocketProtocol] -> ShowS)
-> Show SocketProtocol
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SocketProtocol] -> ShowS
$cshowList :: [SocketProtocol] -> ShowS
show :: SocketProtocol -> String
$cshow :: SocketProtocol -> String
showsPrec :: Int -> SocketProtocol -> ShowS
$cshowsPrec :: Int -> SocketProtocol -> ShowS
Show, SocketProtocol -> SocketProtocol -> Bool
(SocketProtocol -> SocketProtocol -> Bool)
-> (SocketProtocol -> SocketProtocol -> Bool) -> Eq SocketProtocol
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SocketProtocol -> SocketProtocol -> Bool
$c/= :: SocketProtocol -> SocketProtocol -> Bool
== :: SocketProtocol -> SocketProtocol -> Bool
$c== :: SocketProtocol -> SocketProtocol -> Bool
Eq)
instance P.Enum SocketProtocol where
    fromEnum :: SocketProtocol -> Int
fromEnum SocketProtocolUnknown = -1
    fromEnum SocketProtocolDefault = 0
    fromEnum SocketProtocolTcp = 6
    fromEnum SocketProtocolUdp = 17
    fromEnum SocketProtocolSctp = 132
    fromEnum (AnotherSocketProtocol k :: Int
k) = Int
k
    toEnum :: Int -> SocketProtocol
toEnum -1 = SocketProtocol
SocketProtocolUnknown
    toEnum 0 = SocketProtocol
SocketProtocolDefault
    toEnum 6 = SocketProtocol
SocketProtocolTcp
    toEnum 17 = SocketProtocol
SocketProtocolUdp
    toEnum 132 = SocketProtocol
SocketProtocolSctp
    toEnum k :: Int
k = Int -> SocketProtocol
AnotherSocketProtocol Int
k
instance P.Ord SocketProtocol where
    compare :: SocketProtocol -> SocketProtocol -> Ordering
compare a :: SocketProtocol
a b :: SocketProtocol
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (SocketProtocol -> Int
forall a. Enum a => a -> Int
P.fromEnum SocketProtocol
a) (SocketProtocol -> Int
forall a. Enum a => a -> Int
P.fromEnum SocketProtocol
b)
foreign import ccall "g_socket_protocol_get_type" c_g_socket_protocol_get_type :: 
    IO GType
instance BoxedEnum SocketProtocol where
    boxedEnumType :: SocketProtocol -> IO GType
boxedEnumType _ = IO GType
c_g_socket_protocol_get_type
data SocketListenerEvent = 
      SocketListenerEventBinding
    
    | SocketListenerEventBound
    
    | SocketListenerEventListening
    
    
    | SocketListenerEventListened
    
    
    | AnotherSocketListenerEvent Int
    
    deriving (Int -> SocketListenerEvent -> ShowS
[SocketListenerEvent] -> ShowS
SocketListenerEvent -> String
(Int -> SocketListenerEvent -> ShowS)
-> (SocketListenerEvent -> String)
-> ([SocketListenerEvent] -> ShowS)
-> Show SocketListenerEvent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SocketListenerEvent] -> ShowS
$cshowList :: [SocketListenerEvent] -> ShowS
show :: SocketListenerEvent -> String
$cshow :: SocketListenerEvent -> String
showsPrec :: Int -> SocketListenerEvent -> ShowS
$cshowsPrec :: Int -> SocketListenerEvent -> ShowS
Show, SocketListenerEvent -> SocketListenerEvent -> Bool
(SocketListenerEvent -> SocketListenerEvent -> Bool)
-> (SocketListenerEvent -> SocketListenerEvent -> Bool)
-> Eq SocketListenerEvent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SocketListenerEvent -> SocketListenerEvent -> Bool
$c/= :: SocketListenerEvent -> SocketListenerEvent -> Bool
== :: SocketListenerEvent -> SocketListenerEvent -> Bool
$c== :: SocketListenerEvent -> SocketListenerEvent -> Bool
Eq)
instance P.Enum SocketListenerEvent where
    fromEnum :: SocketListenerEvent -> Int
fromEnum SocketListenerEventBinding = 0
    fromEnum SocketListenerEventBound = 1
    fromEnum SocketListenerEventListening = 2
    fromEnum SocketListenerEventListened = 3
    fromEnum (AnotherSocketListenerEvent k :: Int
k) = Int
k
    toEnum :: Int -> SocketListenerEvent
toEnum 0 = SocketListenerEvent
SocketListenerEventBinding
    toEnum 1 = SocketListenerEvent
SocketListenerEventBound
    toEnum 2 = SocketListenerEvent
SocketListenerEventListening
    toEnum 3 = SocketListenerEvent
SocketListenerEventListened
    toEnum k :: Int
k = Int -> SocketListenerEvent
AnotherSocketListenerEvent Int
k
instance P.Ord SocketListenerEvent where
    compare :: SocketListenerEvent -> SocketListenerEvent -> Ordering
compare a :: SocketListenerEvent
a b :: SocketListenerEvent
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (SocketListenerEvent -> Int
forall a. Enum a => a -> Int
P.fromEnum SocketListenerEvent
a) (SocketListenerEvent -> Int
forall a. Enum a => a -> Int
P.fromEnum SocketListenerEvent
b)
foreign import ccall "g_socket_listener_event_get_type" c_g_socket_listener_event_get_type :: 
    IO GType
instance BoxedEnum SocketListenerEvent where
    boxedEnumType :: SocketListenerEvent -> IO GType
boxedEnumType _ = IO GType
c_g_socket_listener_event_get_type
data SocketFamily = 
      SocketFamilyInvalid
    
    | SocketFamilyUnix
    
    | SocketFamilyIpv4
    
    | SocketFamilyIpv6
    
    | AnotherSocketFamily Int
    
    deriving (Int -> SocketFamily -> ShowS
[SocketFamily] -> ShowS
SocketFamily -> String
(Int -> SocketFamily -> ShowS)
-> (SocketFamily -> String)
-> ([SocketFamily] -> ShowS)
-> Show SocketFamily
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SocketFamily] -> ShowS
$cshowList :: [SocketFamily] -> ShowS
show :: SocketFamily -> String
$cshow :: SocketFamily -> String
showsPrec :: Int -> SocketFamily -> ShowS
$cshowsPrec :: Int -> SocketFamily -> ShowS
Show, SocketFamily -> SocketFamily -> Bool
(SocketFamily -> SocketFamily -> Bool)
-> (SocketFamily -> SocketFamily -> Bool) -> Eq SocketFamily
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SocketFamily -> SocketFamily -> Bool
$c/= :: SocketFamily -> SocketFamily -> Bool
== :: SocketFamily -> SocketFamily -> Bool
$c== :: SocketFamily -> SocketFamily -> Bool
Eq)
instance P.Enum SocketFamily where
    fromEnum :: SocketFamily -> Int
fromEnum SocketFamilyInvalid = 0
    fromEnum SocketFamilyUnix = 1
    fromEnum SocketFamilyIpv4 = 2
    fromEnum SocketFamilyIpv6 = 10
    fromEnum (AnotherSocketFamily k :: Int
k) = Int
k
    toEnum :: Int -> SocketFamily
toEnum 0 = SocketFamily
SocketFamilyInvalid
    toEnum 1 = SocketFamily
SocketFamilyUnix
    toEnum 2 = SocketFamily
SocketFamilyIpv4
    toEnum 10 = SocketFamily
SocketFamilyIpv6
    toEnum k :: Int
k = Int -> SocketFamily
AnotherSocketFamily Int
k
instance P.Ord SocketFamily where
    compare :: SocketFamily -> SocketFamily -> Ordering
compare a :: SocketFamily
a b :: SocketFamily
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (SocketFamily -> Int
forall a. Enum a => a -> Int
P.fromEnum SocketFamily
a) (SocketFamily -> Int
forall a. Enum a => a -> Int
P.fromEnum SocketFamily
b)
foreign import ccall "g_socket_family_get_type" c_g_socket_family_get_type :: 
    IO GType
instance BoxedEnum SocketFamily where
    boxedEnumType :: SocketFamily -> IO GType
boxedEnumType _ = IO GType
c_g_socket_family_get_type
data SocketClientEvent = 
      SocketClientEventResolving
    
    | SocketClientEventResolved
    
    | SocketClientEventConnecting
    
    
    | SocketClientEventConnected
    
    
    | SocketClientEventProxyNegotiating
    
    
    | SocketClientEventProxyNegotiated
    
    
    | SocketClientEventTlsHandshaking
    
    
    | SocketClientEventTlsHandshaked
    
    
    | SocketClientEventComplete
    
    
    | AnotherSocketClientEvent Int
    
    deriving (Int -> SocketClientEvent -> ShowS
[SocketClientEvent] -> ShowS
SocketClientEvent -> String
(Int -> SocketClientEvent -> ShowS)
-> (SocketClientEvent -> String)
-> ([SocketClientEvent] -> ShowS)
-> Show SocketClientEvent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SocketClientEvent] -> ShowS
$cshowList :: [SocketClientEvent] -> ShowS
show :: SocketClientEvent -> String
$cshow :: SocketClientEvent -> String
showsPrec :: Int -> SocketClientEvent -> ShowS
$cshowsPrec :: Int -> SocketClientEvent -> ShowS
Show, SocketClientEvent -> SocketClientEvent -> Bool
(SocketClientEvent -> SocketClientEvent -> Bool)
-> (SocketClientEvent -> SocketClientEvent -> Bool)
-> Eq SocketClientEvent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SocketClientEvent -> SocketClientEvent -> Bool
$c/= :: SocketClientEvent -> SocketClientEvent -> Bool
== :: SocketClientEvent -> SocketClientEvent -> Bool
$c== :: SocketClientEvent -> SocketClientEvent -> Bool
Eq)
instance P.Enum SocketClientEvent where
    fromEnum :: SocketClientEvent -> Int
fromEnum SocketClientEventResolving = 0
    fromEnum SocketClientEventResolved = 1
    fromEnum SocketClientEventConnecting = 2
    fromEnum SocketClientEventConnected = 3
    fromEnum SocketClientEventProxyNegotiating = 4
    fromEnum SocketClientEventProxyNegotiated = 5
    fromEnum SocketClientEventTlsHandshaking = 6
    fromEnum SocketClientEventTlsHandshaked = 7
    fromEnum SocketClientEventComplete = 8
    fromEnum (AnotherSocketClientEvent k :: Int
k) = Int
k
    toEnum :: Int -> SocketClientEvent
toEnum 0 = SocketClientEvent
SocketClientEventResolving
    toEnum 1 = SocketClientEvent
SocketClientEventResolved
    toEnum 2 = SocketClientEvent
SocketClientEventConnecting
    toEnum 3 = SocketClientEvent
SocketClientEventConnected
    toEnum 4 = SocketClientEvent
SocketClientEventProxyNegotiating
    toEnum 5 = SocketClientEvent
SocketClientEventProxyNegotiated
    toEnum 6 = SocketClientEvent
SocketClientEventTlsHandshaking
    toEnum 7 = SocketClientEvent
SocketClientEventTlsHandshaked
    toEnum 8 = SocketClientEvent
SocketClientEventComplete
    toEnum k :: Int
k = Int -> SocketClientEvent
AnotherSocketClientEvent Int
k
instance P.Ord SocketClientEvent where
    compare :: SocketClientEvent -> SocketClientEvent -> Ordering
compare a :: SocketClientEvent
a b :: SocketClientEvent
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (SocketClientEvent -> Int
forall a. Enum a => a -> Int
P.fromEnum SocketClientEvent
a) (SocketClientEvent -> Int
forall a. Enum a => a -> Int
P.fromEnum SocketClientEvent
b)
foreign import ccall "g_socket_client_event_get_type" c_g_socket_client_event_get_type :: 
    IO GType
instance BoxedEnum SocketClientEvent where
    boxedEnumType :: SocketClientEvent -> IO GType
boxedEnumType _ = IO GType
c_g_socket_client_event_get_type
data ResourceError = 
      ResourceErrorNotFound
    
    | ResourceErrorInternal
    
    | AnotherResourceError Int
    
    deriving (Int -> ResourceError -> ShowS
[ResourceError] -> ShowS
ResourceError -> String
(Int -> ResourceError -> ShowS)
-> (ResourceError -> String)
-> ([ResourceError] -> ShowS)
-> Show ResourceError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ResourceError] -> ShowS
$cshowList :: [ResourceError] -> ShowS
show :: ResourceError -> String
$cshow :: ResourceError -> String
showsPrec :: Int -> ResourceError -> ShowS
$cshowsPrec :: Int -> ResourceError -> ShowS
Show, ResourceError -> ResourceError -> Bool
(ResourceError -> ResourceError -> Bool)
-> (ResourceError -> ResourceError -> Bool) -> Eq ResourceError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ResourceError -> ResourceError -> Bool
$c/= :: ResourceError -> ResourceError -> Bool
== :: ResourceError -> ResourceError -> Bool
$c== :: ResourceError -> ResourceError -> Bool
Eq)
instance P.Enum ResourceError where
    fromEnum :: ResourceError -> Int
fromEnum ResourceErrorNotFound = 0
    fromEnum ResourceErrorInternal = 1
    fromEnum (AnotherResourceError k :: Int
k) = Int
k
    toEnum :: Int -> ResourceError
toEnum 0 = ResourceError
ResourceErrorNotFound
    toEnum 1 = ResourceError
ResourceErrorInternal
    toEnum k :: Int
k = Int -> ResourceError
AnotherResourceError Int
k
instance P.Ord ResourceError where
    compare :: ResourceError -> ResourceError -> Ordering
compare a :: ResourceError
a b :: ResourceError
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (ResourceError -> Int
forall a. Enum a => a -> Int
P.fromEnum ResourceError
a) (ResourceError -> Int
forall a. Enum a => a -> Int
P.fromEnum ResourceError
b)
instance GErrorClass ResourceError where
    gerrorClassDomain :: ResourceError -> Text
gerrorClassDomain _ = "g-resource-error-quark"
catchResourceError ::
    IO a ->
    (ResourceError -> GErrorMessage -> IO a) ->
    IO a
catchResourceError :: IO a -> (ResourceError -> Text -> IO a) -> IO a
catchResourceError = IO a -> (ResourceError -> Text -> IO a) -> IO a
forall err a.
GErrorClass err =>
IO a -> (err -> Text -> IO a) -> IO a
catchGErrorJustDomain
handleResourceError ::
    (ResourceError -> GErrorMessage -> IO a) ->
    IO a ->
    IO a
handleResourceError :: (ResourceError -> Text -> IO a) -> IO a -> IO a
handleResourceError = (ResourceError -> Text -> IO a) -> IO a -> IO a
forall err a.
GErrorClass err =>
(err -> Text -> IO a) -> IO a -> IO a
handleGErrorJustDomain
foreign import ccall "g_resource_error_get_type" c_g_resource_error_get_type :: 
    IO GType
instance BoxedEnum ResourceError where
    boxedEnumType :: ResourceError -> IO GType
boxedEnumType _ = IO GType
c_g_resource_error_get_type
data ResolverRecordType = 
      ResolverRecordTypeSrv
    
    | ResolverRecordTypeMx
    
    | ResolverRecordTypeTxt
    
    | ResolverRecordTypeSoa
    
    | ResolverRecordTypeNs
    
    | AnotherResolverRecordType Int
    
    deriving (Int -> ResolverRecordType -> ShowS
[ResolverRecordType] -> ShowS
ResolverRecordType -> String
(Int -> ResolverRecordType -> ShowS)
-> (ResolverRecordType -> String)
-> ([ResolverRecordType] -> ShowS)
-> Show ResolverRecordType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ResolverRecordType] -> ShowS
$cshowList :: [ResolverRecordType] -> ShowS
show :: ResolverRecordType -> String
$cshow :: ResolverRecordType -> String
showsPrec :: Int -> ResolverRecordType -> ShowS
$cshowsPrec :: Int -> ResolverRecordType -> ShowS
Show, ResolverRecordType -> ResolverRecordType -> Bool
(ResolverRecordType -> ResolverRecordType -> Bool)
-> (ResolverRecordType -> ResolverRecordType -> Bool)
-> Eq ResolverRecordType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ResolverRecordType -> ResolverRecordType -> Bool
$c/= :: ResolverRecordType -> ResolverRecordType -> Bool
== :: ResolverRecordType -> ResolverRecordType -> Bool
$c== :: ResolverRecordType -> ResolverRecordType -> Bool
Eq)
instance P.Enum ResolverRecordType where
    fromEnum :: ResolverRecordType -> Int
fromEnum ResolverRecordTypeSrv = 1
    fromEnum ResolverRecordTypeMx = 2
    fromEnum ResolverRecordTypeTxt = 3
    fromEnum ResolverRecordTypeSoa = 4
    fromEnum ResolverRecordTypeNs = 5
    fromEnum (AnotherResolverRecordType k :: Int
k) = Int
k
    toEnum :: Int -> ResolverRecordType
toEnum 1 = ResolverRecordType
ResolverRecordTypeSrv
    toEnum 2 = ResolverRecordType
ResolverRecordTypeMx
    toEnum 3 = ResolverRecordType
ResolverRecordTypeTxt
    toEnum 4 = ResolverRecordType
ResolverRecordTypeSoa
    toEnum 5 = ResolverRecordType
ResolverRecordTypeNs
    toEnum k :: Int
k = Int -> ResolverRecordType
AnotherResolverRecordType Int
k
instance P.Ord ResolverRecordType where
    compare :: ResolverRecordType -> ResolverRecordType -> Ordering
compare a :: ResolverRecordType
a b :: ResolverRecordType
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (ResolverRecordType -> Int
forall a. Enum a => a -> Int
P.fromEnum ResolverRecordType
a) (ResolverRecordType -> Int
forall a. Enum a => a -> Int
P.fromEnum ResolverRecordType
b)
foreign import ccall "g_resolver_record_type_get_type" c_g_resolver_record_type_get_type :: 
    IO GType
instance BoxedEnum ResolverRecordType where
    boxedEnumType :: ResolverRecordType -> IO GType
boxedEnumType _ = IO GType
c_g_resolver_record_type_get_type
data ResolverError = 
      ResolverErrorNotFound
    
    
    | ResolverErrorTemporaryFailure
    
    
    | ResolverErrorInternal
    
    | AnotherResolverError Int
    
    deriving (Int -> ResolverError -> ShowS
[ResolverError] -> ShowS
ResolverError -> String
(Int -> ResolverError -> ShowS)
-> (ResolverError -> String)
-> ([ResolverError] -> ShowS)
-> Show ResolverError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ResolverError] -> ShowS
$cshowList :: [ResolverError] -> ShowS
show :: ResolverError -> String
$cshow :: ResolverError -> String
showsPrec :: Int -> ResolverError -> ShowS
$cshowsPrec :: Int -> ResolverError -> ShowS
Show, ResolverError -> ResolverError -> Bool
(ResolverError -> ResolverError -> Bool)
-> (ResolverError -> ResolverError -> Bool) -> Eq ResolverError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ResolverError -> ResolverError -> Bool
$c/= :: ResolverError -> ResolverError -> Bool
== :: ResolverError -> ResolverError -> Bool
$c== :: ResolverError -> ResolverError -> Bool
Eq)
instance P.Enum ResolverError where
    fromEnum :: ResolverError -> Int
fromEnum ResolverErrorNotFound = 0
    fromEnum ResolverErrorTemporaryFailure = 1
    fromEnum ResolverErrorInternal = 2
    fromEnum (AnotherResolverError k :: Int
k) = Int
k
    toEnum :: Int -> ResolverError
toEnum 0 = ResolverError
ResolverErrorNotFound
    toEnum 1 = ResolverError
ResolverErrorTemporaryFailure
    toEnum 2 = ResolverError
ResolverErrorInternal
    toEnum k :: Int
k = Int -> ResolverError
AnotherResolverError Int
k
instance P.Ord ResolverError where
    compare :: ResolverError -> ResolverError -> Ordering
compare a :: ResolverError
a b :: ResolverError
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (ResolverError -> Int
forall a. Enum a => a -> Int
P.fromEnum ResolverError
a) (ResolverError -> Int
forall a. Enum a => a -> Int
P.fromEnum ResolverError
b)
instance GErrorClass ResolverError where
    gerrorClassDomain :: ResolverError -> Text
gerrorClassDomain _ = "g-resolver-error-quark"
catchResolverError ::
    IO a ->
    (ResolverError -> GErrorMessage -> IO a) ->
    IO a
catchResolverError :: IO a -> (ResolverError -> Text -> IO a) -> IO a
catchResolverError = IO a -> (ResolverError -> Text -> IO a) -> IO a
forall err a.
GErrorClass err =>
IO a -> (err -> Text -> IO a) -> IO a
catchGErrorJustDomain
handleResolverError ::
    (ResolverError -> GErrorMessage -> IO a) ->
    IO a ->
    IO a
handleResolverError :: (ResolverError -> Text -> IO a) -> IO a -> IO a
handleResolverError = (ResolverError -> Text -> IO a) -> IO a -> IO a
forall err a.
GErrorClass err =>
(err -> Text -> IO a) -> IO a -> IO a
handleGErrorJustDomain
foreign import ccall "g_resolver_error_get_type" c_g_resolver_error_get_type :: 
    IO GType
instance BoxedEnum ResolverError where
    boxedEnumType :: ResolverError -> IO GType
boxedEnumType _ = IO GType
c_g_resolver_error_get_type
data PollableReturn = 
      PollableReturnFailed
    
    | PollableReturnOk
    
    | PollableReturnWouldBlock
    
    | AnotherPollableReturn Int
    
    deriving (Int -> PollableReturn -> ShowS
[PollableReturn] -> ShowS
PollableReturn -> String
(Int -> PollableReturn -> ShowS)
-> (PollableReturn -> String)
-> ([PollableReturn] -> ShowS)
-> Show PollableReturn
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PollableReturn] -> ShowS
$cshowList :: [PollableReturn] -> ShowS
show :: PollableReturn -> String
$cshow :: PollableReturn -> String
showsPrec :: Int -> PollableReturn -> ShowS
$cshowsPrec :: Int -> PollableReturn -> ShowS
Show, PollableReturn -> PollableReturn -> Bool
(PollableReturn -> PollableReturn -> Bool)
-> (PollableReturn -> PollableReturn -> Bool) -> Eq PollableReturn
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PollableReturn -> PollableReturn -> Bool
$c/= :: PollableReturn -> PollableReturn -> Bool
== :: PollableReturn -> PollableReturn -> Bool
$c== :: PollableReturn -> PollableReturn -> Bool
Eq)
instance P.Enum PollableReturn where
    fromEnum :: PollableReturn -> Int
fromEnum PollableReturnFailed = 0
    fromEnum PollableReturnOk = 1
    fromEnum PollableReturnWouldBlock = -27
    fromEnum (AnotherPollableReturn k :: Int
k) = Int
k
    toEnum :: Int -> PollableReturn
toEnum 0 = PollableReturn
PollableReturnFailed
    toEnum 1 = PollableReturn
PollableReturnOk
    toEnum -27 = PollableReturn
PollableReturnWouldBlock
    toEnum k :: Int
k = Int -> PollableReturn
AnotherPollableReturn Int
k
instance P.Ord PollableReturn where
    compare :: PollableReturn -> PollableReturn -> Ordering
compare a :: PollableReturn
a b :: PollableReturn
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (PollableReturn -> Int
forall a. Enum a => a -> Int
P.fromEnum PollableReturn
a) (PollableReturn -> Int
forall a. Enum a => a -> Int
P.fromEnum PollableReturn
b)
foreign import ccall "g_pollable_return_get_type" c_g_pollable_return_get_type :: 
    IO GType
instance BoxedEnum PollableReturn where
    boxedEnumType :: PollableReturn -> IO GType
boxedEnumType _ = IO GType
c_g_pollable_return_get_type
data PasswordSave = 
      PasswordSaveNever
    
    | PasswordSaveForSession
    
    | PasswordSavePermanently
    
    | AnotherPasswordSave Int
    
    deriving (Int -> PasswordSave -> ShowS
[PasswordSave] -> ShowS
PasswordSave -> String
(Int -> PasswordSave -> ShowS)
-> (PasswordSave -> String)
-> ([PasswordSave] -> ShowS)
-> Show PasswordSave
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PasswordSave] -> ShowS
$cshowList :: [PasswordSave] -> ShowS
show :: PasswordSave -> String
$cshow :: PasswordSave -> String
showsPrec :: Int -> PasswordSave -> ShowS
$cshowsPrec :: Int -> PasswordSave -> ShowS
Show, PasswordSave -> PasswordSave -> Bool
(PasswordSave -> PasswordSave -> Bool)
-> (PasswordSave -> PasswordSave -> Bool) -> Eq PasswordSave
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PasswordSave -> PasswordSave -> Bool
$c/= :: PasswordSave -> PasswordSave -> Bool
== :: PasswordSave -> PasswordSave -> Bool
$c== :: PasswordSave -> PasswordSave -> Bool
Eq)
instance P.Enum PasswordSave where
    fromEnum :: PasswordSave -> Int
fromEnum PasswordSaveNever = 0
    fromEnum PasswordSaveForSession = 1
    fromEnum PasswordSavePermanently = 2
    fromEnum (AnotherPasswordSave k :: Int
k) = Int
k
    toEnum :: Int -> PasswordSave
toEnum 0 = PasswordSave
PasswordSaveNever
    toEnum 1 = PasswordSave
PasswordSaveForSession
    toEnum 2 = PasswordSave
PasswordSavePermanently
    toEnum k :: Int
k = Int -> PasswordSave
AnotherPasswordSave Int
k
instance P.Ord PasswordSave where
    compare :: PasswordSave -> PasswordSave -> Ordering
compare a :: PasswordSave
a b :: PasswordSave
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (PasswordSave -> Int
forall a. Enum a => a -> Int
P.fromEnum PasswordSave
a) (PasswordSave -> Int
forall a. Enum a => a -> Int
P.fromEnum PasswordSave
b)
foreign import ccall "g_password_save_get_type" c_g_password_save_get_type :: 
    IO GType
instance BoxedEnum PasswordSave where
    boxedEnumType :: PasswordSave -> IO GType
boxedEnumType _ = IO GType
c_g_password_save_get_type
data NotificationPriority = 
      NotificationPriorityNormal
    
    
    
    | NotificationPriorityLow
    
    
    
    | NotificationPriorityHigh
    
    
    
    | NotificationPriorityUrgent
    
    
    
    | AnotherNotificationPriority Int
    
    deriving (Int -> NotificationPriority -> ShowS
[NotificationPriority] -> ShowS
NotificationPriority -> String
(Int -> NotificationPriority -> ShowS)
-> (NotificationPriority -> String)
-> ([NotificationPriority] -> ShowS)
-> Show NotificationPriority
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NotificationPriority] -> ShowS
$cshowList :: [NotificationPriority] -> ShowS
show :: NotificationPriority -> String
$cshow :: NotificationPriority -> String
showsPrec :: Int -> NotificationPriority -> ShowS
$cshowsPrec :: Int -> NotificationPriority -> ShowS
Show, NotificationPriority -> NotificationPriority -> Bool
(NotificationPriority -> NotificationPriority -> Bool)
-> (NotificationPriority -> NotificationPriority -> Bool)
-> Eq NotificationPriority
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NotificationPriority -> NotificationPriority -> Bool
$c/= :: NotificationPriority -> NotificationPriority -> Bool
== :: NotificationPriority -> NotificationPriority -> Bool
$c== :: NotificationPriority -> NotificationPriority -> Bool
Eq)
instance P.Enum NotificationPriority where
    fromEnum :: NotificationPriority -> Int
fromEnum NotificationPriorityNormal = 0
    fromEnum NotificationPriorityLow = 1
    fromEnum NotificationPriorityHigh = 2
    fromEnum NotificationPriorityUrgent = 3
    fromEnum (AnotherNotificationPriority k :: Int
k) = Int
k
    toEnum :: Int -> NotificationPriority
toEnum 0 = NotificationPriority
NotificationPriorityNormal
    toEnum 1 = NotificationPriority
NotificationPriorityLow
    toEnum 2 = NotificationPriority
NotificationPriorityHigh
    toEnum 3 = NotificationPriority
NotificationPriorityUrgent
    toEnum k :: Int
k = Int -> NotificationPriority
AnotherNotificationPriority Int
k
instance P.Ord NotificationPriority where
    compare :: NotificationPriority -> NotificationPriority -> Ordering
compare a :: NotificationPriority
a b :: NotificationPriority
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (NotificationPriority -> Int
forall a. Enum a => a -> Int
P.fromEnum NotificationPriority
a) (NotificationPriority -> Int
forall a. Enum a => a -> Int
P.fromEnum NotificationPriority
b)
foreign import ccall "g_notification_priority_get_type" c_g_notification_priority_get_type :: 
    IO GType
instance BoxedEnum NotificationPriority where
    boxedEnumType :: NotificationPriority -> IO GType
boxedEnumType _ = IO GType
c_g_notification_priority_get_type
data NetworkConnectivity = 
      NetworkConnectivityLocal
    
    
    
    | NetworkConnectivityLimited
    
    
    
    | NetworkConnectivityPortal
    
    
    | NetworkConnectivityFull
    
    
    | AnotherNetworkConnectivity Int
    
    deriving (Int -> NetworkConnectivity -> ShowS
[NetworkConnectivity] -> ShowS
NetworkConnectivity -> String
(Int -> NetworkConnectivity -> ShowS)
-> (NetworkConnectivity -> String)
-> ([NetworkConnectivity] -> ShowS)
-> Show NetworkConnectivity
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NetworkConnectivity] -> ShowS
$cshowList :: [NetworkConnectivity] -> ShowS
show :: NetworkConnectivity -> String
$cshow :: NetworkConnectivity -> String
showsPrec :: Int -> NetworkConnectivity -> ShowS
$cshowsPrec :: Int -> NetworkConnectivity -> ShowS
Show, NetworkConnectivity -> NetworkConnectivity -> Bool
(NetworkConnectivity -> NetworkConnectivity -> Bool)
-> (NetworkConnectivity -> NetworkConnectivity -> Bool)
-> Eq NetworkConnectivity
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NetworkConnectivity -> NetworkConnectivity -> Bool
$c/= :: NetworkConnectivity -> NetworkConnectivity -> Bool
== :: NetworkConnectivity -> NetworkConnectivity -> Bool
$c== :: NetworkConnectivity -> NetworkConnectivity -> Bool
Eq)
instance P.Enum NetworkConnectivity where
    fromEnum :: NetworkConnectivity -> Int
fromEnum NetworkConnectivityLocal = 1
    fromEnum NetworkConnectivityLimited = 2
    fromEnum NetworkConnectivityPortal = 3
    fromEnum NetworkConnectivityFull = 4
    fromEnum (AnotherNetworkConnectivity k :: Int
k) = Int
k
    toEnum :: Int -> NetworkConnectivity
toEnum 1 = NetworkConnectivity
NetworkConnectivityLocal
    toEnum 2 = NetworkConnectivity
NetworkConnectivityLimited
    toEnum 3 = NetworkConnectivity
NetworkConnectivityPortal
    toEnum 4 = NetworkConnectivity
NetworkConnectivityFull
    toEnum k :: Int
k = Int -> NetworkConnectivity
AnotherNetworkConnectivity Int
k
instance P.Ord NetworkConnectivity where
    compare :: NetworkConnectivity -> NetworkConnectivity -> Ordering
compare a :: NetworkConnectivity
a b :: NetworkConnectivity
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (NetworkConnectivity -> Int
forall a. Enum a => a -> Int
P.fromEnum NetworkConnectivity
a) (NetworkConnectivity -> Int
forall a. Enum a => a -> Int
P.fromEnum NetworkConnectivity
b)
foreign import ccall "g_network_connectivity_get_type" c_g_network_connectivity_get_type :: 
    IO GType
instance BoxedEnum NetworkConnectivity where
    boxedEnumType :: NetworkConnectivity -> IO GType
boxedEnumType _ = IO GType
c_g_network_connectivity_get_type
data MountOperationResult = 
      MountOperationResultHandled
    
    
    | MountOperationResultAborted
    
    
    | MountOperationResultUnhandled
    
    
    | AnotherMountOperationResult Int
    
    deriving (Int -> MountOperationResult -> ShowS
[MountOperationResult] -> ShowS
MountOperationResult -> String
(Int -> MountOperationResult -> ShowS)
-> (MountOperationResult -> String)
-> ([MountOperationResult] -> ShowS)
-> Show MountOperationResult
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MountOperationResult] -> ShowS
$cshowList :: [MountOperationResult] -> ShowS
show :: MountOperationResult -> String
$cshow :: MountOperationResult -> String
showsPrec :: Int -> MountOperationResult -> ShowS
$cshowsPrec :: Int -> MountOperationResult -> ShowS
Show, MountOperationResult -> MountOperationResult -> Bool
(MountOperationResult -> MountOperationResult -> Bool)
-> (MountOperationResult -> MountOperationResult -> Bool)
-> Eq MountOperationResult
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MountOperationResult -> MountOperationResult -> Bool
$c/= :: MountOperationResult -> MountOperationResult -> Bool
== :: MountOperationResult -> MountOperationResult -> Bool
$c== :: MountOperationResult -> MountOperationResult -> Bool
Eq)
instance P.Enum MountOperationResult where
    fromEnum :: MountOperationResult -> Int
fromEnum MountOperationResultHandled = 0
    fromEnum MountOperationResultAborted = 1
    fromEnum MountOperationResultUnhandled = 2
    fromEnum (AnotherMountOperationResult k :: Int
k) = Int
k
    toEnum :: Int -> MountOperationResult
toEnum 0 = MountOperationResult
MountOperationResultHandled
    toEnum 1 = MountOperationResult
MountOperationResultAborted
    toEnum 2 = MountOperationResult
MountOperationResultUnhandled
    toEnum k :: Int
k = Int -> MountOperationResult
AnotherMountOperationResult Int
k
instance P.Ord MountOperationResult where
    compare :: MountOperationResult -> MountOperationResult -> Ordering
compare a :: MountOperationResult
a b :: MountOperationResult
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (MountOperationResult -> Int
forall a. Enum a => a -> Int
P.fromEnum MountOperationResult
a) (MountOperationResult -> Int
forall a. Enum a => a -> Int
P.fromEnum MountOperationResult
b)
foreign import ccall "g_mount_operation_result_get_type" c_g_mount_operation_result_get_type :: 
    IO GType
instance BoxedEnum MountOperationResult where
    boxedEnumType :: MountOperationResult -> IO GType
boxedEnumType _ = IO GType
c_g_mount_operation_result_get_type
data IOModuleScopeFlags = 
      IOModuleScopeFlagsNone
    
    | IOModuleScopeFlagsBlockDuplicates
    
    
    
    | AnotherIOModuleScopeFlags Int
    
    deriving (Int -> IOModuleScopeFlags -> ShowS
[IOModuleScopeFlags] -> ShowS
IOModuleScopeFlags -> String
(Int -> IOModuleScopeFlags -> ShowS)
-> (IOModuleScopeFlags -> String)
-> ([IOModuleScopeFlags] -> ShowS)
-> Show IOModuleScopeFlags
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [IOModuleScopeFlags] -> ShowS
$cshowList :: [IOModuleScopeFlags] -> ShowS
show :: IOModuleScopeFlags -> String
$cshow :: IOModuleScopeFlags -> String
showsPrec :: Int -> IOModuleScopeFlags -> ShowS
$cshowsPrec :: Int -> IOModuleScopeFlags -> ShowS
Show, IOModuleScopeFlags -> IOModuleScopeFlags -> Bool
(IOModuleScopeFlags -> IOModuleScopeFlags -> Bool)
-> (IOModuleScopeFlags -> IOModuleScopeFlags -> Bool)
-> Eq IOModuleScopeFlags
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IOModuleScopeFlags -> IOModuleScopeFlags -> Bool
$c/= :: IOModuleScopeFlags -> IOModuleScopeFlags -> Bool
== :: IOModuleScopeFlags -> IOModuleScopeFlags -> Bool
$c== :: IOModuleScopeFlags -> IOModuleScopeFlags -> Bool
Eq)
instance P.Enum IOModuleScopeFlags where
    fromEnum :: IOModuleScopeFlags -> Int
fromEnum IOModuleScopeFlagsNone = 0
    fromEnum IOModuleScopeFlagsBlockDuplicates = 1
    fromEnum (AnotherIOModuleScopeFlags k :: Int
k) = Int
k
    toEnum :: Int -> IOModuleScopeFlags
toEnum 0 = IOModuleScopeFlags
IOModuleScopeFlagsNone
    toEnum 1 = IOModuleScopeFlags
IOModuleScopeFlagsBlockDuplicates
    toEnum k :: Int
k = Int -> IOModuleScopeFlags
AnotherIOModuleScopeFlags Int
k
instance P.Ord IOModuleScopeFlags where
    compare :: IOModuleScopeFlags -> IOModuleScopeFlags -> Ordering
compare a :: IOModuleScopeFlags
a b :: IOModuleScopeFlags
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (IOModuleScopeFlags -> Int
forall a. Enum a => a -> Int
P.fromEnum IOModuleScopeFlags
a) (IOModuleScopeFlags -> Int
forall a. Enum a => a -> Int
P.fromEnum IOModuleScopeFlags
b)
foreign import ccall "g_io_module_scope_flags_get_type" c_g_io_module_scope_flags_get_type :: 
    IO GType
instance BoxedEnum IOModuleScopeFlags where
    boxedEnumType :: IOModuleScopeFlags -> IO GType
boxedEnumType _ = IO GType
c_g_io_module_scope_flags_get_type
data IOErrorEnum = 
      IOErrorEnumFailed
    
    
    | IOErrorEnumNotFound
    
    | IOErrorEnumExists
    
    | IOErrorEnumIsDirectory
    
    | IOErrorEnumNotDirectory
    
    | IOErrorEnumNotEmpty
    
    | IOErrorEnumNotRegularFile
    
    | IOErrorEnumNotSymbolicLink
    
    | IOErrorEnumNotMountableFile
    
    | IOErrorEnumFilenameTooLong
    
    | IOErrorEnumInvalidFilename
    
    | IOErrorEnumTooManyLinks
    
    | IOErrorEnumNoSpace
    
    | IOErrorEnumInvalidArgument
    
    | IOErrorEnumPermissionDenied
    
    | IOErrorEnumNotSupported
    
    | IOErrorEnumNotMounted
    
    | IOErrorEnumAlreadyMounted
    
    | IOErrorEnumClosed
    
    | IOErrorEnumCancelled
    
    | IOErrorEnumPending
    
    | IOErrorEnumReadOnly
    
    | IOErrorEnumCantCreateBackup
    
    | IOErrorEnumWrongEtag
    
    | IOErrorEnumTimedOut
    
    | IOErrorEnumWouldRecurse
    
    | IOErrorEnumBusy
    
    | IOErrorEnumWouldBlock
    
    | IOErrorEnumHostNotFound
    
    | IOErrorEnumWouldMerge
    
    | IOErrorEnumFailedHandled
    
    
    | IOErrorEnumTooManyOpenFiles
    
    
    
    | IOErrorEnumNotInitialized
    
    | IOErrorEnumAddressInUse
    
    | IOErrorEnumPartialInput
    
    | IOErrorEnumInvalidData
    
    | IOErrorEnumDbusError
    
    
    
    
    
    | IOErrorEnumHostUnreachable
    
    | IOErrorEnumNetworkUnreachable
    
    | IOErrorEnumConnectionRefused
    
    | IOErrorEnumProxyFailed
    
    | IOErrorEnumProxyAuthFailed
    
    | IOErrorEnumProxyNeedAuth
    
    | IOErrorEnumProxyNotAllowed
    
    
    | IOErrorEnumBrokenPipe
    
    | IOErrorEnumConnectionClosed
    
    
    
    
    
    | IOErrorEnumNotConnected
    
    | IOErrorEnumMessageTooLarge
    
    | AnotherIOErrorEnum Int
    
    deriving (Int -> IOErrorEnum -> ShowS
[IOErrorEnum] -> ShowS
IOErrorEnum -> String
(Int -> IOErrorEnum -> ShowS)
-> (IOErrorEnum -> String)
-> ([IOErrorEnum] -> ShowS)
-> Show IOErrorEnum
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [IOErrorEnum] -> ShowS
$cshowList :: [IOErrorEnum] -> ShowS
show :: IOErrorEnum -> String
$cshow :: IOErrorEnum -> String
showsPrec :: Int -> IOErrorEnum -> ShowS
$cshowsPrec :: Int -> IOErrorEnum -> ShowS
Show, IOErrorEnum -> IOErrorEnum -> Bool
(IOErrorEnum -> IOErrorEnum -> Bool)
-> (IOErrorEnum -> IOErrorEnum -> Bool) -> Eq IOErrorEnum
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IOErrorEnum -> IOErrorEnum -> Bool
$c/= :: IOErrorEnum -> IOErrorEnum -> Bool
== :: IOErrorEnum -> IOErrorEnum -> Bool
$c== :: IOErrorEnum -> IOErrorEnum -> Bool
Eq)
instance P.Enum IOErrorEnum where
    fromEnum :: IOErrorEnum -> Int
fromEnum IOErrorEnumFailed = 0
    fromEnum IOErrorEnumNotFound = 1
    fromEnum IOErrorEnumExists = 2
    fromEnum IOErrorEnumIsDirectory = 3
    fromEnum IOErrorEnumNotDirectory = 4
    fromEnum IOErrorEnumNotEmpty = 5
    fromEnum IOErrorEnumNotRegularFile = 6
    fromEnum IOErrorEnumNotSymbolicLink = 7
    fromEnum IOErrorEnumNotMountableFile = 8
    fromEnum IOErrorEnumFilenameTooLong = 9
    fromEnum IOErrorEnumInvalidFilename = 10
    fromEnum IOErrorEnumTooManyLinks = 11
    fromEnum IOErrorEnumNoSpace = 12
    fromEnum IOErrorEnumInvalidArgument = 13
    fromEnum IOErrorEnumPermissionDenied = 14
    fromEnum IOErrorEnumNotSupported = 15
    fromEnum IOErrorEnumNotMounted = 16
    fromEnum IOErrorEnumAlreadyMounted = 17
    fromEnum IOErrorEnumClosed = 18
    fromEnum IOErrorEnumCancelled = 19
    fromEnum IOErrorEnumPending = 20
    fromEnum IOErrorEnumReadOnly = 21
    fromEnum IOErrorEnumCantCreateBackup = 22
    fromEnum IOErrorEnumWrongEtag = 23
    fromEnum IOErrorEnumTimedOut = 24
    fromEnum IOErrorEnumWouldRecurse = 25
    fromEnum IOErrorEnumBusy = 26
    fromEnum IOErrorEnumWouldBlock = 27
    fromEnum IOErrorEnumHostNotFound = 28
    fromEnum IOErrorEnumWouldMerge = 29
    fromEnum IOErrorEnumFailedHandled = 30
    fromEnum IOErrorEnumTooManyOpenFiles = 31
    fromEnum IOErrorEnumNotInitialized = 32
    fromEnum IOErrorEnumAddressInUse = 33
    fromEnum IOErrorEnumPartialInput = 34
    fromEnum IOErrorEnumInvalidData = 35
    fromEnum IOErrorEnumDbusError = 36
    fromEnum IOErrorEnumHostUnreachable = 37
    fromEnum IOErrorEnumNetworkUnreachable = 38
    fromEnum IOErrorEnumConnectionRefused = 39
    fromEnum IOErrorEnumProxyFailed = 40
    fromEnum IOErrorEnumProxyAuthFailed = 41
    fromEnum IOErrorEnumProxyNeedAuth = 42
    fromEnum IOErrorEnumProxyNotAllowed = 43
    fromEnum IOErrorEnumBrokenPipe = 44
    fromEnum IOErrorEnumConnectionClosed = 44
    fromEnum IOErrorEnumNotConnected = 45
    fromEnum IOErrorEnumMessageTooLarge = 46
    fromEnum (AnotherIOErrorEnum k :: Int
k) = Int
k
    toEnum :: Int -> IOErrorEnum
toEnum 0 = IOErrorEnum
IOErrorEnumFailed
    toEnum 1 = IOErrorEnum
IOErrorEnumNotFound
    toEnum 2 = IOErrorEnum
IOErrorEnumExists
    toEnum 3 = IOErrorEnum
IOErrorEnumIsDirectory
    toEnum 4 = IOErrorEnum
IOErrorEnumNotDirectory
    toEnum 5 = IOErrorEnum
IOErrorEnumNotEmpty
    toEnum 6 = IOErrorEnum
IOErrorEnumNotRegularFile
    toEnum 7 = IOErrorEnum
IOErrorEnumNotSymbolicLink
    toEnum 8 = IOErrorEnum
IOErrorEnumNotMountableFile
    toEnum 9 = IOErrorEnum
IOErrorEnumFilenameTooLong
    toEnum 10 = IOErrorEnum
IOErrorEnumInvalidFilename
    toEnum 11 = IOErrorEnum
IOErrorEnumTooManyLinks
    toEnum 12 = IOErrorEnum
IOErrorEnumNoSpace
    toEnum 13 = IOErrorEnum
IOErrorEnumInvalidArgument
    toEnum 14 = IOErrorEnum
IOErrorEnumPermissionDenied
    toEnum 15 = IOErrorEnum
IOErrorEnumNotSupported
    toEnum 16 = IOErrorEnum
IOErrorEnumNotMounted
    toEnum 17 = IOErrorEnum
IOErrorEnumAlreadyMounted
    toEnum 18 = IOErrorEnum
IOErrorEnumClosed
    toEnum 19 = IOErrorEnum
IOErrorEnumCancelled
    toEnum 20 = IOErrorEnum
IOErrorEnumPending
    toEnum 21 = IOErrorEnum
IOErrorEnumReadOnly
    toEnum 22 = IOErrorEnum
IOErrorEnumCantCreateBackup
    toEnum 23 = IOErrorEnum
IOErrorEnumWrongEtag
    toEnum 24 = IOErrorEnum
IOErrorEnumTimedOut
    toEnum 25 = IOErrorEnum
IOErrorEnumWouldRecurse
    toEnum 26 = IOErrorEnum
IOErrorEnumBusy
    toEnum 27 = IOErrorEnum
IOErrorEnumWouldBlock
    toEnum 28 = IOErrorEnum
IOErrorEnumHostNotFound
    toEnum 29 = IOErrorEnum
IOErrorEnumWouldMerge
    toEnum 30 = IOErrorEnum
IOErrorEnumFailedHandled
    toEnum 31 = IOErrorEnum
IOErrorEnumTooManyOpenFiles
    toEnum 32 = IOErrorEnum
IOErrorEnumNotInitialized
    toEnum 33 = IOErrorEnum
IOErrorEnumAddressInUse
    toEnum 34 = IOErrorEnum
IOErrorEnumPartialInput
    toEnum 35 = IOErrorEnum
IOErrorEnumInvalidData
    toEnum 36 = IOErrorEnum
IOErrorEnumDbusError
    toEnum 37 = IOErrorEnum
IOErrorEnumHostUnreachable
    toEnum 38 = IOErrorEnum
IOErrorEnumNetworkUnreachable
    toEnum 39 = IOErrorEnum
IOErrorEnumConnectionRefused
    toEnum 40 = IOErrorEnum
IOErrorEnumProxyFailed
    toEnum 41 = IOErrorEnum
IOErrorEnumProxyAuthFailed
    toEnum 42 = IOErrorEnum
IOErrorEnumProxyNeedAuth
    toEnum 43 = IOErrorEnum
IOErrorEnumProxyNotAllowed
    toEnum 44 = IOErrorEnum
IOErrorEnumBrokenPipe
    toEnum 45 = IOErrorEnum
IOErrorEnumNotConnected
    toEnum 46 = IOErrorEnum
IOErrorEnumMessageTooLarge
    toEnum k :: Int
k = Int -> IOErrorEnum
AnotherIOErrorEnum Int
k
instance P.Ord IOErrorEnum where
    compare :: IOErrorEnum -> IOErrorEnum -> Ordering
compare a :: IOErrorEnum
a b :: IOErrorEnum
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (IOErrorEnum -> Int
forall a. Enum a => a -> Int
P.fromEnum IOErrorEnum
a) (IOErrorEnum -> Int
forall a. Enum a => a -> Int
P.fromEnum IOErrorEnum
b)
instance GErrorClass IOErrorEnum where
    gerrorClassDomain :: IOErrorEnum -> Text
gerrorClassDomain _ = "g-io-error-quark"
catchIOErrorEnum ::
    IO a ->
    (IOErrorEnum -> GErrorMessage -> IO a) ->
    IO a
catchIOErrorEnum :: IO a -> (IOErrorEnum -> Text -> IO a) -> IO a
catchIOErrorEnum = IO a -> (IOErrorEnum -> Text -> IO a) -> IO a
forall err a.
GErrorClass err =>
IO a -> (err -> Text -> IO a) -> IO a
catchGErrorJustDomain
handleIOErrorEnum ::
    (IOErrorEnum -> GErrorMessage -> IO a) ->
    IO a ->
    IO a
handleIOErrorEnum :: (IOErrorEnum -> Text -> IO a) -> IO a -> IO a
handleIOErrorEnum = (IOErrorEnum -> Text -> IO a) -> IO a -> IO a
forall err a.
GErrorClass err =>
(err -> Text -> IO a) -> IO a -> IO a
handleGErrorJustDomain
foreign import ccall "g_io_error_enum_get_type" c_g_io_error_enum_get_type :: 
    IO GType
instance BoxedEnum IOErrorEnum where
    boxedEnumType :: IOErrorEnum -> IO GType
boxedEnumType _ = IO GType
c_g_io_error_enum_get_type
data FilesystemPreviewType = 
      FilesystemPreviewTypeIfAlways
    
    | FilesystemPreviewTypeIfLocal
    
    | FilesystemPreviewTypeNever
    
    | AnotherFilesystemPreviewType Int
    
    deriving (Int -> FilesystemPreviewType -> ShowS
[FilesystemPreviewType] -> ShowS
FilesystemPreviewType -> String
(Int -> FilesystemPreviewType -> ShowS)
-> (FilesystemPreviewType -> String)
-> ([FilesystemPreviewType] -> ShowS)
-> Show FilesystemPreviewType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FilesystemPreviewType] -> ShowS
$cshowList :: [FilesystemPreviewType] -> ShowS
show :: FilesystemPreviewType -> String
$cshow :: FilesystemPreviewType -> String
showsPrec :: Int -> FilesystemPreviewType -> ShowS
$cshowsPrec :: Int -> FilesystemPreviewType -> ShowS
Show, FilesystemPreviewType -> FilesystemPreviewType -> Bool
(FilesystemPreviewType -> FilesystemPreviewType -> Bool)
-> (FilesystemPreviewType -> FilesystemPreviewType -> Bool)
-> Eq FilesystemPreviewType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FilesystemPreviewType -> FilesystemPreviewType -> Bool
$c/= :: FilesystemPreviewType -> FilesystemPreviewType -> Bool
== :: FilesystemPreviewType -> FilesystemPreviewType -> Bool
$c== :: FilesystemPreviewType -> FilesystemPreviewType -> Bool
Eq)
instance P.Enum FilesystemPreviewType where
    fromEnum :: FilesystemPreviewType -> Int
fromEnum FilesystemPreviewTypeIfAlways = 0
    fromEnum FilesystemPreviewTypeIfLocal = 1
    fromEnum FilesystemPreviewTypeNever = 2
    fromEnum (AnotherFilesystemPreviewType k :: Int
k) = Int
k
    toEnum :: Int -> FilesystemPreviewType
toEnum 0 = FilesystemPreviewType
FilesystemPreviewTypeIfAlways
    toEnum 1 = FilesystemPreviewType
FilesystemPreviewTypeIfLocal
    toEnum 2 = FilesystemPreviewType
FilesystemPreviewTypeNever
    toEnum k :: Int
k = Int -> FilesystemPreviewType
AnotherFilesystemPreviewType Int
k
instance P.Ord FilesystemPreviewType where
    compare :: FilesystemPreviewType -> FilesystemPreviewType -> Ordering
compare a :: FilesystemPreviewType
a b :: FilesystemPreviewType
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (FilesystemPreviewType -> Int
forall a. Enum a => a -> Int
P.fromEnum FilesystemPreviewType
a) (FilesystemPreviewType -> Int
forall a. Enum a => a -> Int
P.fromEnum FilesystemPreviewType
b)
foreign import ccall "g_filesystem_preview_type_get_type" c_g_filesystem_preview_type_get_type :: 
    IO GType
instance BoxedEnum FilesystemPreviewType where
    boxedEnumType :: FilesystemPreviewType -> IO GType
boxedEnumType _ = IO GType
c_g_filesystem_preview_type_get_type
data FileType = 
      FileTypeUnknown
    
    | FileTypeRegular
    
    | FileTypeDirectory
    
    | FileTypeSymbolicLink
    
    
    | FileTypeSpecial
    
    
    | FileTypeShortcut
    
    | FileTypeMountable
    
    | AnotherFileType Int
    
    deriving (Int -> FileType -> ShowS
[FileType] -> ShowS
FileType -> String
(Int -> FileType -> ShowS)
-> (FileType -> String) -> ([FileType] -> ShowS) -> Show FileType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FileType] -> ShowS
$cshowList :: [FileType] -> ShowS
show :: FileType -> String
$cshow :: FileType -> String
showsPrec :: Int -> FileType -> ShowS
$cshowsPrec :: Int -> FileType -> ShowS
Show, FileType -> FileType -> Bool
(FileType -> FileType -> Bool)
-> (FileType -> FileType -> Bool) -> Eq FileType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FileType -> FileType -> Bool
$c/= :: FileType -> FileType -> Bool
== :: FileType -> FileType -> Bool
$c== :: FileType -> FileType -> Bool
Eq)
instance P.Enum FileType where
    fromEnum :: FileType -> Int
fromEnum FileTypeUnknown = 0
    fromEnum FileTypeRegular = 1
    fromEnum FileTypeDirectory = 2
    fromEnum FileTypeSymbolicLink = 3
    fromEnum FileTypeSpecial = 4
    fromEnum FileTypeShortcut = 5
    fromEnum FileTypeMountable = 6
    fromEnum (AnotherFileType k :: Int
k) = Int
k
    toEnum :: Int -> FileType
toEnum 0 = FileType
FileTypeUnknown
    toEnum 1 = FileType
FileTypeRegular
    toEnum 2 = FileType
FileTypeDirectory
    toEnum 3 = FileType
FileTypeSymbolicLink
    toEnum 4 = FileType
FileTypeSpecial
    toEnum 5 = FileType
FileTypeShortcut
    toEnum 6 = FileType
FileTypeMountable
    toEnum k :: Int
k = Int -> FileType
AnotherFileType Int
k
instance P.Ord FileType where
    compare :: FileType -> FileType -> Ordering
compare a :: FileType
a b :: FileType
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (FileType -> Int
forall a. Enum a => a -> Int
P.fromEnum FileType
a) (FileType -> Int
forall a. Enum a => a -> Int
P.fromEnum FileType
b)
foreign import ccall "g_file_type_get_type" c_g_file_type_get_type :: 
    IO GType
instance BoxedEnum FileType where
    boxedEnumType :: FileType -> IO GType
boxedEnumType _ = IO GType
c_g_file_type_get_type
data FileMonitorEvent = 
      FileMonitorEventChanged
    
    | FileMonitorEventChangesDoneHint
    
    | FileMonitorEventDeleted
    
    | FileMonitorEventCreated
    
    | FileMonitorEventAttributeChanged
    
    | FileMonitorEventPreUnmount
    
    | FileMonitorEventUnmounted
    
    | FileMonitorEventMoved
    
    
    | FileMonitorEventRenamed
    
    
    
    | FileMonitorEventMovedIn
    
    
    
    | FileMonitorEventMovedOut
    
    
    
    | AnotherFileMonitorEvent Int
    
    deriving (Int -> FileMonitorEvent -> ShowS
[FileMonitorEvent] -> ShowS
FileMonitorEvent -> String
(Int -> FileMonitorEvent -> ShowS)
-> (FileMonitorEvent -> String)
-> ([FileMonitorEvent] -> ShowS)
-> Show FileMonitorEvent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FileMonitorEvent] -> ShowS
$cshowList :: [FileMonitorEvent] -> ShowS
show :: FileMonitorEvent -> String
$cshow :: FileMonitorEvent -> String
showsPrec :: Int -> FileMonitorEvent -> ShowS
$cshowsPrec :: Int -> FileMonitorEvent -> ShowS
Show, FileMonitorEvent -> FileMonitorEvent -> Bool
(FileMonitorEvent -> FileMonitorEvent -> Bool)
-> (FileMonitorEvent -> FileMonitorEvent -> Bool)
-> Eq FileMonitorEvent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FileMonitorEvent -> FileMonitorEvent -> Bool
$c/= :: FileMonitorEvent -> FileMonitorEvent -> Bool
== :: FileMonitorEvent -> FileMonitorEvent -> Bool
$c== :: FileMonitorEvent -> FileMonitorEvent -> Bool
Eq)
instance P.Enum FileMonitorEvent where
    fromEnum :: FileMonitorEvent -> Int
fromEnum FileMonitorEventChanged = 0
    fromEnum FileMonitorEventChangesDoneHint = 1
    fromEnum FileMonitorEventDeleted = 2
    fromEnum FileMonitorEventCreated = 3
    fromEnum FileMonitorEventAttributeChanged = 4
    fromEnum FileMonitorEventPreUnmount = 5
    fromEnum FileMonitorEventUnmounted = 6
    fromEnum FileMonitorEventMoved = 7
    fromEnum FileMonitorEventRenamed = 8
    fromEnum FileMonitorEventMovedIn = 9
    fromEnum FileMonitorEventMovedOut = 10
    fromEnum (AnotherFileMonitorEvent k :: Int
k) = Int
k
    toEnum :: Int -> FileMonitorEvent
toEnum 0 = FileMonitorEvent
FileMonitorEventChanged
    toEnum 1 = FileMonitorEvent
FileMonitorEventChangesDoneHint
    toEnum 2 = FileMonitorEvent
FileMonitorEventDeleted
    toEnum 3 = FileMonitorEvent
FileMonitorEventCreated
    toEnum 4 = FileMonitorEvent
FileMonitorEventAttributeChanged
    toEnum 5 = FileMonitorEvent
FileMonitorEventPreUnmount
    toEnum 6 = FileMonitorEvent
FileMonitorEventUnmounted
    toEnum 7 = FileMonitorEvent
FileMonitorEventMoved
    toEnum 8 = FileMonitorEvent
FileMonitorEventRenamed
    toEnum 9 = FileMonitorEvent
FileMonitorEventMovedIn
    toEnum 10 = FileMonitorEvent
FileMonitorEventMovedOut
    toEnum k :: Int
k = Int -> FileMonitorEvent
AnotherFileMonitorEvent Int
k
instance P.Ord FileMonitorEvent where
    compare :: FileMonitorEvent -> FileMonitorEvent -> Ordering
compare a :: FileMonitorEvent
a b :: FileMonitorEvent
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (FileMonitorEvent -> Int
forall a. Enum a => a -> Int
P.fromEnum FileMonitorEvent
a) (FileMonitorEvent -> Int
forall a. Enum a => a -> Int
P.fromEnum FileMonitorEvent
b)
foreign import ccall "g_file_monitor_event_get_type" c_g_file_monitor_event_get_type :: 
    IO GType
instance BoxedEnum FileMonitorEvent where
    boxedEnumType :: FileMonitorEvent -> IO GType
boxedEnumType _ = IO GType
c_g_file_monitor_event_get_type
data FileAttributeType = 
      FileAttributeTypeInvalid
    
    | FileAttributeTypeString
    
    | FileAttributeTypeByteString
    
    | FileAttributeTypeBoolean
    
    | FileAttributeTypeUint32
    
    | FileAttributeTypeInt32
    
    | FileAttributeTypeUint64
    
    | FileAttributeTypeInt64
    
    | FileAttributeTypeObject
    
    | FileAttributeTypeStringv
    
    | AnotherFileAttributeType Int
    
    deriving (Int -> FileAttributeType -> ShowS
[FileAttributeType] -> ShowS
FileAttributeType -> String
(Int -> FileAttributeType -> ShowS)
-> (FileAttributeType -> String)
-> ([FileAttributeType] -> ShowS)
-> Show FileAttributeType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FileAttributeType] -> ShowS
$cshowList :: [FileAttributeType] -> ShowS
show :: FileAttributeType -> String
$cshow :: FileAttributeType -> String
showsPrec :: Int -> FileAttributeType -> ShowS
$cshowsPrec :: Int -> FileAttributeType -> ShowS
Show, FileAttributeType -> FileAttributeType -> Bool
(FileAttributeType -> FileAttributeType -> Bool)
-> (FileAttributeType -> FileAttributeType -> Bool)
-> Eq FileAttributeType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FileAttributeType -> FileAttributeType -> Bool
$c/= :: FileAttributeType -> FileAttributeType -> Bool
== :: FileAttributeType -> FileAttributeType -> Bool
$c== :: FileAttributeType -> FileAttributeType -> Bool
Eq)
instance P.Enum FileAttributeType where
    fromEnum :: FileAttributeType -> Int
fromEnum FileAttributeTypeInvalid = 0
    fromEnum FileAttributeTypeString = 1
    fromEnum FileAttributeTypeByteString = 2
    fromEnum FileAttributeTypeBoolean = 3
    fromEnum FileAttributeTypeUint32 = 4
    fromEnum FileAttributeTypeInt32 = 5
    fromEnum FileAttributeTypeUint64 = 6
    fromEnum FileAttributeTypeInt64 = 7
    fromEnum FileAttributeTypeObject = 8
    fromEnum FileAttributeTypeStringv = 9
    fromEnum (AnotherFileAttributeType k :: Int
k) = Int
k
    toEnum :: Int -> FileAttributeType
toEnum 0 = FileAttributeType
FileAttributeTypeInvalid
    toEnum 1 = FileAttributeType
FileAttributeTypeString
    toEnum 2 = FileAttributeType
FileAttributeTypeByteString
    toEnum 3 = FileAttributeType
FileAttributeTypeBoolean
    toEnum 4 = FileAttributeType
FileAttributeTypeUint32
    toEnum 5 = FileAttributeType
FileAttributeTypeInt32
    toEnum 6 = FileAttributeType
FileAttributeTypeUint64
    toEnum 7 = FileAttributeType
FileAttributeTypeInt64
    toEnum 8 = FileAttributeType
FileAttributeTypeObject
    toEnum 9 = FileAttributeType
FileAttributeTypeStringv
    toEnum k :: Int
k = Int -> FileAttributeType
AnotherFileAttributeType Int
k
instance P.Ord FileAttributeType where
    compare :: FileAttributeType -> FileAttributeType -> Ordering
compare a :: FileAttributeType
a b :: FileAttributeType
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (FileAttributeType -> Int
forall a. Enum a => a -> Int
P.fromEnum FileAttributeType
a) (FileAttributeType -> Int
forall a. Enum a => a -> Int
P.fromEnum FileAttributeType
b)
foreign import ccall "g_file_attribute_type_get_type" c_g_file_attribute_type_get_type :: 
    IO GType
instance BoxedEnum FileAttributeType where
    boxedEnumType :: FileAttributeType -> IO GType
boxedEnumType _ = IO GType
c_g_file_attribute_type_get_type
data FileAttributeStatus = 
      FileAttributeStatusUnset
    
    | FileAttributeStatusSet
    
    | FileAttributeStatusErrorSetting
    
    | AnotherFileAttributeStatus Int
    
    deriving (Int -> FileAttributeStatus -> ShowS
[FileAttributeStatus] -> ShowS
FileAttributeStatus -> String
(Int -> FileAttributeStatus -> ShowS)
-> (FileAttributeStatus -> String)
-> ([FileAttributeStatus] -> ShowS)
-> Show FileAttributeStatus
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FileAttributeStatus] -> ShowS
$cshowList :: [FileAttributeStatus] -> ShowS
show :: FileAttributeStatus -> String
$cshow :: FileAttributeStatus -> String
showsPrec :: Int -> FileAttributeStatus -> ShowS
$cshowsPrec :: Int -> FileAttributeStatus -> ShowS
Show, FileAttributeStatus -> FileAttributeStatus -> Bool
(FileAttributeStatus -> FileAttributeStatus -> Bool)
-> (FileAttributeStatus -> FileAttributeStatus -> Bool)
-> Eq FileAttributeStatus
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FileAttributeStatus -> FileAttributeStatus -> Bool
$c/= :: FileAttributeStatus -> FileAttributeStatus -> Bool
== :: FileAttributeStatus -> FileAttributeStatus -> Bool
$c== :: FileAttributeStatus -> FileAttributeStatus -> Bool
Eq)
instance P.Enum FileAttributeStatus where
    fromEnum :: FileAttributeStatus -> Int
fromEnum FileAttributeStatusUnset = 0
    fromEnum FileAttributeStatusSet = 1
    fromEnum FileAttributeStatusErrorSetting = 2
    fromEnum (AnotherFileAttributeStatus k :: Int
k) = Int
k
    toEnum :: Int -> FileAttributeStatus
toEnum 0 = FileAttributeStatus
FileAttributeStatusUnset
    toEnum 1 = FileAttributeStatus
FileAttributeStatusSet
    toEnum 2 = FileAttributeStatus
FileAttributeStatusErrorSetting
    toEnum k :: Int
k = Int -> FileAttributeStatus
AnotherFileAttributeStatus Int
k
instance P.Ord FileAttributeStatus where
    compare :: FileAttributeStatus -> FileAttributeStatus -> Ordering
compare a :: FileAttributeStatus
a b :: FileAttributeStatus
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (FileAttributeStatus -> Int
forall a. Enum a => a -> Int
P.fromEnum FileAttributeStatus
a) (FileAttributeStatus -> Int
forall a. Enum a => a -> Int
P.fromEnum FileAttributeStatus
b)
foreign import ccall "g_file_attribute_status_get_type" c_g_file_attribute_status_get_type :: 
    IO GType
instance BoxedEnum FileAttributeStatus where
    boxedEnumType :: FileAttributeStatus -> IO GType
boxedEnumType _ = IO GType
c_g_file_attribute_status_get_type
data EmblemOrigin = 
      EmblemOriginUnknown
    
    | EmblemOriginDevice
    
    | EmblemOriginLivemetadata
    
    | EmblemOriginTag
    
    | AnotherEmblemOrigin Int
    
    deriving (Int -> EmblemOrigin -> ShowS
[EmblemOrigin] -> ShowS
EmblemOrigin -> String
(Int -> EmblemOrigin -> ShowS)
-> (EmblemOrigin -> String)
-> ([EmblemOrigin] -> ShowS)
-> Show EmblemOrigin
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EmblemOrigin] -> ShowS
$cshowList :: [EmblemOrigin] -> ShowS
show :: EmblemOrigin -> String
$cshow :: EmblemOrigin -> String
showsPrec :: Int -> EmblemOrigin -> ShowS
$cshowsPrec :: Int -> EmblemOrigin -> ShowS
Show, EmblemOrigin -> EmblemOrigin -> Bool
(EmblemOrigin -> EmblemOrigin -> Bool)
-> (EmblemOrigin -> EmblemOrigin -> Bool) -> Eq EmblemOrigin
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EmblemOrigin -> EmblemOrigin -> Bool
$c/= :: EmblemOrigin -> EmblemOrigin -> Bool
== :: EmblemOrigin -> EmblemOrigin -> Bool
$c== :: EmblemOrigin -> EmblemOrigin -> Bool
Eq)
instance P.Enum EmblemOrigin where
    fromEnum :: EmblemOrigin -> Int
fromEnum EmblemOriginUnknown = 0
    fromEnum EmblemOriginDevice = 1
    fromEnum EmblemOriginLivemetadata = 2
    fromEnum EmblemOriginTag = 3
    fromEnum (AnotherEmblemOrigin k :: Int
k) = Int
k
    toEnum :: Int -> EmblemOrigin
toEnum 0 = EmblemOrigin
EmblemOriginUnknown
    toEnum 1 = EmblemOrigin
EmblemOriginDevice
    toEnum 2 = EmblemOrigin
EmblemOriginLivemetadata
    toEnum 3 = EmblemOrigin
EmblemOriginTag
    toEnum k :: Int
k = Int -> EmblemOrigin
AnotherEmblemOrigin Int
k
instance P.Ord EmblemOrigin where
    compare :: EmblemOrigin -> EmblemOrigin -> Ordering
compare a :: EmblemOrigin
a b :: EmblemOrigin
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (EmblemOrigin -> Int
forall a. Enum a => a -> Int
P.fromEnum EmblemOrigin
a) (EmblemOrigin -> Int
forall a. Enum a => a -> Int
P.fromEnum EmblemOrigin
b)
foreign import ccall "g_emblem_origin_get_type" c_g_emblem_origin_get_type :: 
    IO GType
instance BoxedEnum EmblemOrigin where
    boxedEnumType :: EmblemOrigin -> IO GType
boxedEnumType _ = IO GType
c_g_emblem_origin_get_type
data DriveStartStopType = 
      DriveStartStopTypeUnknown
    
    
    | DriveStartStopTypeShutdown
    
    
    
    | DriveStartStopTypeNetwork
    
    
    | DriveStartStopTypeMultidisk
    
    
    
    | DriveStartStopTypePassword
    
    
    
    | AnotherDriveStartStopType Int
    
    deriving (Int -> DriveStartStopType -> ShowS
[DriveStartStopType] -> ShowS
DriveStartStopType -> String
(Int -> DriveStartStopType -> ShowS)
-> (DriveStartStopType -> String)
-> ([DriveStartStopType] -> ShowS)
-> Show DriveStartStopType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DriveStartStopType] -> ShowS
$cshowList :: [DriveStartStopType] -> ShowS
show :: DriveStartStopType -> String
$cshow :: DriveStartStopType -> String
showsPrec :: Int -> DriveStartStopType -> ShowS
$cshowsPrec :: Int -> DriveStartStopType -> ShowS
Show, DriveStartStopType -> DriveStartStopType -> Bool
(DriveStartStopType -> DriveStartStopType -> Bool)
-> (DriveStartStopType -> DriveStartStopType -> Bool)
-> Eq DriveStartStopType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DriveStartStopType -> DriveStartStopType -> Bool
$c/= :: DriveStartStopType -> DriveStartStopType -> Bool
== :: DriveStartStopType -> DriveStartStopType -> Bool
$c== :: DriveStartStopType -> DriveStartStopType -> Bool
Eq)
instance P.Enum DriveStartStopType where
    fromEnum :: DriveStartStopType -> Int
fromEnum DriveStartStopTypeUnknown = 0
    fromEnum DriveStartStopTypeShutdown = 1
    fromEnum DriveStartStopTypeNetwork = 2
    fromEnum DriveStartStopTypeMultidisk = 3
    fromEnum DriveStartStopTypePassword = 4
    fromEnum (AnotherDriveStartStopType k :: Int
k) = Int
k
    toEnum :: Int -> DriveStartStopType
toEnum 0 = DriveStartStopType
DriveStartStopTypeUnknown
    toEnum 1 = DriveStartStopType
DriveStartStopTypeShutdown
    toEnum 2 = DriveStartStopType
DriveStartStopTypeNetwork
    toEnum 3 = DriveStartStopType
DriveStartStopTypeMultidisk
    toEnum 4 = DriveStartStopType
DriveStartStopTypePassword
    toEnum k :: Int
k = Int -> DriveStartStopType
AnotherDriveStartStopType Int
k
instance P.Ord DriveStartStopType where
    compare :: DriveStartStopType -> DriveStartStopType -> Ordering
compare a :: DriveStartStopType
a b :: DriveStartStopType
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (DriveStartStopType -> Int
forall a. Enum a => a -> Int
P.fromEnum DriveStartStopType
a) (DriveStartStopType -> Int
forall a. Enum a => a -> Int
P.fromEnum DriveStartStopType
b)
foreign import ccall "g_drive_start_stop_type_get_type" c_g_drive_start_stop_type_get_type :: 
    IO GType
instance BoxedEnum DriveStartStopType where
    boxedEnumType :: DriveStartStopType -> IO GType
boxedEnumType _ = IO GType
c_g_drive_start_stop_type_get_type
data DataStreamNewlineType = 
      DataStreamNewlineTypeLf
    
    | DataStreamNewlineTypeCr
    
    | DataStreamNewlineTypeCrLf
    
    | DataStreamNewlineTypeAny
    
    | AnotherDataStreamNewlineType Int
    
    deriving (Int -> DataStreamNewlineType -> ShowS
[DataStreamNewlineType] -> ShowS
DataStreamNewlineType -> String
(Int -> DataStreamNewlineType -> ShowS)
-> (DataStreamNewlineType -> String)
-> ([DataStreamNewlineType] -> ShowS)
-> Show DataStreamNewlineType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DataStreamNewlineType] -> ShowS
$cshowList :: [DataStreamNewlineType] -> ShowS
show :: DataStreamNewlineType -> String
$cshow :: DataStreamNewlineType -> String
showsPrec :: Int -> DataStreamNewlineType -> ShowS
$cshowsPrec :: Int -> DataStreamNewlineType -> ShowS
Show, DataStreamNewlineType -> DataStreamNewlineType -> Bool
(DataStreamNewlineType -> DataStreamNewlineType -> Bool)
-> (DataStreamNewlineType -> DataStreamNewlineType -> Bool)
-> Eq DataStreamNewlineType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DataStreamNewlineType -> DataStreamNewlineType -> Bool
$c/= :: DataStreamNewlineType -> DataStreamNewlineType -> Bool
== :: DataStreamNewlineType -> DataStreamNewlineType -> Bool
$c== :: DataStreamNewlineType -> DataStreamNewlineType -> Bool
Eq)
instance P.Enum DataStreamNewlineType where
    fromEnum :: DataStreamNewlineType -> Int
fromEnum DataStreamNewlineTypeLf = 0
    fromEnum DataStreamNewlineTypeCr = 1
    fromEnum DataStreamNewlineTypeCrLf = 2
    fromEnum DataStreamNewlineTypeAny = 3
    fromEnum (AnotherDataStreamNewlineType k :: Int
k) = Int
k
    toEnum :: Int -> DataStreamNewlineType
toEnum 0 = DataStreamNewlineType
DataStreamNewlineTypeLf
    toEnum 1 = DataStreamNewlineType
DataStreamNewlineTypeCr
    toEnum 2 = DataStreamNewlineType
DataStreamNewlineTypeCrLf
    toEnum 3 = DataStreamNewlineType
DataStreamNewlineTypeAny
    toEnum k :: Int
k = Int -> DataStreamNewlineType
AnotherDataStreamNewlineType Int
k
instance P.Ord DataStreamNewlineType where
    compare :: DataStreamNewlineType -> DataStreamNewlineType -> Ordering
compare a :: DataStreamNewlineType
a b :: DataStreamNewlineType
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (DataStreamNewlineType -> Int
forall a. Enum a => a -> Int
P.fromEnum DataStreamNewlineType
a) (DataStreamNewlineType -> Int
forall a. Enum a => a -> Int
P.fromEnum DataStreamNewlineType
b)
foreign import ccall "g_data_stream_newline_type_get_type" c_g_data_stream_newline_type_get_type :: 
    IO GType
instance BoxedEnum DataStreamNewlineType where
    boxedEnumType :: DataStreamNewlineType -> IO GType
boxedEnumType _ = IO GType
c_g_data_stream_newline_type_get_type
data DataStreamByteOrder = 
      DataStreamByteOrderBigEndian
    
    | DataStreamByteOrderLittleEndian
    
    | DataStreamByteOrderHostEndian
    
    | AnotherDataStreamByteOrder Int
    
    deriving (Int -> DataStreamByteOrder -> ShowS
[DataStreamByteOrder] -> ShowS
DataStreamByteOrder -> String
(Int -> DataStreamByteOrder -> ShowS)
-> (DataStreamByteOrder -> String)
-> ([DataStreamByteOrder] -> ShowS)
-> Show DataStreamByteOrder
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DataStreamByteOrder] -> ShowS
$cshowList :: [DataStreamByteOrder] -> ShowS
show :: DataStreamByteOrder -> String
$cshow :: DataStreamByteOrder -> String
showsPrec :: Int -> DataStreamByteOrder -> ShowS
$cshowsPrec :: Int -> DataStreamByteOrder -> ShowS
Show, DataStreamByteOrder -> DataStreamByteOrder -> Bool
(DataStreamByteOrder -> DataStreamByteOrder -> Bool)
-> (DataStreamByteOrder -> DataStreamByteOrder -> Bool)
-> Eq DataStreamByteOrder
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DataStreamByteOrder -> DataStreamByteOrder -> Bool
$c/= :: DataStreamByteOrder -> DataStreamByteOrder -> Bool
== :: DataStreamByteOrder -> DataStreamByteOrder -> Bool
$c== :: DataStreamByteOrder -> DataStreamByteOrder -> Bool
Eq)
instance P.Enum DataStreamByteOrder where
    fromEnum :: DataStreamByteOrder -> Int
fromEnum DataStreamByteOrderBigEndian = 0
    fromEnum DataStreamByteOrderLittleEndian = 1
    fromEnum DataStreamByteOrderHostEndian = 2
    fromEnum (AnotherDataStreamByteOrder k :: Int
k) = Int
k
    toEnum :: Int -> DataStreamByteOrder
toEnum 0 = DataStreamByteOrder
DataStreamByteOrderBigEndian
    toEnum 1 = DataStreamByteOrder
DataStreamByteOrderLittleEndian
    toEnum 2 = DataStreamByteOrder
DataStreamByteOrderHostEndian
    toEnum k :: Int
k = Int -> DataStreamByteOrder
AnotherDataStreamByteOrder Int
k
instance P.Ord DataStreamByteOrder where
    compare :: DataStreamByteOrder -> DataStreamByteOrder -> Ordering
compare a :: DataStreamByteOrder
a b :: DataStreamByteOrder
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (DataStreamByteOrder -> Int
forall a. Enum a => a -> Int
P.fromEnum DataStreamByteOrder
a) (DataStreamByteOrder -> Int
forall a. Enum a => a -> Int
P.fromEnum DataStreamByteOrder
b)
foreign import ccall "g_data_stream_byte_order_get_type" c_g_data_stream_byte_order_get_type :: 
    IO GType
instance BoxedEnum DataStreamByteOrder where
    boxedEnumType :: DataStreamByteOrder -> IO GType
boxedEnumType _ = IO GType
c_g_data_stream_byte_order_get_type
data DBusMessageType = 
      DBusMessageTypeInvalid
    
    | DBusMessageTypeMethodCall
    
    | DBusMessageTypeMethodReturn
    
    | DBusMessageTypeError
    
    | DBusMessageTypeSignal
    
    | AnotherDBusMessageType Int
    
    deriving (Int -> DBusMessageType -> ShowS
[DBusMessageType] -> ShowS
DBusMessageType -> String
(Int -> DBusMessageType -> ShowS)
-> (DBusMessageType -> String)
-> ([DBusMessageType] -> ShowS)
-> Show DBusMessageType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DBusMessageType] -> ShowS
$cshowList :: [DBusMessageType] -> ShowS
show :: DBusMessageType -> String
$cshow :: DBusMessageType -> String
showsPrec :: Int -> DBusMessageType -> ShowS
$cshowsPrec :: Int -> DBusMessageType -> ShowS
Show, DBusMessageType -> DBusMessageType -> Bool
(DBusMessageType -> DBusMessageType -> Bool)
-> (DBusMessageType -> DBusMessageType -> Bool)
-> Eq DBusMessageType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DBusMessageType -> DBusMessageType -> Bool
$c/= :: DBusMessageType -> DBusMessageType -> Bool
== :: DBusMessageType -> DBusMessageType -> Bool
$c== :: DBusMessageType -> DBusMessageType -> Bool
Eq)
instance P.Enum DBusMessageType where
    fromEnum :: DBusMessageType -> Int
fromEnum DBusMessageTypeInvalid = 0
    fromEnum DBusMessageTypeMethodCall = 1
    fromEnum DBusMessageTypeMethodReturn = 2
    fromEnum DBusMessageTypeError = 3
    fromEnum DBusMessageTypeSignal = 4
    fromEnum (AnotherDBusMessageType k :: Int
k) = Int
k
    toEnum :: Int -> DBusMessageType
toEnum 0 = DBusMessageType
DBusMessageTypeInvalid
    toEnum 1 = DBusMessageType
DBusMessageTypeMethodCall
    toEnum 2 = DBusMessageType
DBusMessageTypeMethodReturn
    toEnum 3 = DBusMessageType
DBusMessageTypeError
    toEnum 4 = DBusMessageType
DBusMessageTypeSignal
    toEnum k :: Int
k = Int -> DBusMessageType
AnotherDBusMessageType Int
k
instance P.Ord DBusMessageType where
    compare :: DBusMessageType -> DBusMessageType -> Ordering
compare a :: DBusMessageType
a b :: DBusMessageType
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (DBusMessageType -> Int
forall a. Enum a => a -> Int
P.fromEnum DBusMessageType
a) (DBusMessageType -> Int
forall a. Enum a => a -> Int
P.fromEnum DBusMessageType
b)
foreign import ccall "g_dbus_message_type_get_type" c_g_dbus_message_type_get_type :: 
    IO GType
instance BoxedEnum DBusMessageType where
    boxedEnumType :: DBusMessageType -> IO GType
boxedEnumType _ = IO GType
c_g_dbus_message_type_get_type
data  = 
      
    
    | 
    
    | 
    
    | 
    
    | 
    
    | 
    
    | 
    
    | 
    
    | 
    
    | 
    
    |  Int
    
    deriving (Int -> DBusMessageHeaderField -> ShowS
[DBusMessageHeaderField] -> ShowS
DBusMessageHeaderField -> String
(Int -> DBusMessageHeaderField -> ShowS)
-> (DBusMessageHeaderField -> String)
-> ([DBusMessageHeaderField] -> ShowS)
-> Show DBusMessageHeaderField
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DBusMessageHeaderField] -> ShowS
$cshowList :: [DBusMessageHeaderField] -> ShowS
show :: DBusMessageHeaderField -> String
$cshow :: DBusMessageHeaderField -> String
showsPrec :: Int -> DBusMessageHeaderField -> ShowS
$cshowsPrec :: Int -> DBusMessageHeaderField -> ShowS
Show, DBusMessageHeaderField -> DBusMessageHeaderField -> Bool
(DBusMessageHeaderField -> DBusMessageHeaderField -> Bool)
-> (DBusMessageHeaderField -> DBusMessageHeaderField -> Bool)
-> Eq DBusMessageHeaderField
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DBusMessageHeaderField -> DBusMessageHeaderField -> Bool
$c/= :: DBusMessageHeaderField -> DBusMessageHeaderField -> Bool
== :: DBusMessageHeaderField -> DBusMessageHeaderField -> Bool
$c== :: DBusMessageHeaderField -> DBusMessageHeaderField -> Bool
Eq)
instance P.Enum DBusMessageHeaderField where
    fromEnum :: DBusMessageHeaderField -> Int
fromEnum DBusMessageHeaderFieldInvalid = 0
    fromEnum DBusMessageHeaderFieldPath = 1
    fromEnum DBusMessageHeaderFieldInterface = 2
    fromEnum DBusMessageHeaderFieldMember = 3
    fromEnum DBusMessageHeaderFieldErrorName = 4
    fromEnum DBusMessageHeaderFieldReplySerial = 5
    fromEnum DBusMessageHeaderFieldDestination = 6
    fromEnum DBusMessageHeaderFieldSender = 7
    fromEnum DBusMessageHeaderFieldSignature = 8
    fromEnum DBusMessageHeaderFieldNumUnixFds = 9
    fromEnum (AnotherDBusMessageHeaderField k :: Int
k) = Int
k
    toEnum :: Int -> DBusMessageHeaderField
toEnum 0 = DBusMessageHeaderField
DBusMessageHeaderFieldInvalid
    toEnum 1 = DBusMessageHeaderField
DBusMessageHeaderFieldPath
    toEnum 2 = DBusMessageHeaderField
DBusMessageHeaderFieldInterface
    toEnum 3 = DBusMessageHeaderField
DBusMessageHeaderFieldMember
    toEnum 4 = DBusMessageHeaderField
DBusMessageHeaderFieldErrorName
    toEnum 5 = DBusMessageHeaderField
DBusMessageHeaderFieldReplySerial
    toEnum 6 = DBusMessageHeaderField
DBusMessageHeaderFieldDestination
    toEnum 7 = DBusMessageHeaderField
DBusMessageHeaderFieldSender
    toEnum 8 = DBusMessageHeaderField
DBusMessageHeaderFieldSignature
    toEnum 9 = DBusMessageHeaderField
DBusMessageHeaderFieldNumUnixFds
    toEnum k :: Int
k = Int -> DBusMessageHeaderField
AnotherDBusMessageHeaderField Int
k
instance P.Ord DBusMessageHeaderField where
    compare :: DBusMessageHeaderField -> DBusMessageHeaderField -> Ordering
compare a :: DBusMessageHeaderField
a b :: DBusMessageHeaderField
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (DBusMessageHeaderField -> Int
forall a. Enum a => a -> Int
P.fromEnum DBusMessageHeaderField
a) (DBusMessageHeaderField -> Int
forall a. Enum a => a -> Int
P.fromEnum DBusMessageHeaderField
b)
foreign import ccall "g_dbus_message_header_field_get_type"  :: 
    IO GType
instance BoxedEnum DBusMessageHeaderField where
    boxedEnumType :: DBusMessageHeaderField -> IO GType
boxedEnumType _ = IO GType
c_g_dbus_message_header_field_get_type
data DBusMessageByteOrder = 
      DBusMessageByteOrderBigEndian
    
    | DBusMessageByteOrderLittleEndian
    
    | AnotherDBusMessageByteOrder Int
    
    deriving (Int -> DBusMessageByteOrder -> ShowS
[DBusMessageByteOrder] -> ShowS
DBusMessageByteOrder -> String
(Int -> DBusMessageByteOrder -> ShowS)
-> (DBusMessageByteOrder -> String)
-> ([DBusMessageByteOrder] -> ShowS)
-> Show DBusMessageByteOrder
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DBusMessageByteOrder] -> ShowS
$cshowList :: [DBusMessageByteOrder] -> ShowS
show :: DBusMessageByteOrder -> String
$cshow :: DBusMessageByteOrder -> String
showsPrec :: Int -> DBusMessageByteOrder -> ShowS
$cshowsPrec :: Int -> DBusMessageByteOrder -> ShowS
Show, DBusMessageByteOrder -> DBusMessageByteOrder -> Bool
(DBusMessageByteOrder -> DBusMessageByteOrder -> Bool)
-> (DBusMessageByteOrder -> DBusMessageByteOrder -> Bool)
-> Eq DBusMessageByteOrder
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DBusMessageByteOrder -> DBusMessageByteOrder -> Bool
$c/= :: DBusMessageByteOrder -> DBusMessageByteOrder -> Bool
== :: DBusMessageByteOrder -> DBusMessageByteOrder -> Bool
$c== :: DBusMessageByteOrder -> DBusMessageByteOrder -> Bool
Eq)
instance P.Enum DBusMessageByteOrder where
    fromEnum :: DBusMessageByteOrder -> Int
fromEnum DBusMessageByteOrderBigEndian = 66
    fromEnum DBusMessageByteOrderLittleEndian = 108
    fromEnum (AnotherDBusMessageByteOrder k :: Int
k) = Int
k
    toEnum :: Int -> DBusMessageByteOrder
toEnum 66 = DBusMessageByteOrder
DBusMessageByteOrderBigEndian
    toEnum 108 = DBusMessageByteOrder
DBusMessageByteOrderLittleEndian
    toEnum k :: Int
k = Int -> DBusMessageByteOrder
AnotherDBusMessageByteOrder Int
k
instance P.Ord DBusMessageByteOrder where
    compare :: DBusMessageByteOrder -> DBusMessageByteOrder -> Ordering
compare a :: DBusMessageByteOrder
a b :: DBusMessageByteOrder
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (DBusMessageByteOrder -> Int
forall a. Enum a => a -> Int
P.fromEnum DBusMessageByteOrder
a) (DBusMessageByteOrder -> Int
forall a. Enum a => a -> Int
P.fromEnum DBusMessageByteOrder
b)
foreign import ccall "g_dbus_message_byte_order_get_type" c_g_dbus_message_byte_order_get_type :: 
    IO GType
instance BoxedEnum DBusMessageByteOrder where
    boxedEnumType :: DBusMessageByteOrder -> IO GType
boxedEnumType _ = IO GType
c_g_dbus_message_byte_order_get_type
data DBusError = 
      DBusErrorFailed
    
    
    | DBusErrorNoMemory
    
    | DBusErrorServiceUnknown
    
    
    | DBusErrorNameHasNoOwner
    
    
    | DBusErrorNoReply
    
    | DBusErrorIoError
    
    | DBusErrorBadAddress
    
    | DBusErrorNotSupported
    
    | DBusErrorLimitsExceeded
    
    | DBusErrorAccessDenied
    
    | DBusErrorAuthFailed
    
    | DBusErrorNoServer
    
    
    | DBusErrorTimeout
    
    
    
    
    
    | DBusErrorNoNetwork
    
    | DBusErrorAddressInUse
    
    | DBusErrorDisconnected
    
    | DBusErrorInvalidArgs
    
    | DBusErrorFileNotFound
    
    | DBusErrorFileExists
    
    | DBusErrorUnknownMethod
    
    | DBusErrorTimedOut
    
    
    
    | DBusErrorMatchRuleNotFound
    
    | DBusErrorMatchRuleInvalid
    
    | DBusErrorSpawnExecFailed
    
    | DBusErrorSpawnForkFailed
    
    | DBusErrorSpawnChildExited
    
    | DBusErrorSpawnChildSignaled
    
    | DBusErrorSpawnFailed
    
    | DBusErrorSpawnSetupFailed
    
    | DBusErrorSpawnConfigInvalid
    
    | DBusErrorSpawnServiceInvalid
    
    | DBusErrorSpawnServiceNotFound
    
    | DBusErrorSpawnPermissionsInvalid
    
    | DBusErrorSpawnFileInvalid
    
    | DBusErrorSpawnNoMemory
    
    | DBusErrorUnixProcessIdUnknown
    
    | DBusErrorInvalidSignature
    
    | DBusErrorInvalidFileContent
    
    | DBusErrorSelinuxSecurityContextUnknown
    
    | DBusErrorAdtAuditDataUnknown
    
    | DBusErrorObjectPathInUse
    
    | DBusErrorUnknownObject
    
    | DBusErrorUnknownInterface
    
    | DBusErrorUnknownProperty
    
    | DBusErrorPropertyReadOnly
    
    | AnotherDBusError Int
    
    deriving (Int -> DBusError -> ShowS
[DBusError] -> ShowS
DBusError -> String
(Int -> DBusError -> ShowS)
-> (DBusError -> String)
-> ([DBusError] -> ShowS)
-> Show DBusError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DBusError] -> ShowS
$cshowList :: [DBusError] -> ShowS
show :: DBusError -> String
$cshow :: DBusError -> String
showsPrec :: Int -> DBusError -> ShowS
$cshowsPrec :: Int -> DBusError -> ShowS
Show, DBusError -> DBusError -> Bool
(DBusError -> DBusError -> Bool)
-> (DBusError -> DBusError -> Bool) -> Eq DBusError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DBusError -> DBusError -> Bool
$c/= :: DBusError -> DBusError -> Bool
== :: DBusError -> DBusError -> Bool
$c== :: DBusError -> DBusError -> Bool
Eq)
instance P.Enum DBusError where
    fromEnum :: DBusError -> Int
fromEnum DBusErrorFailed = 0
    fromEnum DBusErrorNoMemory = 1
    fromEnum DBusErrorServiceUnknown = 2
    fromEnum DBusErrorNameHasNoOwner = 3
    fromEnum DBusErrorNoReply = 4
    fromEnum DBusErrorIoError = 5
    fromEnum DBusErrorBadAddress = 6
    fromEnum DBusErrorNotSupported = 7
    fromEnum DBusErrorLimitsExceeded = 8
    fromEnum DBusErrorAccessDenied = 9
    fromEnum DBusErrorAuthFailed = 10
    fromEnum DBusErrorNoServer = 11
    fromEnum DBusErrorTimeout = 12
    fromEnum DBusErrorNoNetwork = 13
    fromEnum DBusErrorAddressInUse = 14
    fromEnum DBusErrorDisconnected = 15
    fromEnum DBusErrorInvalidArgs = 16
    fromEnum DBusErrorFileNotFound = 17
    fromEnum DBusErrorFileExists = 18
    fromEnum DBusErrorUnknownMethod = 19
    fromEnum DBusErrorTimedOut = 20
    fromEnum DBusErrorMatchRuleNotFound = 21
    fromEnum DBusErrorMatchRuleInvalid = 22
    fromEnum DBusErrorSpawnExecFailed = 23
    fromEnum DBusErrorSpawnForkFailed = 24
    fromEnum DBusErrorSpawnChildExited = 25
    fromEnum DBusErrorSpawnChildSignaled = 26
    fromEnum DBusErrorSpawnFailed = 27
    fromEnum DBusErrorSpawnSetupFailed = 28
    fromEnum DBusErrorSpawnConfigInvalid = 29
    fromEnum DBusErrorSpawnServiceInvalid = 30
    fromEnum DBusErrorSpawnServiceNotFound = 31
    fromEnum DBusErrorSpawnPermissionsInvalid = 32
    fromEnum DBusErrorSpawnFileInvalid = 33
    fromEnum DBusErrorSpawnNoMemory = 34
    fromEnum DBusErrorUnixProcessIdUnknown = 35
    fromEnum DBusErrorInvalidSignature = 36
    fromEnum DBusErrorInvalidFileContent = 37
    fromEnum DBusErrorSelinuxSecurityContextUnknown = 38
    fromEnum DBusErrorAdtAuditDataUnknown = 39
    fromEnum DBusErrorObjectPathInUse = 40
    fromEnum DBusErrorUnknownObject = 41
    fromEnum DBusErrorUnknownInterface = 42
    fromEnum DBusErrorUnknownProperty = 43
    fromEnum DBusErrorPropertyReadOnly = 44
    fromEnum (AnotherDBusError k :: Int
k) = Int
k
    toEnum :: Int -> DBusError
toEnum 0 = DBusError
DBusErrorFailed
    toEnum 1 = DBusError
DBusErrorNoMemory
    toEnum 2 = DBusError
DBusErrorServiceUnknown
    toEnum 3 = DBusError
DBusErrorNameHasNoOwner
    toEnum 4 = DBusError
DBusErrorNoReply
    toEnum 5 = DBusError
DBusErrorIoError
    toEnum 6 = DBusError
DBusErrorBadAddress
    toEnum 7 = DBusError
DBusErrorNotSupported
    toEnum 8 = DBusError
DBusErrorLimitsExceeded
    toEnum 9 = DBusError
DBusErrorAccessDenied
    toEnum 10 = DBusError
DBusErrorAuthFailed
    toEnum 11 = DBusError
DBusErrorNoServer
    toEnum 12 = DBusError
DBusErrorTimeout
    toEnum 13 = DBusError
DBusErrorNoNetwork
    toEnum 14 = DBusError
DBusErrorAddressInUse
    toEnum 15 = DBusError
DBusErrorDisconnected
    toEnum 16 = DBusError
DBusErrorInvalidArgs
    toEnum 17 = DBusError
DBusErrorFileNotFound
    toEnum 18 = DBusError
DBusErrorFileExists
    toEnum 19 = DBusError
DBusErrorUnknownMethod
    toEnum 20 = DBusError
DBusErrorTimedOut
    toEnum 21 = DBusError
DBusErrorMatchRuleNotFound
    toEnum 22 = DBusError
DBusErrorMatchRuleInvalid
    toEnum 23 = DBusError
DBusErrorSpawnExecFailed
    toEnum 24 = DBusError
DBusErrorSpawnForkFailed
    toEnum 25 = DBusError
DBusErrorSpawnChildExited
    toEnum 26 = DBusError
DBusErrorSpawnChildSignaled
    toEnum 27 = DBusError
DBusErrorSpawnFailed
    toEnum 28 = DBusError
DBusErrorSpawnSetupFailed
    toEnum 29 = DBusError
DBusErrorSpawnConfigInvalid
    toEnum 30 = DBusError
DBusErrorSpawnServiceInvalid
    toEnum 31 = DBusError
DBusErrorSpawnServiceNotFound
    toEnum 32 = DBusError
DBusErrorSpawnPermissionsInvalid
    toEnum 33 = DBusError
DBusErrorSpawnFileInvalid
    toEnum 34 = DBusError
DBusErrorSpawnNoMemory
    toEnum 35 = DBusError
DBusErrorUnixProcessIdUnknown
    toEnum 36 = DBusError
DBusErrorInvalidSignature
    toEnum 37 = DBusError
DBusErrorInvalidFileContent
    toEnum 38 = DBusError
DBusErrorSelinuxSecurityContextUnknown
    toEnum 39 = DBusError
DBusErrorAdtAuditDataUnknown
    toEnum 40 = DBusError
DBusErrorObjectPathInUse
    toEnum 41 = DBusError
DBusErrorUnknownObject
    toEnum 42 = DBusError
DBusErrorUnknownInterface
    toEnum 43 = DBusError
DBusErrorUnknownProperty
    toEnum 44 = DBusError
DBusErrorPropertyReadOnly
    toEnum k :: Int
k = Int -> DBusError
AnotherDBusError Int
k
instance P.Ord DBusError where
    compare :: DBusError -> DBusError -> Ordering
compare a :: DBusError
a b :: DBusError
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (DBusError -> Int
forall a. Enum a => a -> Int
P.fromEnum DBusError
a) (DBusError -> Int
forall a. Enum a => a -> Int
P.fromEnum DBusError
b)
instance GErrorClass DBusError where
    gerrorClassDomain :: DBusError -> Text
gerrorClassDomain _ = "g-dbus-error-quark"
catchDBusError ::
    IO a ->
    (DBusError -> GErrorMessage -> IO a) ->
    IO a
catchDBusError :: IO a -> (DBusError -> Text -> IO a) -> IO a
catchDBusError = IO a -> (DBusError -> Text -> IO a) -> IO a
forall err a.
GErrorClass err =>
IO a -> (err -> Text -> IO a) -> IO a
catchGErrorJustDomain
handleDBusError ::
    (DBusError -> GErrorMessage -> IO a) ->
    IO a ->
    IO a
handleDBusError :: (DBusError -> Text -> IO a) -> IO a -> IO a
handleDBusError = (DBusError -> Text -> IO a) -> IO a -> IO a
forall err a.
GErrorClass err =>
(err -> Text -> IO a) -> IO a -> IO a
handleGErrorJustDomain
foreign import ccall "g_dbus_error_get_type" c_g_dbus_error_get_type :: 
    IO GType
instance BoxedEnum DBusError where
    boxedEnumType :: DBusError -> IO GType
boxedEnumType _ = IO GType
c_g_dbus_error_get_type
data CredentialsType = 
      CredentialsTypeInvalid
    
    | CredentialsTypeLinuxUcred
    
    | CredentialsTypeFreebsdCmsgcred
    
    | CredentialsTypeOpenbsdSockpeercred
    
    | CredentialsTypeSolarisUcred
    
    | CredentialsTypeNetbsdUnpcbid
    
    | AnotherCredentialsType Int
    
    deriving (Int -> CredentialsType -> ShowS
[CredentialsType] -> ShowS
CredentialsType -> String
(Int -> CredentialsType -> ShowS)
-> (CredentialsType -> String)
-> ([CredentialsType] -> ShowS)
-> Show CredentialsType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CredentialsType] -> ShowS
$cshowList :: [CredentialsType] -> ShowS
show :: CredentialsType -> String
$cshow :: CredentialsType -> String
showsPrec :: Int -> CredentialsType -> ShowS
$cshowsPrec :: Int -> CredentialsType -> ShowS
Show, CredentialsType -> CredentialsType -> Bool
(CredentialsType -> CredentialsType -> Bool)
-> (CredentialsType -> CredentialsType -> Bool)
-> Eq CredentialsType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CredentialsType -> CredentialsType -> Bool
$c/= :: CredentialsType -> CredentialsType -> Bool
== :: CredentialsType -> CredentialsType -> Bool
$c== :: CredentialsType -> CredentialsType -> Bool
Eq)
instance P.Enum CredentialsType where
    fromEnum :: CredentialsType -> Int
fromEnum CredentialsTypeInvalid = 0
    fromEnum CredentialsTypeLinuxUcred = 1
    fromEnum CredentialsTypeFreebsdCmsgcred = 2
    fromEnum CredentialsTypeOpenbsdSockpeercred = 3
    fromEnum CredentialsTypeSolarisUcred = 4
    fromEnum CredentialsTypeNetbsdUnpcbid = 5
    fromEnum (AnotherCredentialsType k :: Int
k) = Int
k
    toEnum :: Int -> CredentialsType
toEnum 0 = CredentialsType
CredentialsTypeInvalid
    toEnum 1 = CredentialsType
CredentialsTypeLinuxUcred
    toEnum 2 = CredentialsType
CredentialsTypeFreebsdCmsgcred
    toEnum 3 = CredentialsType
CredentialsTypeOpenbsdSockpeercred
    toEnum 4 = CredentialsType
CredentialsTypeSolarisUcred
    toEnum 5 = CredentialsType
CredentialsTypeNetbsdUnpcbid
    toEnum k :: Int
k = Int -> CredentialsType
AnotherCredentialsType Int
k
instance P.Ord CredentialsType where
    compare :: CredentialsType -> CredentialsType -> Ordering
compare a :: CredentialsType
a b :: CredentialsType
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (CredentialsType -> Int
forall a. Enum a => a -> Int
P.fromEnum CredentialsType
a) (CredentialsType -> Int
forall a. Enum a => a -> Int
P.fromEnum CredentialsType
b)
foreign import ccall "g_credentials_type_get_type" c_g_credentials_type_get_type :: 
    IO GType
instance BoxedEnum CredentialsType where
    boxedEnumType :: CredentialsType -> IO GType
boxedEnumType _ = IO GType
c_g_credentials_type_get_type
data ConverterResult = 
      ConverterResultError
    
    | ConverterResultConverted
    
    | ConverterResultFinished
    
    | ConverterResultFlushed
    
    | AnotherConverterResult Int
    
    deriving (Int -> ConverterResult -> ShowS
[ConverterResult] -> ShowS
ConverterResult -> String
(Int -> ConverterResult -> ShowS)
-> (ConverterResult -> String)
-> ([ConverterResult] -> ShowS)
-> Show ConverterResult
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ConverterResult] -> ShowS
$cshowList :: [ConverterResult] -> ShowS
show :: ConverterResult -> String
$cshow :: ConverterResult -> String
showsPrec :: Int -> ConverterResult -> ShowS
$cshowsPrec :: Int -> ConverterResult -> ShowS
Show, ConverterResult -> ConverterResult -> Bool
(ConverterResult -> ConverterResult -> Bool)
-> (ConverterResult -> ConverterResult -> Bool)
-> Eq ConverterResult
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ConverterResult -> ConverterResult -> Bool
$c/= :: ConverterResult -> ConverterResult -> Bool
== :: ConverterResult -> ConverterResult -> Bool
$c== :: ConverterResult -> ConverterResult -> Bool
Eq)
instance P.Enum ConverterResult where
    fromEnum :: ConverterResult -> Int
fromEnum ConverterResultError = 0
    fromEnum ConverterResultConverted = 1
    fromEnum ConverterResultFinished = 2
    fromEnum ConverterResultFlushed = 3
    fromEnum (AnotherConverterResult k :: Int
k) = Int
k
    toEnum :: Int -> ConverterResult
toEnum 0 = ConverterResult
ConverterResultError
    toEnum 1 = ConverterResult
ConverterResultConverted
    toEnum 2 = ConverterResult
ConverterResultFinished
    toEnum 3 = ConverterResult
ConverterResultFlushed
    toEnum k :: Int
k = Int -> ConverterResult
AnotherConverterResult Int
k
instance P.Ord ConverterResult where
    compare :: ConverterResult -> ConverterResult -> Ordering
compare a :: ConverterResult
a b :: ConverterResult
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (ConverterResult -> Int
forall a. Enum a => a -> Int
P.fromEnum ConverterResult
a) (ConverterResult -> Int
forall a. Enum a => a -> Int
P.fromEnum ConverterResult
b)
foreign import ccall "g_converter_result_get_type" c_g_converter_result_get_type :: 
    IO GType
instance BoxedEnum ConverterResult where
    boxedEnumType :: ConverterResult -> IO GType
boxedEnumType _ = IO GType
c_g_converter_result_get_type
data BusType = 
      BusTypeStarter
    
    | BusTypeNone
    
    | BusTypeSystem
    
    | BusTypeSession
    
    | AnotherBusType Int
    
    deriving (Int -> BusType -> ShowS
[BusType] -> ShowS
BusType -> String
(Int -> BusType -> ShowS)
-> (BusType -> String) -> ([BusType] -> ShowS) -> Show BusType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BusType] -> ShowS
$cshowList :: [BusType] -> ShowS
show :: BusType -> String
$cshow :: BusType -> String
showsPrec :: Int -> BusType -> ShowS
$cshowsPrec :: Int -> BusType -> ShowS
Show, BusType -> BusType -> Bool
(BusType -> BusType -> Bool)
-> (BusType -> BusType -> Bool) -> Eq BusType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BusType -> BusType -> Bool
$c/= :: BusType -> BusType -> Bool
== :: BusType -> BusType -> Bool
$c== :: BusType -> BusType -> Bool
Eq)
instance P.Enum BusType where
    fromEnum :: BusType -> Int
fromEnum BusTypeStarter = -1
    fromEnum BusTypeNone = 0
    fromEnum BusTypeSystem = 1
    fromEnum BusTypeSession = 2
    fromEnum (AnotherBusType k :: Int
k) = Int
k
    toEnum :: Int -> BusType
toEnum -1 = BusType
BusTypeStarter
    toEnum 0 = BusType
BusTypeNone
    toEnum 1 = BusType
BusTypeSystem
    toEnum 2 = BusType
BusTypeSession
    toEnum k :: Int
k = Int -> BusType
AnotherBusType Int
k
instance P.Ord BusType where
    compare :: BusType -> BusType -> Ordering
compare a :: BusType
a b :: BusType
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (BusType -> Int
forall a. Enum a => a -> Int
P.fromEnum BusType
a) (BusType -> Int
forall a. Enum a => a -> Int
P.fromEnum BusType
b)
foreign import ccall "g_bus_type_get_type" c_g_bus_type_get_type :: 
    IO GType
instance BoxedEnum BusType where
    boxedEnumType :: BusType -> IO GType
boxedEnumType _ = IO GType
c_g_bus_type_get_type