-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria

#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif

module GI.GLib.Enums
    ( 

 -- * Enumerations


-- ** BookmarkFileError #enum:BookmarkFileError#

    BookmarkFileError(..)                   ,
    catchBookmarkFileError                  ,
    handleBookmarkFileError                 ,


-- ** ChecksumType #enum:ChecksumType#

    ChecksumType(..)                        ,


-- ** ConvertError #enum:ConvertError#

    ConvertError(..)                        ,
    catchConvertError                       ,
    handleConvertError                      ,


-- ** DateDMY #enum:DateDMY#

    DateDMY(..)                             ,


-- ** DateMonth #enum:DateMonth#

    DateMonth(..)                           ,


-- ** DateWeekday #enum:DateWeekday#

    DateWeekday(..)                         ,


-- ** ErrorType #enum:ErrorType#

    ErrorType(..)                           ,


-- ** FileError #enum:FileError#

    FileError(..)                           ,
    catchFileError                          ,
    handleFileError                         ,


-- ** IOChannelError #enum:IOChannelError#

    IOChannelError(..)                      ,
    catchIOChannelError                     ,
    handleIOChannelError                    ,


-- ** IOError #enum:IOError#

    IOError(..)                             ,


-- ** IOStatus #enum:IOStatus#

    IOStatus(..)                            ,


-- ** KeyFileError #enum:KeyFileError#

    KeyFileError(..)                        ,
    catchKeyFileError                       ,
    handleKeyFileError                      ,


-- ** LogWriterOutput #enum:LogWriterOutput#

    LogWriterOutput(..)                     ,


-- ** MarkupError #enum:MarkupError#

    MarkupError(..)                         ,
    catchMarkupError                        ,
    handleMarkupError                       ,


-- ** NormalizeMode #enum:NormalizeMode#

    NormalizeMode(..)                       ,


-- ** NumberParserError #enum:NumberParserError#

    NumberParserError(..)                   ,
    catchNumberParserError                  ,
    handleNumberParserError                 ,


-- ** OnceStatus #enum:OnceStatus#

    OnceStatus(..)                          ,


-- ** OptionArg #enum:OptionArg#

    OptionArg(..)                           ,


-- ** OptionError #enum:OptionError#

    OptionError(..)                         ,
    catchOptionError                        ,
    handleOptionError                       ,


-- ** RegexError #enum:RegexError#

    RegexError(..)                          ,
    catchRegexError                         ,
    handleRegexError                        ,


-- ** SeekType #enum:SeekType#

    SeekType(..)                            ,


-- ** ShellError #enum:ShellError#

    ShellError(..)                          ,
    catchShellError                         ,
    handleShellError                        ,


-- ** SliceConfig #enum:SliceConfig#

    SliceConfig(..)                         ,


-- ** SpawnError #enum:SpawnError#

    SpawnError(..)                          ,
    catchSpawnError                         ,
    handleSpawnError                        ,


-- ** TestFileType #enum:TestFileType#

    TestFileType(..)                        ,


-- ** TestLogType #enum:TestLogType#

    TestLogType(..)                         ,


-- ** TestResult #enum:TestResult#

    TestResult(..)                          ,


-- ** ThreadError #enum:ThreadError#

    ThreadError(..)                         ,
    catchThreadError                        ,
    handleThreadError                       ,


-- ** TimeType #enum:TimeType#

    TimeType(..)                            ,


-- ** TokenType #enum:TokenType#

    TokenType(..)                           ,


-- ** TraverseType #enum:TraverseType#

    TraverseType(..)                        ,


-- ** UnicodeBreakType #enum:UnicodeBreakType#

    UnicodeBreakType(..)                    ,


-- ** UnicodeScript #enum:UnicodeScript#

    UnicodeScript(..)                       ,


-- ** UnicodeType #enum:UnicodeType#

    UnicodeType(..)                         ,


-- ** UriError #enum:UriError#

    UriError(..)                            ,
    catchUriError                           ,
    handleUriError                          ,


-- ** UserDirectory #enum:UserDirectory#

    UserDirectory(..)                       ,


-- ** VariantClass #enum:VariantClass#

    VariantClass(..)                        ,


-- ** VariantParseError #enum:VariantParseError#

    VariantParseError(..)                   ,
    catchVariantParseError                  ,
    handleVariantParseError                 ,




    ) 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.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
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.Coerce as Coerce
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
import qualified GHC.Records as R


-- Enum VariantParseError
-- | Error codes returned by parsing text-format GVariants.
data VariantParseError = 
      VariantParseErrorFailed
    -- ^ generic error (unused)
    | VariantParseErrorBasicTypeExpected
    -- ^ a non-basic t'GI.GLib.Structs.VariantType.VariantType' was given where a basic type was expected
    | VariantParseErrorCannotInferType
    -- ^ cannot infer the t'GI.GLib.Structs.VariantType.VariantType'
    | VariantParseErrorDefiniteTypeExpected
    -- ^ an indefinite t'GI.GLib.Structs.VariantType.VariantType' was given where a definite type was expected
    | VariantParseErrorInputNotAtEnd
    -- ^ extra data after parsing finished
    | VariantParseErrorInvalidCharacter
    -- ^ invalid character in number or unicode escape
    | VariantParseErrorInvalidFormatString
    -- ^ not a valid t'GVariant' format string
    | VariantParseErrorInvalidObjectPath
    -- ^ not a valid object path
    | VariantParseErrorInvalidSignature
    -- ^ not a valid type signature
    | VariantParseErrorInvalidTypeString
    -- ^ not a valid t'GVariant' type string
    | VariantParseErrorNoCommonType
    -- ^ could not find a common type for array entries
    | VariantParseErrorNumberOutOfRange
    -- ^ the numerical value is out of range of the given type
    | VariantParseErrorNumberTooBig
    -- ^ the numerical value is out of range for any type
    | VariantParseErrorTypeError
    -- ^ cannot parse as variant of the specified type
    | VariantParseErrorUnexpectedToken
    -- ^ an unexpected token was encountered
    | VariantParseErrorUnknownKeyword
    -- ^ an unknown keyword was encountered
    | VariantParseErrorUnterminatedStringConstant
    -- ^ unterminated string constant
    | VariantParseErrorValueExpected
    -- ^ no value given
    | VariantParseErrorRecursion
    -- ^ variant was too deeply nested; t'GVariant' is only guaranteed to handle nesting up to 64 levels (Since: 2.64)
    | AnotherVariantParseError Int
    -- ^ Catch-all for unknown values
    deriving (Int -> VariantParseError -> ShowS
[VariantParseError] -> ShowS
VariantParseError -> String
(Int -> VariantParseError -> ShowS)
-> (VariantParseError -> String)
-> ([VariantParseError] -> ShowS)
-> Show VariantParseError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> VariantParseError -> ShowS
showsPrec :: Int -> VariantParseError -> ShowS
$cshow :: VariantParseError -> String
show :: VariantParseError -> String
$cshowList :: [VariantParseError] -> ShowS
showList :: [VariantParseError] -> ShowS
Show, VariantParseError -> VariantParseError -> Bool
(VariantParseError -> VariantParseError -> Bool)
-> (VariantParseError -> VariantParseError -> Bool)
-> Eq VariantParseError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: VariantParseError -> VariantParseError -> Bool
== :: VariantParseError -> VariantParseError -> Bool
$c/= :: VariantParseError -> VariantParseError -> Bool
/= :: VariantParseError -> VariantParseError -> Bool
Eq)

instance P.Enum VariantParseError where
    fromEnum :: VariantParseError -> Int
fromEnum VariantParseError
VariantParseErrorFailed = Int
0
    fromEnum VariantParseError
VariantParseErrorBasicTypeExpected = Int
1
    fromEnum VariantParseError
VariantParseErrorCannotInferType = Int
2
    fromEnum VariantParseError
VariantParseErrorDefiniteTypeExpected = Int
3
    fromEnum VariantParseError
VariantParseErrorInputNotAtEnd = Int
4
    fromEnum VariantParseError
VariantParseErrorInvalidCharacter = Int
5
    fromEnum VariantParseError
VariantParseErrorInvalidFormatString = Int
6
    fromEnum VariantParseError
VariantParseErrorInvalidObjectPath = Int
7
    fromEnum VariantParseError
VariantParseErrorInvalidSignature = Int
8
    fromEnum VariantParseError
VariantParseErrorInvalidTypeString = Int
9
    fromEnum VariantParseError
VariantParseErrorNoCommonType = Int
10
    fromEnum VariantParseError
VariantParseErrorNumberOutOfRange = Int
11
    fromEnum VariantParseError
VariantParseErrorNumberTooBig = Int
12
    fromEnum VariantParseError
VariantParseErrorTypeError = Int
13
    fromEnum VariantParseError
VariantParseErrorUnexpectedToken = Int
14
    fromEnum VariantParseError
VariantParseErrorUnknownKeyword = Int
15
    fromEnum VariantParseError
VariantParseErrorUnterminatedStringConstant = Int
16
    fromEnum VariantParseError
VariantParseErrorValueExpected = Int
17
    fromEnum VariantParseError
VariantParseErrorRecursion = Int
18
    fromEnum (AnotherVariantParseError Int
k) = Int
k

    toEnum :: Int -> VariantParseError
toEnum Int
0 = VariantParseError
VariantParseErrorFailed
    toEnum Int
1 = VariantParseError
VariantParseErrorBasicTypeExpected
    toEnum Int
2 = VariantParseError
VariantParseErrorCannotInferType
    toEnum Int
3 = VariantParseError
VariantParseErrorDefiniteTypeExpected
    toEnum Int
4 = VariantParseError
VariantParseErrorInputNotAtEnd
    toEnum Int
5 = VariantParseError
VariantParseErrorInvalidCharacter
    toEnum Int
6 = VariantParseError
VariantParseErrorInvalidFormatString
    toEnum Int
7 = VariantParseError
VariantParseErrorInvalidObjectPath
    toEnum Int
8 = VariantParseError
VariantParseErrorInvalidSignature
    toEnum Int
9 = VariantParseError
VariantParseErrorInvalidTypeString
    toEnum Int
10 = VariantParseError
VariantParseErrorNoCommonType
    toEnum Int
11 = VariantParseError
VariantParseErrorNumberOutOfRange
    toEnum Int
12 = VariantParseError
VariantParseErrorNumberTooBig
    toEnum Int
13 = VariantParseError
VariantParseErrorTypeError
    toEnum Int
14 = VariantParseError
VariantParseErrorUnexpectedToken
    toEnum Int
15 = VariantParseError
VariantParseErrorUnknownKeyword
    toEnum Int
16 = VariantParseError
VariantParseErrorUnterminatedStringConstant
    toEnum Int
17 = VariantParseError
VariantParseErrorValueExpected
    toEnum Int
18 = VariantParseError
VariantParseErrorRecursion
    toEnum Int
k = Int -> VariantParseError
AnotherVariantParseError Int
k

instance P.Ord VariantParseError where
    compare :: VariantParseError -> VariantParseError -> Ordering
compare VariantParseError
a VariantParseError
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (VariantParseError -> Int
forall a. Enum a => a -> Int
P.fromEnum VariantParseError
a) (VariantParseError -> Int
forall a. Enum a => a -> Int
P.fromEnum VariantParseError
b)

instance GErrorClass VariantParseError where
    gerrorClassDomain :: VariantParseError -> Text
gerrorClassDomain VariantParseError
_ = Text
"g-variant-parse-error-quark"

-- | Catch exceptions of type `VariantParseError`. This is a specialized version of `Data.GI.Base.GError.catchGErrorJustDomain`.
catchVariantParseError ::
    IO a ->
    (VariantParseError -> GErrorMessage -> IO a) ->
    IO a
catchVariantParseError :: forall a. IO a -> (VariantParseError -> Text -> IO a) -> IO a
catchVariantParseError = IO a -> (VariantParseError -> Text -> IO a) -> IO a
forall err a.
GErrorClass err =>
IO a -> (err -> Text -> IO a) -> IO a
catchGErrorJustDomain

-- | Handle exceptions of type `VariantParseError`. This is a specialized version of `Data.GI.Base.GError.handleGErrorJustDomain`.
handleVariantParseError ::
    (VariantParseError -> GErrorMessage -> IO a) ->
    IO a ->
    IO a
handleVariantParseError :: forall a. (VariantParseError -> Text -> IO a) -> IO a -> IO a
handleVariantParseError = (VariantParseError -> Text -> IO a) -> IO a -> IO a
forall err a.
GErrorClass err =>
(err -> Text -> IO a) -> IO a -> IO a
handleGErrorJustDomain

-- Enum VariantClass
-- | The range of possible top-level types of t'GVariant' instances.
-- 
-- /Since: 2.24/
data VariantClass = 
      VariantClassBoolean
    -- ^ The t'GVariant' is a boolean.
    | VariantClassByte
    -- ^ The t'GVariant' is a byte.
    | VariantClassInt16
    -- ^ The t'GVariant' is a signed 16 bit integer.
    | VariantClassUint16
    -- ^ The t'GVariant' is an unsigned 16 bit integer.
    | VariantClassInt32
    -- ^ The t'GVariant' is a signed 32 bit integer.
    | VariantClassUint32
    -- ^ The t'GVariant' is an unsigned 32 bit integer.
    | VariantClassInt64
    -- ^ The t'GVariant' is a signed 64 bit integer.
    | VariantClassUint64
    -- ^ The t'GVariant' is an unsigned 64 bit integer.
    | VariantClassHandle
    -- ^ The t'GVariant' is a file handle index.
    | VariantClassDouble
    -- ^ The t'GVariant' is a double precision floating
    --                          point value.
    | VariantClassString
    -- ^ The t'GVariant' is a normal string.
    | VariantClassObjectPath
    -- ^ The t'GVariant' is a D-Bus object path
    --                               string.
    | VariantClassSignature
    -- ^ The t'GVariant' is a D-Bus signature string.
    | VariantClassVariant
    -- ^ The t'GVariant' is a variant.
    | VariantClassMaybe
    -- ^ The t'GVariant' is a maybe-typed value.
    | VariantClassArray
    -- ^ The t'GVariant' is an array.
    | VariantClassTuple
    -- ^ The t'GVariant' is a tuple.
    | VariantClassDictEntry
    -- ^ The t'GVariant' is a dictionary entry.
    | AnotherVariantClass Int
    -- ^ Catch-all for unknown values
    deriving (Int -> VariantClass -> ShowS
[VariantClass] -> ShowS
VariantClass -> String
(Int -> VariantClass -> ShowS)
-> (VariantClass -> String)
-> ([VariantClass] -> ShowS)
-> Show VariantClass
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> VariantClass -> ShowS
showsPrec :: Int -> VariantClass -> ShowS
$cshow :: VariantClass -> String
show :: VariantClass -> String
$cshowList :: [VariantClass] -> ShowS
showList :: [VariantClass] -> ShowS
Show, VariantClass -> VariantClass -> Bool
(VariantClass -> VariantClass -> Bool)
-> (VariantClass -> VariantClass -> Bool) -> Eq VariantClass
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: VariantClass -> VariantClass -> Bool
== :: VariantClass -> VariantClass -> Bool
$c/= :: VariantClass -> VariantClass -> Bool
/= :: VariantClass -> VariantClass -> Bool
Eq)

instance P.Enum VariantClass where
    fromEnum :: VariantClass -> Int
fromEnum VariantClass
VariantClassBoolean = Int
98
    fromEnum VariantClass
VariantClassByte = Int
121
    fromEnum VariantClass
VariantClassInt16 = Int
110
    fromEnum VariantClass
VariantClassUint16 = Int
113
    fromEnum VariantClass
VariantClassInt32 = Int
105
    fromEnum VariantClass
VariantClassUint32 = Int
117
    fromEnum VariantClass
VariantClassInt64 = Int
120
    fromEnum VariantClass
VariantClassUint64 = Int
116
    fromEnum VariantClass
VariantClassHandle = Int
104
    fromEnum VariantClass
VariantClassDouble = Int
100
    fromEnum VariantClass
VariantClassString = Int
115
    fromEnum VariantClass
VariantClassObjectPath = Int
111
    fromEnum VariantClass
VariantClassSignature = Int
103
    fromEnum VariantClass
VariantClassVariant = Int
118
    fromEnum VariantClass
VariantClassMaybe = Int
109
    fromEnum VariantClass
VariantClassArray = Int
97
    fromEnum VariantClass
VariantClassTuple = Int
40
    fromEnum VariantClass
VariantClassDictEntry = Int
123
    fromEnum (AnotherVariantClass Int
k) = Int
k

    toEnum :: Int -> VariantClass
toEnum Int
98 = VariantClass
VariantClassBoolean
    toEnum Int
121 = VariantClass
VariantClassByte
    toEnum Int
110 = VariantClass
VariantClassInt16
    toEnum Int
113 = VariantClass
VariantClassUint16
    toEnum Int
105 = VariantClass
VariantClassInt32
    toEnum Int
117 = VariantClass
VariantClassUint32
    toEnum Int
120 = VariantClass
VariantClassInt64
    toEnum Int
116 = VariantClass
VariantClassUint64
    toEnum Int
104 = VariantClass
VariantClassHandle
    toEnum Int
100 = VariantClass
VariantClassDouble
    toEnum Int
115 = VariantClass
VariantClassString
    toEnum Int
111 = VariantClass
VariantClassObjectPath
    toEnum Int
103 = VariantClass
VariantClassSignature
    toEnum Int
118 = VariantClass
VariantClassVariant
    toEnum Int
109 = VariantClass
VariantClassMaybe
    toEnum Int
97 = VariantClass
VariantClassArray
    toEnum Int
40 = VariantClass
VariantClassTuple
    toEnum Int
123 = VariantClass
VariantClassDictEntry
    toEnum Int
k = Int -> VariantClass
AnotherVariantClass Int
k

instance P.Ord VariantClass where
    compare :: VariantClass -> VariantClass -> Ordering
compare VariantClass
a VariantClass
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (VariantClass -> Int
forall a. Enum a => a -> Int
P.fromEnum VariantClass
a) (VariantClass -> Int
forall a. Enum a => a -> Int
P.fromEnum VariantClass
b)

-- Enum UserDirectory
-- | These are logical ids for special directories which are defined
-- depending on the platform used. You should use 'GI.GLib.Functions.getUserSpecialDir'
-- to retrieve the full path associated to the logical id.
-- 
-- The t'GI.GLib.Enums.UserDirectory' enumeration can be extended at later date. Not
-- every platform has a directory for every logical id in this
-- enumeration.
-- 
-- /Since: 2.14/
data UserDirectory = 
      UserDirectoryDirectoryDesktop
    -- ^ the user\'s Desktop directory
    | UserDirectoryDirectoryDocuments
    -- ^ the user\'s Documents directory
    | UserDirectoryDirectoryDownload
    -- ^ the user\'s Downloads directory
    | UserDirectoryDirectoryMusic
    -- ^ the user\'s Music directory
    | UserDirectoryDirectoryPictures
    -- ^ the user\'s Pictures directory
    | UserDirectoryDirectoryPublicShare
    -- ^ the user\'s shared directory
    | UserDirectoryDirectoryTemplates
    -- ^ the user\'s Templates directory
    | UserDirectoryDirectoryVideos
    -- ^ the user\'s Movies directory
    | UserDirectoryNDirectories
    -- ^ the number of enum values
    | AnotherUserDirectory Int
    -- ^ Catch-all for unknown values
    deriving (Int -> UserDirectory -> ShowS
[UserDirectory] -> ShowS
UserDirectory -> String
(Int -> UserDirectory -> ShowS)
-> (UserDirectory -> String)
-> ([UserDirectory] -> ShowS)
-> Show UserDirectory
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> UserDirectory -> ShowS
showsPrec :: Int -> UserDirectory -> ShowS
$cshow :: UserDirectory -> String
show :: UserDirectory -> String
$cshowList :: [UserDirectory] -> ShowS
showList :: [UserDirectory] -> ShowS
Show, UserDirectory -> UserDirectory -> Bool
(UserDirectory -> UserDirectory -> Bool)
-> (UserDirectory -> UserDirectory -> Bool) -> Eq UserDirectory
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: UserDirectory -> UserDirectory -> Bool
== :: UserDirectory -> UserDirectory -> Bool
$c/= :: UserDirectory -> UserDirectory -> Bool
/= :: UserDirectory -> UserDirectory -> Bool
Eq)

instance P.Enum UserDirectory where
    fromEnum :: UserDirectory -> Int
fromEnum UserDirectory
UserDirectoryDirectoryDesktop = Int
0
    fromEnum UserDirectory
UserDirectoryDirectoryDocuments = Int
1
    fromEnum UserDirectory
UserDirectoryDirectoryDownload = Int
2
    fromEnum UserDirectory
UserDirectoryDirectoryMusic = Int
3
    fromEnum UserDirectory
UserDirectoryDirectoryPictures = Int
4
    fromEnum UserDirectory
UserDirectoryDirectoryPublicShare = Int
5
    fromEnum UserDirectory
UserDirectoryDirectoryTemplates = Int
6
    fromEnum UserDirectory
UserDirectoryDirectoryVideos = Int
7
    fromEnum UserDirectory
UserDirectoryNDirectories = Int
8
    fromEnum (AnotherUserDirectory Int
k) = Int
k

    toEnum :: Int -> UserDirectory
toEnum Int
0 = UserDirectory
UserDirectoryDirectoryDesktop
    toEnum Int
1 = UserDirectory
UserDirectoryDirectoryDocuments
    toEnum Int
2 = UserDirectory
UserDirectoryDirectoryDownload
    toEnum Int
3 = UserDirectory
UserDirectoryDirectoryMusic
    toEnum Int
4 = UserDirectory
UserDirectoryDirectoryPictures
    toEnum Int
5 = UserDirectory
UserDirectoryDirectoryPublicShare
    toEnum Int
6 = UserDirectory
UserDirectoryDirectoryTemplates
    toEnum Int
7 = UserDirectory
UserDirectoryDirectoryVideos
    toEnum Int
8 = UserDirectory
UserDirectoryNDirectories
    toEnum Int
k = Int -> UserDirectory
AnotherUserDirectory Int
k

instance P.Ord UserDirectory where
    compare :: UserDirectory -> UserDirectory -> Ordering
compare UserDirectory
a UserDirectory
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (UserDirectory -> Int
forall a. Enum a => a -> Int
P.fromEnum UserDirectory
a) (UserDirectory -> Int
forall a. Enum a => a -> Int
P.fromEnum UserDirectory
b)

-- Enum UriError
-- | Error codes returned by t'GI.GLib.Structs.Uri.Uri' methods.
-- 
-- /Since: 2.66/
data UriError = 
      UriErrorFailed
    -- ^ Generic error if no more specific error is available.
    --     See the error message for details.
    | UriErrorBadScheme
    -- ^ The scheme of a URI could not be parsed.
    | UriErrorBadUser
    -- ^ The user\/userinfo of a URI could not be parsed.
    | UriErrorBadPassword
    -- ^ The password of a URI could not be parsed.
    | UriErrorBadAuthParams
    -- ^ The authentication parameters of a URI could not be parsed.
    | UriErrorBadHost
    -- ^ The host of a URI could not be parsed.
    | UriErrorBadPort
    -- ^ The port of a URI could not be parsed.
    | UriErrorBadPath
    -- ^ The path of a URI could not be parsed.
    | UriErrorBadQuery
    -- ^ The query of a URI could not be parsed.
    | UriErrorBadFragment
    -- ^ The fragment of a URI could not be parsed.
    | AnotherUriError Int
    -- ^ Catch-all for unknown values
    deriving (Int -> UriError -> ShowS
[UriError] -> ShowS
UriError -> String
(Int -> UriError -> ShowS)
-> (UriError -> String) -> ([UriError] -> ShowS) -> Show UriError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> UriError -> ShowS
showsPrec :: Int -> UriError -> ShowS
$cshow :: UriError -> String
show :: UriError -> String
$cshowList :: [UriError] -> ShowS
showList :: [UriError] -> ShowS
Show, UriError -> UriError -> Bool
(UriError -> UriError -> Bool)
-> (UriError -> UriError -> Bool) -> Eq UriError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: UriError -> UriError -> Bool
== :: UriError -> UriError -> Bool
$c/= :: UriError -> UriError -> Bool
/= :: UriError -> UriError -> Bool
Eq)

instance P.Enum UriError where
    fromEnum :: UriError -> Int
fromEnum UriError
UriErrorFailed = Int
0
    fromEnum UriError
UriErrorBadScheme = Int
1
    fromEnum UriError
UriErrorBadUser = Int
2
    fromEnum UriError
UriErrorBadPassword = Int
3
    fromEnum UriError
UriErrorBadAuthParams = Int
4
    fromEnum UriError
UriErrorBadHost = Int
5
    fromEnum UriError
UriErrorBadPort = Int
6
    fromEnum UriError
UriErrorBadPath = Int
7
    fromEnum UriError
UriErrorBadQuery = Int
8
    fromEnum UriError
UriErrorBadFragment = Int
9
    fromEnum (AnotherUriError Int
k) = Int
k

    toEnum :: Int -> UriError
toEnum Int
0 = UriError
UriErrorFailed
    toEnum Int
1 = UriError
UriErrorBadScheme
    toEnum Int
2 = UriError
UriErrorBadUser
    toEnum Int
3 = UriError
UriErrorBadPassword
    toEnum Int
4 = UriError
UriErrorBadAuthParams
    toEnum Int
5 = UriError
UriErrorBadHost
    toEnum Int
6 = UriError
UriErrorBadPort
    toEnum Int
7 = UriError
UriErrorBadPath
    toEnum Int
8 = UriError
UriErrorBadQuery
    toEnum Int
9 = UriError
UriErrorBadFragment
    toEnum Int
k = Int -> UriError
AnotherUriError Int
k

instance P.Ord UriError where
    compare :: UriError -> UriError -> Ordering
compare UriError
a UriError
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (UriError -> Int
forall a. Enum a => a -> Int
P.fromEnum UriError
a) (UriError -> Int
forall a. Enum a => a -> Int
P.fromEnum UriError
b)

instance GErrorClass UriError where
    gerrorClassDomain :: UriError -> Text
gerrorClassDomain UriError
_ = Text
"g-uri-quark"

-- | Catch exceptions of type `UriError`. This is a specialized version of `Data.GI.Base.GError.catchGErrorJustDomain`.
catchUriError ::
    IO a ->
    (UriError -> GErrorMessage -> IO a) ->
    IO a
catchUriError :: forall a. IO a -> (UriError -> Text -> IO a) -> IO a
catchUriError = IO a -> (UriError -> Text -> IO a) -> IO a
forall err a.
GErrorClass err =>
IO a -> (err -> Text -> IO a) -> IO a
catchGErrorJustDomain

-- | Handle exceptions of type `UriError`. This is a specialized version of `Data.GI.Base.GError.handleGErrorJustDomain`.
handleUriError ::
    (UriError -> GErrorMessage -> IO a) ->
    IO a ->
    IO a
handleUriError :: forall a. (UriError -> Text -> IO a) -> IO a -> IO a
handleUriError = (UriError -> Text -> IO a) -> IO a -> IO a
forall err a.
GErrorClass err =>
(err -> Text -> IO a) -> IO a -> IO a
handleGErrorJustDomain

-- Enum UnicodeType
-- | These are the possible character classifications from the
-- Unicode specification.
-- See <http://www.unicode.org/reports/tr44/#General_Category_Values Unicode Character Database>.
data UnicodeType = 
      UnicodeTypeControl
    -- ^ General category \"Other, Control\" (Cc)
    | UnicodeTypeFormat
    -- ^ General category \"Other, Format\" (Cf)
    | UnicodeTypeUnassigned
    -- ^ General category \"Other, Not Assigned\" (Cn)
    | UnicodeTypePrivateUse
    -- ^ General category \"Other, Private Use\" (Co)
    | UnicodeTypeSurrogate
    -- ^ General category \"Other, Surrogate\" (Cs)
    | UnicodeTypeLowercaseLetter
    -- ^ General category \"Letter, Lowercase\" (Ll)
    | UnicodeTypeModifierLetter
    -- ^ General category \"Letter, Modifier\" (Lm)
    | UnicodeTypeOtherLetter
    -- ^ General category \"Letter, Other\" (Lo)
    | UnicodeTypeTitlecaseLetter
    -- ^ General category \"Letter, Titlecase\" (Lt)
    | UnicodeTypeUppercaseLetter
    -- ^ General category \"Letter, Uppercase\" (Lu)
    | UnicodeTypeSpacingMark
    -- ^ General category \"Mark, Spacing\" (Mc)
    | UnicodeTypeEnclosingMark
    -- ^ General category \"Mark, Enclosing\" (Me)
    | UnicodeTypeNonSpacingMark
    -- ^ General category \"Mark, Nonspacing\" (Mn)
    | UnicodeTypeDecimalNumber
    -- ^ General category \"Number, Decimal Digit\" (Nd)
    | UnicodeTypeLetterNumber
    -- ^ General category \"Number, Letter\" (Nl)
    | UnicodeTypeOtherNumber
    -- ^ General category \"Number, Other\" (No)
    | UnicodeTypeConnectPunctuation
    -- ^ General category \"Punctuation, Connector\" (Pc)
    | UnicodeTypeDashPunctuation
    -- ^ General category \"Punctuation, Dash\" (Pd)
    | UnicodeTypeClosePunctuation
    -- ^ General category \"Punctuation, Close\" (Pe)
    | UnicodeTypeFinalPunctuation
    -- ^ General category \"Punctuation, Final quote\" (Pf)
    | UnicodeTypeInitialPunctuation
    -- ^ General category \"Punctuation, Initial quote\" (Pi)
    | UnicodeTypeOtherPunctuation
    -- ^ General category \"Punctuation, Other\" (Po)
    | UnicodeTypeOpenPunctuation
    -- ^ General category \"Punctuation, Open\" (Ps)
    | UnicodeTypeCurrencySymbol
    -- ^ General category \"Symbol, Currency\" (Sc)
    | UnicodeTypeModifierSymbol
    -- ^ General category \"Symbol, Modifier\" (Sk)
    | UnicodeTypeMathSymbol
    -- ^ General category \"Symbol, Math\" (Sm)
    | UnicodeTypeOtherSymbol
    -- ^ General category \"Symbol, Other\" (So)
    | UnicodeTypeLineSeparator
    -- ^ General category \"Separator, Line\" (Zl)
    | UnicodeTypeParagraphSeparator
    -- ^ General category \"Separator, Paragraph\" (Zp)
    | UnicodeTypeSpaceSeparator
    -- ^ General category \"Separator, Space\" (Zs)
    | AnotherUnicodeType Int
    -- ^ Catch-all for unknown values
    deriving (Int -> UnicodeType -> ShowS
[UnicodeType] -> ShowS
UnicodeType -> String
(Int -> UnicodeType -> ShowS)
-> (UnicodeType -> String)
-> ([UnicodeType] -> ShowS)
-> Show UnicodeType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> UnicodeType -> ShowS
showsPrec :: Int -> UnicodeType -> ShowS
$cshow :: UnicodeType -> String
show :: UnicodeType -> String
$cshowList :: [UnicodeType] -> ShowS
showList :: [UnicodeType] -> ShowS
Show, UnicodeType -> UnicodeType -> Bool
(UnicodeType -> UnicodeType -> Bool)
-> (UnicodeType -> UnicodeType -> Bool) -> Eq UnicodeType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: UnicodeType -> UnicodeType -> Bool
== :: UnicodeType -> UnicodeType -> Bool
$c/= :: UnicodeType -> UnicodeType -> Bool
/= :: UnicodeType -> UnicodeType -> Bool
Eq)

instance P.Enum UnicodeType where
    fromEnum :: UnicodeType -> Int
fromEnum UnicodeType
UnicodeTypeControl = Int
0
    fromEnum UnicodeType
UnicodeTypeFormat = Int
1
    fromEnum UnicodeType
UnicodeTypeUnassigned = Int
2
    fromEnum UnicodeType
UnicodeTypePrivateUse = Int
3
    fromEnum UnicodeType
UnicodeTypeSurrogate = Int
4
    fromEnum UnicodeType
UnicodeTypeLowercaseLetter = Int
5
    fromEnum UnicodeType
UnicodeTypeModifierLetter = Int
6
    fromEnum UnicodeType
UnicodeTypeOtherLetter = Int
7
    fromEnum UnicodeType
UnicodeTypeTitlecaseLetter = Int
8
    fromEnum UnicodeType
UnicodeTypeUppercaseLetter = Int
9
    fromEnum UnicodeType
UnicodeTypeSpacingMark = Int
10
    fromEnum UnicodeType
UnicodeTypeEnclosingMark = Int
11
    fromEnum UnicodeType
UnicodeTypeNonSpacingMark = Int
12
    fromEnum UnicodeType
UnicodeTypeDecimalNumber = Int
13
    fromEnum UnicodeType
UnicodeTypeLetterNumber = Int
14
    fromEnum UnicodeType
UnicodeTypeOtherNumber = Int
15
    fromEnum UnicodeType
UnicodeTypeConnectPunctuation = Int
16
    fromEnum UnicodeType
UnicodeTypeDashPunctuation = Int
17
    fromEnum UnicodeType
UnicodeTypeClosePunctuation = Int
18
    fromEnum UnicodeType
UnicodeTypeFinalPunctuation = Int
19
    fromEnum UnicodeType
UnicodeTypeInitialPunctuation = Int
20
    fromEnum UnicodeType
UnicodeTypeOtherPunctuation = Int
21
    fromEnum UnicodeType
UnicodeTypeOpenPunctuation = Int
22
    fromEnum UnicodeType
UnicodeTypeCurrencySymbol = Int
23
    fromEnum UnicodeType
UnicodeTypeModifierSymbol = Int
24
    fromEnum UnicodeType
UnicodeTypeMathSymbol = Int
25
    fromEnum UnicodeType
UnicodeTypeOtherSymbol = Int
26
    fromEnum UnicodeType
UnicodeTypeLineSeparator = Int
27
    fromEnum UnicodeType
UnicodeTypeParagraphSeparator = Int
28
    fromEnum UnicodeType
UnicodeTypeSpaceSeparator = Int
29
    fromEnum (AnotherUnicodeType Int
k) = Int
k

    toEnum :: Int -> UnicodeType
toEnum Int
0 = UnicodeType
UnicodeTypeControl
    toEnum Int
1 = UnicodeType
UnicodeTypeFormat
    toEnum Int
2 = UnicodeType
UnicodeTypeUnassigned
    toEnum Int
3 = UnicodeType
UnicodeTypePrivateUse
    toEnum Int
4 = UnicodeType
UnicodeTypeSurrogate
    toEnum Int
5 = UnicodeType
UnicodeTypeLowercaseLetter
    toEnum Int
6 = UnicodeType
UnicodeTypeModifierLetter
    toEnum Int
7 = UnicodeType
UnicodeTypeOtherLetter
    toEnum Int
8 = UnicodeType
UnicodeTypeTitlecaseLetter
    toEnum Int
9 = UnicodeType
UnicodeTypeUppercaseLetter
    toEnum Int
10 = UnicodeType
UnicodeTypeSpacingMark
    toEnum Int
11 = UnicodeType
UnicodeTypeEnclosingMark
    toEnum Int
12 = UnicodeType
UnicodeTypeNonSpacingMark
    toEnum Int
13 = UnicodeType
UnicodeTypeDecimalNumber
    toEnum Int
14 = UnicodeType
UnicodeTypeLetterNumber
    toEnum Int
15 = UnicodeType
UnicodeTypeOtherNumber
    toEnum Int
16 = UnicodeType
UnicodeTypeConnectPunctuation
    toEnum Int
17 = UnicodeType
UnicodeTypeDashPunctuation
    toEnum Int
18 = UnicodeType
UnicodeTypeClosePunctuation
    toEnum Int
19 = UnicodeType
UnicodeTypeFinalPunctuation
    toEnum Int
20 = UnicodeType
UnicodeTypeInitialPunctuation
    toEnum Int
21 = UnicodeType
UnicodeTypeOtherPunctuation
    toEnum Int
22 = UnicodeType
UnicodeTypeOpenPunctuation
    toEnum Int
23 = UnicodeType
UnicodeTypeCurrencySymbol
    toEnum Int
24 = UnicodeType
UnicodeTypeModifierSymbol
    toEnum Int
25 = UnicodeType
UnicodeTypeMathSymbol
    toEnum Int
26 = UnicodeType
UnicodeTypeOtherSymbol
    toEnum Int
27 = UnicodeType
UnicodeTypeLineSeparator
    toEnum Int
28 = UnicodeType
UnicodeTypeParagraphSeparator
    toEnum Int
29 = UnicodeType
UnicodeTypeSpaceSeparator
    toEnum Int
k = Int -> UnicodeType
AnotherUnicodeType Int
k

instance P.Ord UnicodeType where
    compare :: UnicodeType -> UnicodeType -> Ordering
compare UnicodeType
a UnicodeType
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (UnicodeType -> Int
forall a. Enum a => a -> Int
P.fromEnum UnicodeType
a) (UnicodeType -> Int
forall a. Enum a => a -> Int
P.fromEnum UnicodeType
b)

-- Enum UnicodeScript
-- | The t'GI.GLib.Enums.UnicodeScript' enumeration identifies different writing
-- systems. The values correspond to the names as defined in the
-- Unicode standard. The enumeration has been added in GLib 2.14,
-- and is interchangeable with @/PangoScript/@.
-- 
-- Note that new types may be added in the future. Applications
-- should be ready to handle unknown values.
-- See <http://www.unicode.org/reports/tr24/ Unicode Standard Annex #24: Script names>.
data UnicodeScript = 
      UnicodeScriptInvalidCode
    -- ^ a value never returned from 'GI.GLib.Functions.unicharGetScript'
    | UnicodeScriptCommon
    -- ^ a character used by multiple different scripts
    | UnicodeScriptInherited
    -- ^ a mark glyph that takes its script from the
    --                               base glyph to which it is attached
    | UnicodeScriptArabic
    -- ^ Arabic
    | UnicodeScriptArmenian
    -- ^ Armenian
    | UnicodeScriptBengali
    -- ^ Bengali
    | UnicodeScriptBopomofo
    -- ^ Bopomofo
    | UnicodeScriptCherokee
    -- ^ Cherokee
    | UnicodeScriptCoptic
    -- ^ Coptic
    | UnicodeScriptCyrillic
    -- ^ Cyrillic
    | UnicodeScriptDeseret
    -- ^ Deseret
    | UnicodeScriptDevanagari
    -- ^ Devanagari
    | UnicodeScriptEthiopic
    -- ^ Ethiopic
    | UnicodeScriptGeorgian
    -- ^ Georgian
    | UnicodeScriptGothic
    -- ^ Gothic
    | UnicodeScriptGreek
    -- ^ Greek
    | UnicodeScriptGujarati
    -- ^ Gujarati
    | UnicodeScriptGurmukhi
    -- ^ Gurmukhi
    | UnicodeScriptHan
    -- ^ Han
    | UnicodeScriptHangul
    -- ^ Hangul
    | UnicodeScriptHebrew
    -- ^ Hebrew
    | UnicodeScriptHiragana
    -- ^ Hiragana
    | UnicodeScriptKannada
    -- ^ Kannada
    | UnicodeScriptKatakana
    -- ^ Katakana
    | UnicodeScriptKhmer
    -- ^ Khmer
    | UnicodeScriptLao
    -- ^ Lao
    | UnicodeScriptLatin
    -- ^ Latin
    | UnicodeScriptMalayalam
    -- ^ Malayalam
    | UnicodeScriptMongolian
    -- ^ Mongolian
    | UnicodeScriptMyanmar
    -- ^ Myanmar
    | UnicodeScriptOgham
    -- ^ Ogham
    | UnicodeScriptOldItalic
    -- ^ Old Italic
    | UnicodeScriptOriya
    -- ^ Oriya
    | UnicodeScriptRunic
    -- ^ Runic
    | UnicodeScriptSinhala
    -- ^ Sinhala
    | UnicodeScriptSyriac
    -- ^ Syriac
    | UnicodeScriptTamil
    -- ^ Tamil
    | UnicodeScriptTelugu
    -- ^ Telugu
    | UnicodeScriptThaana
    -- ^ Thaana
    | UnicodeScriptThai
    -- ^ Thai
    | UnicodeScriptTibetan
    -- ^ Tibetan
    | UnicodeScriptCanadianAboriginal
    -- ^ Canadian Aboriginal
    | UnicodeScriptYi
    -- ^ Yi
    | UnicodeScriptTagalog
    -- ^ Tagalog
    | UnicodeScriptHanunoo
    -- ^ Hanunoo
    | UnicodeScriptBuhid
    -- ^ Buhid
    | UnicodeScriptTagbanwa
    -- ^ Tagbanwa
    | UnicodeScriptBraille
    -- ^ Braille
    | UnicodeScriptCypriot
    -- ^ Cypriot
    | UnicodeScriptLimbu
    -- ^ Limbu
    | UnicodeScriptOsmanya
    -- ^ Osmanya
    | UnicodeScriptShavian
    -- ^ Shavian
    | UnicodeScriptLinearB
    -- ^ Linear B
    | UnicodeScriptTaiLe
    -- ^ Tai Le
    | UnicodeScriptUgaritic
    -- ^ Ugaritic
    | UnicodeScriptNewTaiLue
    -- ^ New Tai Lue
    | UnicodeScriptBuginese
    -- ^ Buginese
    | UnicodeScriptGlagolitic
    -- ^ Glagolitic
    | UnicodeScriptTifinagh
    -- ^ Tifinagh
    | UnicodeScriptSylotiNagri
    -- ^ Syloti Nagri
    | UnicodeScriptOldPersian
    -- ^ Old Persian
    | UnicodeScriptKharoshthi
    -- ^ Kharoshthi
    | UnicodeScriptUnknown
    -- ^ an unassigned code point
    | UnicodeScriptBalinese
    -- ^ Balinese
    | UnicodeScriptCuneiform
    -- ^ Cuneiform
    | UnicodeScriptPhoenician
    -- ^ Phoenician
    | UnicodeScriptPhagsPa
    -- ^ Phags-pa
    | UnicodeScriptNko
    -- ^ N\'Ko
    | UnicodeScriptKayahLi
    -- ^ Kayah Li. Since 2.16.3
    | UnicodeScriptLepcha
    -- ^ Lepcha. Since 2.16.3
    | UnicodeScriptRejang
    -- ^ Rejang. Since 2.16.3
    | UnicodeScriptSundanese
    -- ^ Sundanese. Since 2.16.3
    | UnicodeScriptSaurashtra
    -- ^ Saurashtra. Since 2.16.3
    | UnicodeScriptCham
    -- ^ Cham. Since 2.16.3
    | UnicodeScriptOlChiki
    -- ^ Ol Chiki. Since 2.16.3
    | UnicodeScriptVai
    -- ^ Vai. Since 2.16.3
    | UnicodeScriptCarian
    -- ^ Carian. Since 2.16.3
    | UnicodeScriptLycian
    -- ^ Lycian. Since 2.16.3
    | UnicodeScriptLydian
    -- ^ Lydian. Since 2.16.3
    | UnicodeScriptAvestan
    -- ^ Avestan. Since 2.26
    | UnicodeScriptBamum
    -- ^ Bamum. Since 2.26
    | UnicodeScriptEgyptianHieroglyphs
    -- ^ Egyptian Hieroglpyhs. Since 2.26
    | UnicodeScriptImperialAramaic
    -- ^ Imperial Aramaic. Since 2.26
    | UnicodeScriptInscriptionalPahlavi
    -- ^ Inscriptional Pahlavi. Since 2.26
    | UnicodeScriptInscriptionalParthian
    -- ^ Inscriptional Parthian. Since 2.26
    | UnicodeScriptJavanese
    -- ^ Javanese. Since 2.26
    | UnicodeScriptKaithi
    -- ^ Kaithi. Since 2.26
    | UnicodeScriptLisu
    -- ^ Lisu. Since 2.26
    | UnicodeScriptMeeteiMayek
    -- ^ Meetei Mayek. Since 2.26
    | UnicodeScriptOldSouthArabian
    -- ^ Old South Arabian. Since 2.26
    | UnicodeScriptOldTurkic
    -- ^ Old Turkic. Since 2.28
    | UnicodeScriptSamaritan
    -- ^ Samaritan. Since 2.26
    | UnicodeScriptTaiTham
    -- ^ Tai Tham. Since 2.26
    | UnicodeScriptTaiViet
    -- ^ Tai Viet. Since 2.26
    | UnicodeScriptBatak
    -- ^ Batak. Since 2.28
    | UnicodeScriptBrahmi
    -- ^ Brahmi. Since 2.28
    | UnicodeScriptMandaic
    -- ^ Mandaic. Since 2.28
    | UnicodeScriptChakma
    -- ^ Chakma. Since: 2.32
    | UnicodeScriptMeroiticCursive
    -- ^ Meroitic Cursive. Since: 2.32
    | UnicodeScriptMeroiticHieroglyphs
    -- ^ Meroitic Hieroglyphs. Since: 2.32
    | UnicodeScriptMiao
    -- ^ Miao. Since: 2.32
    | UnicodeScriptSharada
    -- ^ Sharada. Since: 2.32
    | UnicodeScriptSoraSompeng
    -- ^ Sora Sompeng. Since: 2.32
    | UnicodeScriptTakri
    -- ^ Takri. Since: 2.32
    | UnicodeScriptBassaVah
    -- ^ Bassa. Since: 2.42
    | UnicodeScriptCaucasianAlbanian
    -- ^ Caucasian Albanian. Since: 2.42
    | UnicodeScriptDuployan
    -- ^ Duployan. Since: 2.42
    | UnicodeScriptElbasan
    -- ^ Elbasan. Since: 2.42
    | UnicodeScriptGrantha
    -- ^ Grantha. Since: 2.42
    | UnicodeScriptKhojki
    -- ^ Kjohki. Since: 2.42
    | UnicodeScriptKhudawadi
    -- ^ Khudawadi, Sindhi. Since: 2.42
    | UnicodeScriptLinearA
    -- ^ Linear A. Since: 2.42
    | UnicodeScriptMahajani
    -- ^ Mahajani. Since: 2.42
    | UnicodeScriptManichaean
    -- ^ Manichaean. Since: 2.42
    | UnicodeScriptMendeKikakui
    -- ^ Mende Kikakui. Since: 2.42
    | UnicodeScriptModi
    -- ^ Modi. Since: 2.42
    | UnicodeScriptMro
    -- ^ Mro. Since: 2.42
    | UnicodeScriptNabataean
    -- ^ Nabataean. Since: 2.42
    | UnicodeScriptOldNorthArabian
    -- ^ Old North Arabian. Since: 2.42
    | UnicodeScriptOldPermic
    -- ^ Old Permic. Since: 2.42
    | UnicodeScriptPahawhHmong
    -- ^ Pahawh Hmong. Since: 2.42
    | UnicodeScriptPalmyrene
    -- ^ Palmyrene. Since: 2.42
    | UnicodeScriptPauCinHau
    -- ^ Pau Cin Hau. Since: 2.42
    | UnicodeScriptPsalterPahlavi
    -- ^ Psalter Pahlavi. Since: 2.42
    | UnicodeScriptSiddham
    -- ^ Siddham. Since: 2.42
    | UnicodeScriptTirhuta
    -- ^ Tirhuta. Since: 2.42
    | UnicodeScriptWarangCiti
    -- ^ Warang Citi. Since: 2.42
    | UnicodeScriptAhom
    -- ^ Ahom. Since: 2.48
    | UnicodeScriptAnatolianHieroglyphs
    -- ^ Anatolian Hieroglyphs. Since: 2.48
    | UnicodeScriptHatran
    -- ^ Hatran. Since: 2.48
    | UnicodeScriptMultani
    -- ^ Multani. Since: 2.48
    | UnicodeScriptOldHungarian
    -- ^ Old Hungarian. Since: 2.48
    | UnicodeScriptSignwriting
    -- ^ Signwriting. Since: 2.48
    | UnicodeScriptAdlam
    -- ^ Adlam. Since: 2.50
    | UnicodeScriptBhaiksuki
    -- ^ Bhaiksuki. Since: 2.50
    | UnicodeScriptMarchen
    -- ^ Marchen. Since: 2.50
    | UnicodeScriptNewa
    -- ^ Newa. Since: 2.50
    | UnicodeScriptOsage
    -- ^ Osage. Since: 2.50
    | UnicodeScriptTangut
    -- ^ Tangut. Since: 2.50
    | UnicodeScriptMasaramGondi
    -- ^ Masaram Gondi. Since: 2.54
    | UnicodeScriptNushu
    -- ^ Nushu. Since: 2.54
    | UnicodeScriptSoyombo
    -- ^ Soyombo. Since: 2.54
    | UnicodeScriptZanabazarSquare
    -- ^ Zanabazar Square. Since: 2.54
    | UnicodeScriptDogra
    -- ^ Dogra. Since: 2.58
    | UnicodeScriptGunjalaGondi
    -- ^ Gunjala Gondi. Since: 2.58
    | UnicodeScriptHanifiRohingya
    -- ^ Hanifi Rohingya. Since: 2.58
    | UnicodeScriptMakasar
    -- ^ Makasar. Since: 2.58
    | UnicodeScriptMedefaidrin
    -- ^ Medefaidrin. Since: 2.58
    | UnicodeScriptOldSogdian
    -- ^ Old Sogdian. Since: 2.58
    | UnicodeScriptSogdian
    -- ^ Sogdian. Since: 2.58
    | UnicodeScriptElymaic
    -- ^ Elym. Since: 2.62
    | UnicodeScriptNandinagari
    -- ^ Nand. Since: 2.62
    | UnicodeScriptNyiakengPuachueHmong
    -- ^ Rohg. Since: 2.62
    | UnicodeScriptWancho
    -- ^ Wcho. Since: 2.62
    | UnicodeScriptChorasmian
    -- ^ Chorasmian. Since: 2.66
    | UnicodeScriptDivesAkuru
    -- ^ Dives Akuru. Since: 2.66
    | UnicodeScriptKhitanSmallScript
    -- ^ Khitan small script. Since: 2.66
    | UnicodeScriptYezidi
    -- ^ Yezidi. Since: 2.66
    | UnicodeScriptCyproMinoan
    -- ^ Cypro-Minoan. Since: 2.72
    | UnicodeScriptOldUyghur
    -- ^ Old Uyghur. Since: 2.72
    | UnicodeScriptTangsa
    -- ^ Tangsa. Since: 2.72
    | UnicodeScriptToto
    -- ^ Toto. Since: 2.72
    | UnicodeScriptVithkuqi
    -- ^ Vithkuqi. Since: 2.72
    | UnicodeScriptMath
    -- ^ Mathematical notation. Since: 2.72
    | AnotherUnicodeScript Int
    -- ^ Catch-all for unknown values
    deriving (Int -> UnicodeScript -> ShowS
[UnicodeScript] -> ShowS
UnicodeScript -> String
(Int -> UnicodeScript -> ShowS)
-> (UnicodeScript -> String)
-> ([UnicodeScript] -> ShowS)
-> Show UnicodeScript
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> UnicodeScript -> ShowS
showsPrec :: Int -> UnicodeScript -> ShowS
$cshow :: UnicodeScript -> String
show :: UnicodeScript -> String
$cshowList :: [UnicodeScript] -> ShowS
showList :: [UnicodeScript] -> ShowS
Show, UnicodeScript -> UnicodeScript -> Bool
(UnicodeScript -> UnicodeScript -> Bool)
-> (UnicodeScript -> UnicodeScript -> Bool) -> Eq UnicodeScript
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: UnicodeScript -> UnicodeScript -> Bool
== :: UnicodeScript -> UnicodeScript -> Bool
$c/= :: UnicodeScript -> UnicodeScript -> Bool
/= :: UnicodeScript -> UnicodeScript -> Bool
Eq)

instance P.Enum UnicodeScript where
    fromEnum :: UnicodeScript -> Int
fromEnum UnicodeScript
UnicodeScriptInvalidCode = Int
-1
    fromEnum UnicodeScript
UnicodeScriptCommon = Int
0
    fromEnum UnicodeScript
UnicodeScriptInherited = Int
1
    fromEnum UnicodeScript
UnicodeScriptArabic = Int
2
    fromEnum UnicodeScript
UnicodeScriptArmenian = Int
3
    fromEnum UnicodeScript
UnicodeScriptBengali = Int
4
    fromEnum UnicodeScript
UnicodeScriptBopomofo = Int
5
    fromEnum UnicodeScript
UnicodeScriptCherokee = Int
6
    fromEnum UnicodeScript
UnicodeScriptCoptic = Int
7
    fromEnum UnicodeScript
UnicodeScriptCyrillic = Int
8
    fromEnum UnicodeScript
UnicodeScriptDeseret = Int
9
    fromEnum UnicodeScript
UnicodeScriptDevanagari = Int
10
    fromEnum UnicodeScript
UnicodeScriptEthiopic = Int
11
    fromEnum UnicodeScript
UnicodeScriptGeorgian = Int
12
    fromEnum UnicodeScript
UnicodeScriptGothic = Int
13
    fromEnum UnicodeScript
UnicodeScriptGreek = Int
14
    fromEnum UnicodeScript
UnicodeScriptGujarati = Int
15
    fromEnum UnicodeScript
UnicodeScriptGurmukhi = Int
16
    fromEnum UnicodeScript
UnicodeScriptHan = Int
17
    fromEnum UnicodeScript
UnicodeScriptHangul = Int
18
    fromEnum UnicodeScript
UnicodeScriptHebrew = Int
19
    fromEnum UnicodeScript
UnicodeScriptHiragana = Int
20
    fromEnum UnicodeScript
UnicodeScriptKannada = Int
21
    fromEnum UnicodeScript
UnicodeScriptKatakana = Int
22
    fromEnum UnicodeScript
UnicodeScriptKhmer = Int
23
    fromEnum UnicodeScript
UnicodeScriptLao = Int
24
    fromEnum UnicodeScript
UnicodeScriptLatin = Int
25
    fromEnum UnicodeScript
UnicodeScriptMalayalam = Int
26
    fromEnum UnicodeScript
UnicodeScriptMongolian = Int
27
    fromEnum UnicodeScript
UnicodeScriptMyanmar = Int
28
    fromEnum UnicodeScript
UnicodeScriptOgham = Int
29
    fromEnum UnicodeScript
UnicodeScriptOldItalic = Int
30
    fromEnum UnicodeScript
UnicodeScriptOriya = Int
31
    fromEnum UnicodeScript
UnicodeScriptRunic = Int
32
    fromEnum UnicodeScript
UnicodeScriptSinhala = Int
33
    fromEnum UnicodeScript
UnicodeScriptSyriac = Int
34
    fromEnum UnicodeScript
UnicodeScriptTamil = Int
35
    fromEnum UnicodeScript
UnicodeScriptTelugu = Int
36
    fromEnum UnicodeScript
UnicodeScriptThaana = Int
37
    fromEnum UnicodeScript
UnicodeScriptThai = Int
38
    fromEnum UnicodeScript
UnicodeScriptTibetan = Int
39
    fromEnum UnicodeScript
UnicodeScriptCanadianAboriginal = Int
40
    fromEnum UnicodeScript
UnicodeScriptYi = Int
41
    fromEnum UnicodeScript
UnicodeScriptTagalog = Int
42
    fromEnum UnicodeScript
UnicodeScriptHanunoo = Int
43
    fromEnum UnicodeScript
UnicodeScriptBuhid = Int
44
    fromEnum UnicodeScript
UnicodeScriptTagbanwa = Int
45
    fromEnum UnicodeScript
UnicodeScriptBraille = Int
46
    fromEnum UnicodeScript
UnicodeScriptCypriot = Int
47
    fromEnum UnicodeScript
UnicodeScriptLimbu = Int
48
    fromEnum UnicodeScript
UnicodeScriptOsmanya = Int
49
    fromEnum UnicodeScript
UnicodeScriptShavian = Int
50
    fromEnum UnicodeScript
UnicodeScriptLinearB = Int
51
    fromEnum UnicodeScript
UnicodeScriptTaiLe = Int
52
    fromEnum UnicodeScript
UnicodeScriptUgaritic = Int
53
    fromEnum UnicodeScript
UnicodeScriptNewTaiLue = Int
54
    fromEnum UnicodeScript
UnicodeScriptBuginese = Int
55
    fromEnum UnicodeScript
UnicodeScriptGlagolitic = Int
56
    fromEnum UnicodeScript
UnicodeScriptTifinagh = Int
57
    fromEnum UnicodeScript
UnicodeScriptSylotiNagri = Int
58
    fromEnum UnicodeScript
UnicodeScriptOldPersian = Int
59
    fromEnum UnicodeScript
UnicodeScriptKharoshthi = Int
60
    fromEnum UnicodeScript
UnicodeScriptUnknown = Int
61
    fromEnum UnicodeScript
UnicodeScriptBalinese = Int
62
    fromEnum UnicodeScript
UnicodeScriptCuneiform = Int
63
    fromEnum UnicodeScript
UnicodeScriptPhoenician = Int
64
    fromEnum UnicodeScript
UnicodeScriptPhagsPa = Int
65
    fromEnum UnicodeScript
UnicodeScriptNko = Int
66
    fromEnum UnicodeScript
UnicodeScriptKayahLi = Int
67
    fromEnum UnicodeScript
UnicodeScriptLepcha = Int
68
    fromEnum UnicodeScript
UnicodeScriptRejang = Int
69
    fromEnum UnicodeScript
UnicodeScriptSundanese = Int
70
    fromEnum UnicodeScript
UnicodeScriptSaurashtra = Int
71
    fromEnum UnicodeScript
UnicodeScriptCham = Int
72
    fromEnum UnicodeScript
UnicodeScriptOlChiki = Int
73
    fromEnum UnicodeScript
UnicodeScriptVai = Int
74
    fromEnum UnicodeScript
UnicodeScriptCarian = Int
75
    fromEnum UnicodeScript
UnicodeScriptLycian = Int
76
    fromEnum UnicodeScript
UnicodeScriptLydian = Int
77
    fromEnum UnicodeScript
UnicodeScriptAvestan = Int
78
    fromEnum UnicodeScript
UnicodeScriptBamum = Int
79
    fromEnum UnicodeScript
UnicodeScriptEgyptianHieroglyphs = Int
80
    fromEnum UnicodeScript
UnicodeScriptImperialAramaic = Int
81
    fromEnum UnicodeScript
UnicodeScriptInscriptionalPahlavi = Int
82
    fromEnum UnicodeScript
UnicodeScriptInscriptionalParthian = Int
83
    fromEnum UnicodeScript
UnicodeScriptJavanese = Int
84
    fromEnum UnicodeScript
UnicodeScriptKaithi = Int
85
    fromEnum UnicodeScript
UnicodeScriptLisu = Int
86
    fromEnum UnicodeScript
UnicodeScriptMeeteiMayek = Int
87
    fromEnum UnicodeScript
UnicodeScriptOldSouthArabian = Int
88
    fromEnum UnicodeScript
UnicodeScriptOldTurkic = Int
89
    fromEnum UnicodeScript
UnicodeScriptSamaritan = Int
90
    fromEnum UnicodeScript
UnicodeScriptTaiTham = Int
91
    fromEnum UnicodeScript
UnicodeScriptTaiViet = Int
92
    fromEnum UnicodeScript
UnicodeScriptBatak = Int
93
    fromEnum UnicodeScript
UnicodeScriptBrahmi = Int
94
    fromEnum UnicodeScript
UnicodeScriptMandaic = Int
95
    fromEnum UnicodeScript
UnicodeScriptChakma = Int
96
    fromEnum UnicodeScript
UnicodeScriptMeroiticCursive = Int
97
    fromEnum UnicodeScript
UnicodeScriptMeroiticHieroglyphs = Int
98
    fromEnum UnicodeScript
UnicodeScriptMiao = Int
99
    fromEnum UnicodeScript
UnicodeScriptSharada = Int
100
    fromEnum UnicodeScript
UnicodeScriptSoraSompeng = Int
101
    fromEnum UnicodeScript
UnicodeScriptTakri = Int
102
    fromEnum UnicodeScript
UnicodeScriptBassaVah = Int
103
    fromEnum UnicodeScript
UnicodeScriptCaucasianAlbanian = Int
104
    fromEnum UnicodeScript
UnicodeScriptDuployan = Int
105
    fromEnum UnicodeScript
UnicodeScriptElbasan = Int
106
    fromEnum UnicodeScript
UnicodeScriptGrantha = Int
107
    fromEnum UnicodeScript
UnicodeScriptKhojki = Int
108
    fromEnum UnicodeScript
UnicodeScriptKhudawadi = Int
109
    fromEnum UnicodeScript
UnicodeScriptLinearA = Int
110
    fromEnum UnicodeScript
UnicodeScriptMahajani = Int
111
    fromEnum UnicodeScript
UnicodeScriptManichaean = Int
112
    fromEnum UnicodeScript
UnicodeScriptMendeKikakui = Int
113
    fromEnum UnicodeScript
UnicodeScriptModi = Int
114
    fromEnum UnicodeScript
UnicodeScriptMro = Int
115
    fromEnum UnicodeScript
UnicodeScriptNabataean = Int
116
    fromEnum UnicodeScript
UnicodeScriptOldNorthArabian = Int
117
    fromEnum UnicodeScript
UnicodeScriptOldPermic = Int
118
    fromEnum UnicodeScript
UnicodeScriptPahawhHmong = Int
119
    fromEnum UnicodeScript
UnicodeScriptPalmyrene = Int
120
    fromEnum UnicodeScript
UnicodeScriptPauCinHau = Int
121
    fromEnum UnicodeScript
UnicodeScriptPsalterPahlavi = Int
122
    fromEnum UnicodeScript
UnicodeScriptSiddham = Int
123
    fromEnum UnicodeScript
UnicodeScriptTirhuta = Int
124
    fromEnum UnicodeScript
UnicodeScriptWarangCiti = Int
125
    fromEnum UnicodeScript
UnicodeScriptAhom = Int
126
    fromEnum UnicodeScript
UnicodeScriptAnatolianHieroglyphs = Int
127
    fromEnum UnicodeScript
UnicodeScriptHatran = Int
128
    fromEnum UnicodeScript
UnicodeScriptMultani = Int
129
    fromEnum UnicodeScript
UnicodeScriptOldHungarian = Int
130
    fromEnum UnicodeScript
UnicodeScriptSignwriting = Int
131
    fromEnum UnicodeScript
UnicodeScriptAdlam = Int
132
    fromEnum UnicodeScript
UnicodeScriptBhaiksuki = Int
133
    fromEnum UnicodeScript
UnicodeScriptMarchen = Int
134
    fromEnum UnicodeScript
UnicodeScriptNewa = Int
135
    fromEnum UnicodeScript
UnicodeScriptOsage = Int
136
    fromEnum UnicodeScript
UnicodeScriptTangut = Int
137
    fromEnum UnicodeScript
UnicodeScriptMasaramGondi = Int
138
    fromEnum UnicodeScript
UnicodeScriptNushu = Int
139
    fromEnum UnicodeScript
UnicodeScriptSoyombo = Int
140
    fromEnum UnicodeScript
UnicodeScriptZanabazarSquare = Int
141
    fromEnum UnicodeScript
UnicodeScriptDogra = Int
142
    fromEnum UnicodeScript
UnicodeScriptGunjalaGondi = Int
143
    fromEnum UnicodeScript
UnicodeScriptHanifiRohingya = Int
144
    fromEnum UnicodeScript
UnicodeScriptMakasar = Int
145
    fromEnum UnicodeScript
UnicodeScriptMedefaidrin = Int
146
    fromEnum UnicodeScript
UnicodeScriptOldSogdian = Int
147
    fromEnum UnicodeScript
UnicodeScriptSogdian = Int
148
    fromEnum UnicodeScript
UnicodeScriptElymaic = Int
149
    fromEnum UnicodeScript
UnicodeScriptNandinagari = Int
150
    fromEnum UnicodeScript
UnicodeScriptNyiakengPuachueHmong = Int
151
    fromEnum UnicodeScript
UnicodeScriptWancho = Int
152
    fromEnum UnicodeScript
UnicodeScriptChorasmian = Int
153
    fromEnum UnicodeScript
UnicodeScriptDivesAkuru = Int
154
    fromEnum UnicodeScript
UnicodeScriptKhitanSmallScript = Int
155
    fromEnum UnicodeScript
UnicodeScriptYezidi = Int
156
    fromEnum UnicodeScript
UnicodeScriptCyproMinoan = Int
157
    fromEnum UnicodeScript
UnicodeScriptOldUyghur = Int
158
    fromEnum UnicodeScript
UnicodeScriptTangsa = Int
159
    fromEnum UnicodeScript
UnicodeScriptToto = Int
160
    fromEnum UnicodeScript
UnicodeScriptVithkuqi = Int
161
    fromEnum UnicodeScript
UnicodeScriptMath = Int
162
    fromEnum (AnotherUnicodeScript Int
k) = Int
k

    toEnum :: Int -> UnicodeScript
toEnum Int
-1 = UnicodeScript
UnicodeScriptInvalidCode
    toEnum Int
0 = UnicodeScript
UnicodeScriptCommon
    toEnum Int
1 = UnicodeScript
UnicodeScriptInherited
    toEnum Int
2 = UnicodeScript
UnicodeScriptArabic
    toEnum Int
3 = UnicodeScript
UnicodeScriptArmenian
    toEnum Int
4 = UnicodeScript
UnicodeScriptBengali
    toEnum Int
5 = UnicodeScript
UnicodeScriptBopomofo
    toEnum Int
6 = UnicodeScript
UnicodeScriptCherokee
    toEnum Int
7 = UnicodeScript
UnicodeScriptCoptic
    toEnum Int
8 = UnicodeScript
UnicodeScriptCyrillic
    toEnum Int
9 = UnicodeScript
UnicodeScriptDeseret
    toEnum Int
10 = UnicodeScript
UnicodeScriptDevanagari
    toEnum Int
11 = UnicodeScript
UnicodeScriptEthiopic
    toEnum Int
12 = UnicodeScript
UnicodeScriptGeorgian
    toEnum Int
13 = UnicodeScript
UnicodeScriptGothic
    toEnum Int
14 = UnicodeScript
UnicodeScriptGreek
    toEnum Int
15 = UnicodeScript
UnicodeScriptGujarati
    toEnum Int
16 = UnicodeScript
UnicodeScriptGurmukhi
    toEnum Int
17 = UnicodeScript
UnicodeScriptHan
    toEnum Int
18 = UnicodeScript
UnicodeScriptHangul
    toEnum Int
19 = UnicodeScript
UnicodeScriptHebrew
    toEnum Int
20 = UnicodeScript
UnicodeScriptHiragana
    toEnum Int
21 = UnicodeScript
UnicodeScriptKannada
    toEnum Int
22 = UnicodeScript
UnicodeScriptKatakana
    toEnum Int
23 = UnicodeScript
UnicodeScriptKhmer
    toEnum Int
24 = UnicodeScript
UnicodeScriptLao
    toEnum Int
25 = UnicodeScript
UnicodeScriptLatin
    toEnum Int
26 = UnicodeScript
UnicodeScriptMalayalam
    toEnum Int
27 = UnicodeScript
UnicodeScriptMongolian
    toEnum Int
28 = UnicodeScript
UnicodeScriptMyanmar
    toEnum Int
29 = UnicodeScript
UnicodeScriptOgham
    toEnum Int
30 = UnicodeScript
UnicodeScriptOldItalic
    toEnum Int
31 = UnicodeScript
UnicodeScriptOriya
    toEnum Int
32 = UnicodeScript
UnicodeScriptRunic
    toEnum Int
33 = UnicodeScript
UnicodeScriptSinhala
    toEnum Int
34 = UnicodeScript
UnicodeScriptSyriac
    toEnum Int
35 = UnicodeScript
UnicodeScriptTamil
    toEnum Int
36 = UnicodeScript
UnicodeScriptTelugu
    toEnum Int
37 = UnicodeScript
UnicodeScriptThaana
    toEnum Int
38 = UnicodeScript
UnicodeScriptThai
    toEnum Int
39 = UnicodeScript
UnicodeScriptTibetan
    toEnum Int
40 = UnicodeScript
UnicodeScriptCanadianAboriginal
    toEnum Int
41 = UnicodeScript
UnicodeScriptYi
    toEnum Int
42 = UnicodeScript
UnicodeScriptTagalog
    toEnum Int
43 = UnicodeScript
UnicodeScriptHanunoo
    toEnum Int
44 = UnicodeScript
UnicodeScriptBuhid
    toEnum Int
45 = UnicodeScript
UnicodeScriptTagbanwa
    toEnum Int
46 = UnicodeScript
UnicodeScriptBraille
    toEnum Int
47 = UnicodeScript
UnicodeScriptCypriot
    toEnum Int
48 = UnicodeScript
UnicodeScriptLimbu
    toEnum Int
49 = UnicodeScript
UnicodeScriptOsmanya
    toEnum Int
50 = UnicodeScript
UnicodeScriptShavian
    toEnum Int
51 = UnicodeScript
UnicodeScriptLinearB
    toEnum Int
52 = UnicodeScript
UnicodeScriptTaiLe
    toEnum Int
53 = UnicodeScript
UnicodeScriptUgaritic
    toEnum Int
54 = UnicodeScript
UnicodeScriptNewTaiLue
    toEnum Int
55 = UnicodeScript
UnicodeScriptBuginese
    toEnum Int
56 = UnicodeScript
UnicodeScriptGlagolitic
    toEnum Int
57 = UnicodeScript
UnicodeScriptTifinagh
    toEnum Int
58 = UnicodeScript
UnicodeScriptSylotiNagri
    toEnum Int
59 = UnicodeScript
UnicodeScriptOldPersian
    toEnum Int
60 = UnicodeScript
UnicodeScriptKharoshthi
    toEnum Int
61 = UnicodeScript
UnicodeScriptUnknown
    toEnum Int
62 = UnicodeScript
UnicodeScriptBalinese
    toEnum Int
63 = UnicodeScript
UnicodeScriptCuneiform
    toEnum Int
64 = UnicodeScript
UnicodeScriptPhoenician
    toEnum Int
65 = UnicodeScript
UnicodeScriptPhagsPa
    toEnum Int
66 = UnicodeScript
UnicodeScriptNko
    toEnum Int
67 = UnicodeScript
UnicodeScriptKayahLi
    toEnum Int
68 = UnicodeScript
UnicodeScriptLepcha
    toEnum Int
69 = UnicodeScript
UnicodeScriptRejang
    toEnum Int
70 = UnicodeScript
UnicodeScriptSundanese
    toEnum Int
71 = UnicodeScript
UnicodeScriptSaurashtra
    toEnum Int
72 = UnicodeScript
UnicodeScriptCham
    toEnum Int
73 = UnicodeScript
UnicodeScriptOlChiki
    toEnum Int
74 = UnicodeScript
UnicodeScriptVai
    toEnum Int
75 = UnicodeScript
UnicodeScriptCarian
    toEnum Int
76 = UnicodeScript
UnicodeScriptLycian
    toEnum Int
77 = UnicodeScript
UnicodeScriptLydian
    toEnum Int
78 = UnicodeScript
UnicodeScriptAvestan
    toEnum Int
79 = UnicodeScript
UnicodeScriptBamum
    toEnum Int
80 = UnicodeScript
UnicodeScriptEgyptianHieroglyphs
    toEnum Int
81 = UnicodeScript
UnicodeScriptImperialAramaic
    toEnum Int
82 = UnicodeScript
UnicodeScriptInscriptionalPahlavi
    toEnum Int
83 = UnicodeScript
UnicodeScriptInscriptionalParthian
    toEnum Int
84 = UnicodeScript
UnicodeScriptJavanese
    toEnum Int
85 = UnicodeScript
UnicodeScriptKaithi
    toEnum Int
86 = UnicodeScript
UnicodeScriptLisu
    toEnum Int
87 = UnicodeScript
UnicodeScriptMeeteiMayek
    toEnum Int
88 = UnicodeScript
UnicodeScriptOldSouthArabian
    toEnum Int
89 = UnicodeScript
UnicodeScriptOldTurkic
    toEnum Int
90 = UnicodeScript
UnicodeScriptSamaritan
    toEnum Int
91 = UnicodeScript
UnicodeScriptTaiTham
    toEnum Int
92 = UnicodeScript
UnicodeScriptTaiViet
    toEnum Int
93 = UnicodeScript
UnicodeScriptBatak
    toEnum Int
94 = UnicodeScript
UnicodeScriptBrahmi
    toEnum Int
95 = UnicodeScript
UnicodeScriptMandaic
    toEnum Int
96 = UnicodeScript
UnicodeScriptChakma
    toEnum Int
97 = UnicodeScript
UnicodeScriptMeroiticCursive
    toEnum Int
98 = UnicodeScript
UnicodeScriptMeroiticHieroglyphs
    toEnum Int
99 = UnicodeScript
UnicodeScriptMiao
    toEnum Int
100 = UnicodeScript
UnicodeScriptSharada
    toEnum Int
101 = UnicodeScript
UnicodeScriptSoraSompeng
    toEnum Int
102 = UnicodeScript
UnicodeScriptTakri
    toEnum Int
103 = UnicodeScript
UnicodeScriptBassaVah
    toEnum Int
104 = UnicodeScript
UnicodeScriptCaucasianAlbanian
    toEnum Int
105 = UnicodeScript
UnicodeScriptDuployan
    toEnum Int
106 = UnicodeScript
UnicodeScriptElbasan
    toEnum Int
107 = UnicodeScript
UnicodeScriptGrantha
    toEnum Int
108 = UnicodeScript
UnicodeScriptKhojki
    toEnum Int
109 = UnicodeScript
UnicodeScriptKhudawadi
    toEnum Int
110 = UnicodeScript
UnicodeScriptLinearA
    toEnum Int
111 = UnicodeScript
UnicodeScriptMahajani
    toEnum Int
112 = UnicodeScript
UnicodeScriptManichaean
    toEnum Int
113 = UnicodeScript
UnicodeScriptMendeKikakui
    toEnum Int
114 = UnicodeScript
UnicodeScriptModi
    toEnum Int
115 = UnicodeScript
UnicodeScriptMro
    toEnum Int
116 = UnicodeScript
UnicodeScriptNabataean
    toEnum Int
117 = UnicodeScript
UnicodeScriptOldNorthArabian
    toEnum Int
118 = UnicodeScript
UnicodeScriptOldPermic
    toEnum Int
119 = UnicodeScript
UnicodeScriptPahawhHmong
    toEnum Int
120 = UnicodeScript
UnicodeScriptPalmyrene
    toEnum Int
121 = UnicodeScript
UnicodeScriptPauCinHau
    toEnum Int
122 = UnicodeScript
UnicodeScriptPsalterPahlavi
    toEnum Int
123 = UnicodeScript
UnicodeScriptSiddham
    toEnum Int
124 = UnicodeScript
UnicodeScriptTirhuta
    toEnum Int
125 = UnicodeScript
UnicodeScriptWarangCiti
    toEnum Int
126 = UnicodeScript
UnicodeScriptAhom
    toEnum Int
127 = UnicodeScript
UnicodeScriptAnatolianHieroglyphs
    toEnum Int
128 = UnicodeScript
UnicodeScriptHatran
    toEnum Int
129 = UnicodeScript
UnicodeScriptMultani
    toEnum Int
130 = UnicodeScript
UnicodeScriptOldHungarian
    toEnum Int
131 = UnicodeScript
UnicodeScriptSignwriting
    toEnum Int
132 = UnicodeScript
UnicodeScriptAdlam
    toEnum Int
133 = UnicodeScript
UnicodeScriptBhaiksuki
    toEnum Int
134 = UnicodeScript
UnicodeScriptMarchen
    toEnum Int
135 = UnicodeScript
UnicodeScriptNewa
    toEnum Int
136 = UnicodeScript
UnicodeScriptOsage
    toEnum Int
137 = UnicodeScript
UnicodeScriptTangut
    toEnum Int
138 = UnicodeScript
UnicodeScriptMasaramGondi
    toEnum Int
139 = UnicodeScript
UnicodeScriptNushu
    toEnum Int
140 = UnicodeScript
UnicodeScriptSoyombo
    toEnum Int
141 = UnicodeScript
UnicodeScriptZanabazarSquare
    toEnum Int
142 = UnicodeScript
UnicodeScriptDogra
    toEnum Int
143 = UnicodeScript
UnicodeScriptGunjalaGondi
    toEnum Int
144 = UnicodeScript
UnicodeScriptHanifiRohingya
    toEnum Int
145 = UnicodeScript
UnicodeScriptMakasar
    toEnum Int
146 = UnicodeScript
UnicodeScriptMedefaidrin
    toEnum Int
147 = UnicodeScript
UnicodeScriptOldSogdian
    toEnum Int
148 = UnicodeScript
UnicodeScriptSogdian
    toEnum Int
149 = UnicodeScript
UnicodeScriptElymaic
    toEnum Int
150 = UnicodeScript
UnicodeScriptNandinagari
    toEnum Int
151 = UnicodeScript
UnicodeScriptNyiakengPuachueHmong
    toEnum Int
152 = UnicodeScript
UnicodeScriptWancho
    toEnum Int
153 = UnicodeScript
UnicodeScriptChorasmian
    toEnum Int
154 = UnicodeScript
UnicodeScriptDivesAkuru
    toEnum Int
155 = UnicodeScript
UnicodeScriptKhitanSmallScript
    toEnum Int
156 = UnicodeScript
UnicodeScriptYezidi
    toEnum Int
157 = UnicodeScript
UnicodeScriptCyproMinoan
    toEnum Int
158 = UnicodeScript
UnicodeScriptOldUyghur
    toEnum Int
159 = UnicodeScript
UnicodeScriptTangsa
    toEnum Int
160 = UnicodeScript
UnicodeScriptToto
    toEnum Int
161 = UnicodeScript
UnicodeScriptVithkuqi
    toEnum Int
162 = UnicodeScript
UnicodeScriptMath
    toEnum Int
k = Int -> UnicodeScript
AnotherUnicodeScript Int
k

instance P.Ord UnicodeScript where
    compare :: UnicodeScript -> UnicodeScript -> Ordering
compare UnicodeScript
a UnicodeScript
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (UnicodeScript -> Int
forall a. Enum a => a -> Int
P.fromEnum UnicodeScript
a) (UnicodeScript -> Int
forall a. Enum a => a -> Int
P.fromEnum UnicodeScript
b)

-- Enum UnicodeBreakType
-- | These are the possible line break classifications.
-- 
-- Since new unicode versions may add new types here, applications should be ready
-- to handle unknown values. They may be regarded as 'GI.GLib.Enums.UnicodeBreakTypeUnknown'.
-- 
-- See <http://www.unicode.org/unicode/reports/tr14/ Unicode Line Breaking Algorithm>.
data UnicodeBreakType = 
      UnicodeBreakTypeMandatory
    -- ^ Mandatory Break (BK)
    | UnicodeBreakTypeCarriageReturn
    -- ^ Carriage Return (CR)
    | UnicodeBreakTypeLineFeed
    -- ^ Line Feed (LF)
    | UnicodeBreakTypeCombiningMark
    -- ^ Attached Characters and Combining Marks (CM)
    | UnicodeBreakTypeSurrogate
    -- ^ Surrogates (SG)
    | UnicodeBreakTypeZeroWidthSpace
    -- ^ Zero Width Space (ZW)
    | UnicodeBreakTypeInseparable
    -- ^ Inseparable (IN)
    | UnicodeBreakTypeNonBreakingGlue
    -- ^ Non-breaking (\"Glue\") (GL)
    | UnicodeBreakTypeContingent
    -- ^ Contingent Break Opportunity (CB)
    | UnicodeBreakTypeSpace
    -- ^ Space (SP)
    | UnicodeBreakTypeAfter
    -- ^ Break Opportunity After (BA)
    | UnicodeBreakTypeBefore
    -- ^ Break Opportunity Before (BB)
    | UnicodeBreakTypeBeforeAndAfter
    -- ^ Break Opportunity Before and After (B2)
    | UnicodeBreakTypeHyphen
    -- ^ Hyphen (HY)
    | UnicodeBreakTypeNonStarter
    -- ^ Nonstarter (NS)
    | UnicodeBreakTypeOpenPunctuation
    -- ^ Opening Punctuation (OP)
    | UnicodeBreakTypeClosePunctuation
    -- ^ Closing Punctuation (CL)
    | UnicodeBreakTypeQuotation
    -- ^ Ambiguous Quotation (QU)
    | UnicodeBreakTypeExclamation
    -- ^ Exclamation\/Interrogation (EX)
    | UnicodeBreakTypeIdeographic
    -- ^ Ideographic (ID)
    | UnicodeBreakTypeNumeric
    -- ^ Numeric (NU)
    | UnicodeBreakTypeInfixSeparator
    -- ^ Infix Separator (Numeric) (IS)
    | UnicodeBreakTypeSymbol
    -- ^ Symbols Allowing Break After (SY)
    | UnicodeBreakTypeAlphabetic
    -- ^ Ordinary Alphabetic and Symbol Characters (AL)
    | UnicodeBreakTypePrefix
    -- ^ Prefix (Numeric) (PR)
    | UnicodeBreakTypePostfix
    -- ^ Postfix (Numeric) (PO)
    | UnicodeBreakTypeComplexContext
    -- ^ Complex Content Dependent (South East Asian) (SA)
    | UnicodeBreakTypeAmbiguous
    -- ^ Ambiguous (Alphabetic or Ideographic) (AI)
    | UnicodeBreakTypeUnknown
    -- ^ Unknown (XX)
    | UnicodeBreakTypeNextLine
    -- ^ Next Line (NL)
    | UnicodeBreakTypeWordJoiner
    -- ^ Word Joiner (WJ)
    | UnicodeBreakTypeHangulLJamo
    -- ^ Hangul L Jamo (JL)
    | UnicodeBreakTypeHangulVJamo
    -- ^ Hangul V Jamo (JV)
    | UnicodeBreakTypeHangulTJamo
    -- ^ Hangul T Jamo (JT)
    | UnicodeBreakTypeHangulLvSyllable
    -- ^ Hangul LV Syllable (H2)
    | UnicodeBreakTypeHangulLvtSyllable
    -- ^ Hangul LVT Syllable (H3)
    | UnicodeBreakTypeCloseParanthesis
    -- ^ Closing Parenthesis (CP). Since 2.28. Deprecated: 2.70: Use 'GI.GLib.Enums.UnicodeBreakTypeCloseParenthesis' instead.
    | UnicodeBreakTypeCloseParenthesis
    -- ^ Closing Parenthesis (CP). Since 2.70
    | UnicodeBreakTypeConditionalJapaneseStarter
    -- ^ Conditional Japanese Starter (CJ). Since: 2.32
    | UnicodeBreakTypeHebrewLetter
    -- ^ Hebrew Letter (HL). Since: 2.32
    | UnicodeBreakTypeRegionalIndicator
    -- ^ Regional Indicator (RI). Since: 2.36
    | UnicodeBreakTypeEmojiBase
    -- ^ Emoji Base (EB). Since: 2.50
    | UnicodeBreakTypeEmojiModifier
    -- ^ Emoji Modifier (EM). Since: 2.50
    | UnicodeBreakTypeZeroWidthJoiner
    -- ^ Zero Width Joiner (ZWJ). Since: 2.50
    | AnotherUnicodeBreakType Int
    -- ^ Catch-all for unknown values
    deriving (Int -> UnicodeBreakType -> ShowS
[UnicodeBreakType] -> ShowS
UnicodeBreakType -> String
(Int -> UnicodeBreakType -> ShowS)
-> (UnicodeBreakType -> String)
-> ([UnicodeBreakType] -> ShowS)
-> Show UnicodeBreakType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> UnicodeBreakType -> ShowS
showsPrec :: Int -> UnicodeBreakType -> ShowS
$cshow :: UnicodeBreakType -> String
show :: UnicodeBreakType -> String
$cshowList :: [UnicodeBreakType] -> ShowS
showList :: [UnicodeBreakType] -> ShowS
Show, UnicodeBreakType -> UnicodeBreakType -> Bool
(UnicodeBreakType -> UnicodeBreakType -> Bool)
-> (UnicodeBreakType -> UnicodeBreakType -> Bool)
-> Eq UnicodeBreakType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: UnicodeBreakType -> UnicodeBreakType -> Bool
== :: UnicodeBreakType -> UnicodeBreakType -> Bool
$c/= :: UnicodeBreakType -> UnicodeBreakType -> Bool
/= :: UnicodeBreakType -> UnicodeBreakType -> Bool
Eq)

instance P.Enum UnicodeBreakType where
    fromEnum :: UnicodeBreakType -> Int
fromEnum UnicodeBreakType
UnicodeBreakTypeMandatory = Int
0
    fromEnum UnicodeBreakType
UnicodeBreakTypeCarriageReturn = Int
1
    fromEnum UnicodeBreakType
UnicodeBreakTypeLineFeed = Int
2
    fromEnum UnicodeBreakType
UnicodeBreakTypeCombiningMark = Int
3
    fromEnum UnicodeBreakType
UnicodeBreakTypeSurrogate = Int
4
    fromEnum UnicodeBreakType
UnicodeBreakTypeZeroWidthSpace = Int
5
    fromEnum UnicodeBreakType
UnicodeBreakTypeInseparable = Int
6
    fromEnum UnicodeBreakType
UnicodeBreakTypeNonBreakingGlue = Int
7
    fromEnum UnicodeBreakType
UnicodeBreakTypeContingent = Int
8
    fromEnum UnicodeBreakType
UnicodeBreakTypeSpace = Int
9
    fromEnum UnicodeBreakType
UnicodeBreakTypeAfter = Int
10
    fromEnum UnicodeBreakType
UnicodeBreakTypeBefore = Int
11
    fromEnum UnicodeBreakType
UnicodeBreakTypeBeforeAndAfter = Int
12
    fromEnum UnicodeBreakType
UnicodeBreakTypeHyphen = Int
13
    fromEnum UnicodeBreakType
UnicodeBreakTypeNonStarter = Int
14
    fromEnum UnicodeBreakType
UnicodeBreakTypeOpenPunctuation = Int
15
    fromEnum UnicodeBreakType
UnicodeBreakTypeClosePunctuation = Int
16
    fromEnum UnicodeBreakType
UnicodeBreakTypeQuotation = Int
17
    fromEnum UnicodeBreakType
UnicodeBreakTypeExclamation = Int
18
    fromEnum UnicodeBreakType
UnicodeBreakTypeIdeographic = Int
19
    fromEnum UnicodeBreakType
UnicodeBreakTypeNumeric = Int
20
    fromEnum UnicodeBreakType
UnicodeBreakTypeInfixSeparator = Int
21
    fromEnum UnicodeBreakType
UnicodeBreakTypeSymbol = Int
22
    fromEnum UnicodeBreakType
UnicodeBreakTypeAlphabetic = Int
23
    fromEnum UnicodeBreakType
UnicodeBreakTypePrefix = Int
24
    fromEnum UnicodeBreakType
UnicodeBreakTypePostfix = Int
25
    fromEnum UnicodeBreakType
UnicodeBreakTypeComplexContext = Int
26
    fromEnum UnicodeBreakType
UnicodeBreakTypeAmbiguous = Int
27
    fromEnum UnicodeBreakType
UnicodeBreakTypeUnknown = Int
28
    fromEnum UnicodeBreakType
UnicodeBreakTypeNextLine = Int
29
    fromEnum UnicodeBreakType
UnicodeBreakTypeWordJoiner = Int
30
    fromEnum UnicodeBreakType
UnicodeBreakTypeHangulLJamo = Int
31
    fromEnum UnicodeBreakType
UnicodeBreakTypeHangulVJamo = Int
32
    fromEnum UnicodeBreakType
UnicodeBreakTypeHangulTJamo = Int
33
    fromEnum UnicodeBreakType
UnicodeBreakTypeHangulLvSyllable = Int
34
    fromEnum UnicodeBreakType
UnicodeBreakTypeHangulLvtSyllable = Int
35
    fromEnum UnicodeBreakType
UnicodeBreakTypeCloseParanthesis = Int
36
    fromEnum UnicodeBreakType
UnicodeBreakTypeCloseParenthesis = Int
36
    fromEnum UnicodeBreakType
UnicodeBreakTypeConditionalJapaneseStarter = Int
37
    fromEnum UnicodeBreakType
UnicodeBreakTypeHebrewLetter = Int
38
    fromEnum UnicodeBreakType
UnicodeBreakTypeRegionalIndicator = Int
39
    fromEnum UnicodeBreakType
UnicodeBreakTypeEmojiBase = Int
40
    fromEnum UnicodeBreakType
UnicodeBreakTypeEmojiModifier = Int
41
    fromEnum UnicodeBreakType
UnicodeBreakTypeZeroWidthJoiner = Int
42
    fromEnum (AnotherUnicodeBreakType Int
k) = Int
k

    toEnum :: Int -> UnicodeBreakType
toEnum Int
0 = UnicodeBreakType
UnicodeBreakTypeMandatory
    toEnum Int
1 = UnicodeBreakType
UnicodeBreakTypeCarriageReturn
    toEnum Int
2 = UnicodeBreakType
UnicodeBreakTypeLineFeed
    toEnum Int
3 = UnicodeBreakType
UnicodeBreakTypeCombiningMark
    toEnum Int
4 = UnicodeBreakType
UnicodeBreakTypeSurrogate
    toEnum Int
5 = UnicodeBreakType
UnicodeBreakTypeZeroWidthSpace
    toEnum Int
6 = UnicodeBreakType
UnicodeBreakTypeInseparable
    toEnum Int
7 = UnicodeBreakType
UnicodeBreakTypeNonBreakingGlue
    toEnum Int
8 = UnicodeBreakType
UnicodeBreakTypeContingent
    toEnum Int
9 = UnicodeBreakType
UnicodeBreakTypeSpace
    toEnum Int
10 = UnicodeBreakType
UnicodeBreakTypeAfter
    toEnum Int
11 = UnicodeBreakType
UnicodeBreakTypeBefore
    toEnum Int
12 = UnicodeBreakType
UnicodeBreakTypeBeforeAndAfter
    toEnum Int
13 = UnicodeBreakType
UnicodeBreakTypeHyphen
    toEnum Int
14 = UnicodeBreakType
UnicodeBreakTypeNonStarter
    toEnum Int
15 = UnicodeBreakType
UnicodeBreakTypeOpenPunctuation
    toEnum Int
16 = UnicodeBreakType
UnicodeBreakTypeClosePunctuation
    toEnum Int
17 = UnicodeBreakType
UnicodeBreakTypeQuotation
    toEnum Int
18 = UnicodeBreakType
UnicodeBreakTypeExclamation
    toEnum Int
19 = UnicodeBreakType
UnicodeBreakTypeIdeographic
    toEnum Int
20 = UnicodeBreakType
UnicodeBreakTypeNumeric
    toEnum Int
21 = UnicodeBreakType
UnicodeBreakTypeInfixSeparator
    toEnum Int
22 = UnicodeBreakType
UnicodeBreakTypeSymbol
    toEnum Int
23 = UnicodeBreakType
UnicodeBreakTypeAlphabetic
    toEnum Int
24 = UnicodeBreakType
UnicodeBreakTypePrefix
    toEnum Int
25 = UnicodeBreakType
UnicodeBreakTypePostfix
    toEnum Int
26 = UnicodeBreakType
UnicodeBreakTypeComplexContext
    toEnum Int
27 = UnicodeBreakType
UnicodeBreakTypeAmbiguous
    toEnum Int
28 = UnicodeBreakType
UnicodeBreakTypeUnknown
    toEnum Int
29 = UnicodeBreakType
UnicodeBreakTypeNextLine
    toEnum Int
30 = UnicodeBreakType
UnicodeBreakTypeWordJoiner
    toEnum Int
31 = UnicodeBreakType
UnicodeBreakTypeHangulLJamo
    toEnum Int
32 = UnicodeBreakType
UnicodeBreakTypeHangulVJamo
    toEnum Int
33 = UnicodeBreakType
UnicodeBreakTypeHangulTJamo
    toEnum Int
34 = UnicodeBreakType
UnicodeBreakTypeHangulLvSyllable
    toEnum Int
35 = UnicodeBreakType
UnicodeBreakTypeHangulLvtSyllable
    toEnum Int
36 = UnicodeBreakType
UnicodeBreakTypeCloseParanthesis
    toEnum Int
37 = UnicodeBreakType
UnicodeBreakTypeConditionalJapaneseStarter
    toEnum Int
38 = UnicodeBreakType
UnicodeBreakTypeHebrewLetter
    toEnum Int
39 = UnicodeBreakType
UnicodeBreakTypeRegionalIndicator
    toEnum Int
40 = UnicodeBreakType
UnicodeBreakTypeEmojiBase
    toEnum Int
41 = UnicodeBreakType
UnicodeBreakTypeEmojiModifier
    toEnum Int
42 = UnicodeBreakType
UnicodeBreakTypeZeroWidthJoiner
    toEnum Int
k = Int -> UnicodeBreakType
AnotherUnicodeBreakType Int
k

instance P.Ord UnicodeBreakType where
    compare :: UnicodeBreakType -> UnicodeBreakType -> Ordering
compare UnicodeBreakType
a UnicodeBreakType
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (UnicodeBreakType -> Int
forall a. Enum a => a -> Int
P.fromEnum UnicodeBreakType
a) (UnicodeBreakType -> Int
forall a. Enum a => a -> Int
P.fromEnum UnicodeBreakType
b)

-- Enum TraverseType
-- | Specifies the type of traversal performed by @/g_tree_traverse()/@,
-- @/g_node_traverse()/@ and @/g_node_find()/@. The different orders are
-- illustrated here:
-- 
-- * In order: A, B, C, D, E, F, G, H, I
-- <<http://developer.gnome.org/glib/stable/Sorted_binary_tree_inorder.svg>>
-- * Pre order: F, B, A, D, C, E, G, I, H
-- <<http://developer.gnome.org/glib/stable/Sorted_binary_tree_preorder.svg>>
-- * Post order: A, C, E, D, B, H, I, G, F
-- <<http://developer.gnome.org/glib/stable/Sorted_binary_tree_postorder.svg>>
-- * Level order: F, B, G, A, D, I, C, E, H
-- <<http://developer.gnome.org/glib/stable/Sorted_binary_tree_breadth-first_traversal.svg>>
data TraverseType = 
      TraverseTypeInOrder
    -- ^ vists a node\'s left child first, then the node itself,
    --              then its right child. This is the one to use if you
    --              want the output sorted according to the compare
    --              function.
    | TraverseTypePreOrder
    -- ^ visits a node, then its children.
    | TraverseTypePostOrder
    -- ^ visits the node\'s children, then the node itself.
    | TraverseTypeLevelOrder
    -- ^ is not implemented for
    --              [balanced binary trees][glib-Balanced-Binary-Trees].
    --              For [n-ary trees][glib-N-ary-Trees], it
    --              vists the root node first, then its children, then
    --              its grandchildren, and so on. Note that this is less
    --              efficient than the other orders.
    | AnotherTraverseType Int
    -- ^ Catch-all for unknown values
    deriving (Int -> TraverseType -> ShowS
[TraverseType] -> ShowS
TraverseType -> String
(Int -> TraverseType -> ShowS)
-> (TraverseType -> String)
-> ([TraverseType] -> ShowS)
-> Show TraverseType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TraverseType -> ShowS
showsPrec :: Int -> TraverseType -> ShowS
$cshow :: TraverseType -> String
show :: TraverseType -> String
$cshowList :: [TraverseType] -> ShowS
showList :: [TraverseType] -> ShowS
Show, TraverseType -> TraverseType -> Bool
(TraverseType -> TraverseType -> Bool)
-> (TraverseType -> TraverseType -> Bool) -> Eq TraverseType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TraverseType -> TraverseType -> Bool
== :: TraverseType -> TraverseType -> Bool
$c/= :: TraverseType -> TraverseType -> Bool
/= :: TraverseType -> TraverseType -> Bool
Eq)

instance P.Enum TraverseType where
    fromEnum :: TraverseType -> Int
fromEnum TraverseType
TraverseTypeInOrder = Int
0
    fromEnum TraverseType
TraverseTypePreOrder = Int
1
    fromEnum TraverseType
TraverseTypePostOrder = Int
2
    fromEnum TraverseType
TraverseTypeLevelOrder = Int
3
    fromEnum (AnotherTraverseType Int
k) = Int
k

    toEnum :: Int -> TraverseType
toEnum Int
0 = TraverseType
TraverseTypeInOrder
    toEnum Int
1 = TraverseType
TraverseTypePreOrder
    toEnum Int
2 = TraverseType
TraverseTypePostOrder
    toEnum Int
3 = TraverseType
TraverseTypeLevelOrder
    toEnum Int
k = Int -> TraverseType
AnotherTraverseType Int
k

instance P.Ord TraverseType where
    compare :: TraverseType -> TraverseType -> Ordering
compare TraverseType
a TraverseType
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (TraverseType -> Int
forall a. Enum a => a -> Int
P.fromEnum TraverseType
a) (TraverseType -> Int
forall a. Enum a => a -> Int
P.fromEnum TraverseType
b)

-- Enum TokenType
-- | The possible types of token returned from each
-- 'GI.GLib.Structs.Scanner.scannerGetNextToken' call.
data TokenType = 
      TokenTypeEof
    -- ^ the end of the file
    | TokenTypeLeftParen
    -- ^ a \'(\' character
    | TokenTypeRightParen
    -- ^ a \')\' character
    | TokenTypeLeftCurly
    -- ^ a \'{\' character
    | TokenTypeRightCurly
    -- ^ a \'}\' character
    | TokenTypeLeftBrace
    -- ^ a \'[\' character
    | TokenTypeRightBrace
    -- ^ a \']\' character
    | TokenTypeEqualSign
    -- ^ a \'=\' character
    | TokenTypeComma
    -- ^ a \',\' character
    | TokenTypeNone
    -- ^ not a token
    | TokenTypeError
    -- ^ an error occurred
    | TokenTypeChar
    -- ^ a character
    | TokenTypeBinary
    -- ^ a binary integer
    | TokenTypeOctal
    -- ^ an octal integer
    | TokenTypeInt
    -- ^ an integer
    | TokenTypeHex
    -- ^ a hex integer
    | TokenTypeFloat
    -- ^ a floating point number
    | TokenTypeString
    -- ^ a string
    | TokenTypeSymbol
    -- ^ a symbol
    | TokenTypeIdentifier
    -- ^ an identifier
    | TokenTypeIdentifierNull
    -- ^ a null identifier
    | TokenTypeCommentSingle
    -- ^ one line comment
    | TokenTypeCommentMulti
    -- ^ multi line comment
    | AnotherTokenType Int
    -- ^ Catch-all for unknown values
    deriving (Int -> TokenType -> ShowS
[TokenType] -> ShowS
TokenType -> String
(Int -> TokenType -> ShowS)
-> (TokenType -> String)
-> ([TokenType] -> ShowS)
-> Show TokenType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TokenType -> ShowS
showsPrec :: Int -> TokenType -> ShowS
$cshow :: TokenType -> String
show :: TokenType -> String
$cshowList :: [TokenType] -> ShowS
showList :: [TokenType] -> ShowS
Show, TokenType -> TokenType -> Bool
(TokenType -> TokenType -> Bool)
-> (TokenType -> TokenType -> Bool) -> Eq TokenType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TokenType -> TokenType -> Bool
== :: TokenType -> TokenType -> Bool
$c/= :: TokenType -> TokenType -> Bool
/= :: TokenType -> TokenType -> Bool
Eq)

instance P.Enum TokenType where
    fromEnum :: TokenType -> Int
fromEnum TokenType
TokenTypeEof = Int
0
    fromEnum TokenType
TokenTypeLeftParen = Int
40
    fromEnum TokenType
TokenTypeRightParen = Int
41
    fromEnum TokenType
TokenTypeLeftCurly = Int
123
    fromEnum TokenType
TokenTypeRightCurly = Int
125
    fromEnum TokenType
TokenTypeLeftBrace = Int
91
    fromEnum TokenType
TokenTypeRightBrace = Int
93
    fromEnum TokenType
TokenTypeEqualSign = Int
61
    fromEnum TokenType
TokenTypeComma = Int
44
    fromEnum TokenType
TokenTypeNone = Int
256
    fromEnum TokenType
TokenTypeError = Int
257
    fromEnum TokenType
TokenTypeChar = Int
258
    fromEnum TokenType
TokenTypeBinary = Int
259
    fromEnum TokenType
TokenTypeOctal = Int
260
    fromEnum TokenType
TokenTypeInt = Int
261
    fromEnum TokenType
TokenTypeHex = Int
262
    fromEnum TokenType
TokenTypeFloat = Int
263
    fromEnum TokenType
TokenTypeString = Int
264
    fromEnum TokenType
TokenTypeSymbol = Int
265
    fromEnum TokenType
TokenTypeIdentifier = Int
266
    fromEnum TokenType
TokenTypeIdentifierNull = Int
267
    fromEnum TokenType
TokenTypeCommentSingle = Int
268
    fromEnum TokenType
TokenTypeCommentMulti = Int
269
    fromEnum (AnotherTokenType Int
k) = Int
k

    toEnum :: Int -> TokenType
toEnum Int
0 = TokenType
TokenTypeEof
    toEnum Int
40 = TokenType
TokenTypeLeftParen
    toEnum Int
41 = TokenType
TokenTypeRightParen
    toEnum Int
123 = TokenType
TokenTypeLeftCurly
    toEnum Int
125 = TokenType
TokenTypeRightCurly
    toEnum Int
91 = TokenType
TokenTypeLeftBrace
    toEnum Int
93 = TokenType
TokenTypeRightBrace
    toEnum Int
61 = TokenType
TokenTypeEqualSign
    toEnum Int
44 = TokenType
TokenTypeComma
    toEnum Int
256 = TokenType
TokenTypeNone
    toEnum Int
257 = TokenType
TokenTypeError
    toEnum Int
258 = TokenType
TokenTypeChar
    toEnum Int
259 = TokenType
TokenTypeBinary
    toEnum Int
260 = TokenType
TokenTypeOctal
    toEnum Int
261 = TokenType
TokenTypeInt
    toEnum Int
262 = TokenType
TokenTypeHex
    toEnum Int
263 = TokenType
TokenTypeFloat
    toEnum Int
264 = TokenType
TokenTypeString
    toEnum Int
265 = TokenType
TokenTypeSymbol
    toEnum Int
266 = TokenType
TokenTypeIdentifier
    toEnum Int
267 = TokenType
TokenTypeIdentifierNull
    toEnum Int
268 = TokenType
TokenTypeCommentSingle
    toEnum Int
269 = TokenType
TokenTypeCommentMulti
    toEnum Int
k = Int -> TokenType
AnotherTokenType Int
k

instance P.Ord TokenType where
    compare :: TokenType -> TokenType -> Ordering
compare TokenType
a TokenType
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (TokenType -> Int
forall a. Enum a => a -> Int
P.fromEnum TokenType
a) (TokenType -> Int
forall a. Enum a => a -> Int
P.fromEnum TokenType
b)

-- Enum TimeType
-- | Disambiguates a given time in two ways.
-- 
-- First, specifies if the given time is in universal or local time.
-- 
-- Second, if the time is in local time, specifies if it is local
-- standard time or local daylight time.  This is important for the case
-- where the same local time occurs twice (during daylight savings time
-- transitions, for example).
data TimeType = 
      TimeTypeStandard
    -- ^ the time is in local standard time
    | TimeTypeDaylight
    -- ^ the time is in local daylight time
    | TimeTypeUniversal
    -- ^ the time is in UTC
    | AnotherTimeType Int
    -- ^ Catch-all for unknown values
    deriving (Int -> TimeType -> ShowS
[TimeType] -> ShowS
TimeType -> String
(Int -> TimeType -> ShowS)
-> (TimeType -> String) -> ([TimeType] -> ShowS) -> Show TimeType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TimeType -> ShowS
showsPrec :: Int -> TimeType -> ShowS
$cshow :: TimeType -> String
show :: TimeType -> String
$cshowList :: [TimeType] -> ShowS
showList :: [TimeType] -> ShowS
Show, TimeType -> TimeType -> Bool
(TimeType -> TimeType -> Bool)
-> (TimeType -> TimeType -> Bool) -> Eq TimeType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TimeType -> TimeType -> Bool
== :: TimeType -> TimeType -> Bool
$c/= :: TimeType -> TimeType -> Bool
/= :: TimeType -> TimeType -> Bool
Eq)

instance P.Enum TimeType where
    fromEnum :: TimeType -> Int
fromEnum TimeType
TimeTypeStandard = Int
0
    fromEnum TimeType
TimeTypeDaylight = Int
1
    fromEnum TimeType
TimeTypeUniversal = Int
2
    fromEnum (AnotherTimeType Int
k) = Int
k

    toEnum :: Int -> TimeType
toEnum Int
0 = TimeType
TimeTypeStandard
    toEnum Int
1 = TimeType
TimeTypeDaylight
    toEnum Int
2 = TimeType
TimeTypeUniversal
    toEnum Int
k = Int -> TimeType
AnotherTimeType Int
k

instance P.Ord TimeType where
    compare :: TimeType -> TimeType -> Ordering
compare TimeType
a TimeType
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (TimeType -> Int
forall a. Enum a => a -> Int
P.fromEnum TimeType
a) (TimeType -> Int
forall a. Enum a => a -> Int
P.fromEnum TimeType
b)

-- Enum ThreadError
-- | Possible errors of thread related functions.
data ThreadError = 
      ThreadErrorThreadErrorAgain
    -- ^ a thread couldn\'t be created due to resource
    --                        shortage. Try again later.
    | AnotherThreadError Int
    -- ^ Catch-all for unknown values
    deriving (Int -> ThreadError -> ShowS
[ThreadError] -> ShowS
ThreadError -> String
(Int -> ThreadError -> ShowS)
-> (ThreadError -> String)
-> ([ThreadError] -> ShowS)
-> Show ThreadError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ThreadError -> ShowS
showsPrec :: Int -> ThreadError -> ShowS
$cshow :: ThreadError -> String
show :: ThreadError -> String
$cshowList :: [ThreadError] -> ShowS
showList :: [ThreadError] -> ShowS
Show, ThreadError -> ThreadError -> Bool
(ThreadError -> ThreadError -> Bool)
-> (ThreadError -> ThreadError -> Bool) -> Eq ThreadError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ThreadError -> ThreadError -> Bool
== :: ThreadError -> ThreadError -> Bool
$c/= :: ThreadError -> ThreadError -> Bool
/= :: ThreadError -> ThreadError -> Bool
Eq)

instance P.Enum ThreadError where
    fromEnum :: ThreadError -> Int
fromEnum ThreadError
ThreadErrorThreadErrorAgain = Int
0
    fromEnum (AnotherThreadError Int
k) = Int
k

    toEnum :: Int -> ThreadError
toEnum Int
0 = ThreadError
ThreadErrorThreadErrorAgain
    toEnum Int
k = Int -> ThreadError
AnotherThreadError Int
k

instance P.Ord ThreadError where
    compare :: ThreadError -> ThreadError -> Ordering
compare ThreadError
a ThreadError
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (ThreadError -> Int
forall a. Enum a => a -> Int
P.fromEnum ThreadError
a) (ThreadError -> Int
forall a. Enum a => a -> Int
P.fromEnum ThreadError
b)

instance GErrorClass ThreadError where
    gerrorClassDomain :: ThreadError -> Text
gerrorClassDomain ThreadError
_ = Text
"g_thread_error"

-- | Catch exceptions of type `ThreadError`. This is a specialized version of `Data.GI.Base.GError.catchGErrorJustDomain`.
catchThreadError ::
    IO a ->
    (ThreadError -> GErrorMessage -> IO a) ->
    IO a
catchThreadError :: forall a. IO a -> (ThreadError -> Text -> IO a) -> IO a
catchThreadError = IO a -> (ThreadError -> Text -> IO a) -> IO a
forall err a.
GErrorClass err =>
IO a -> (err -> Text -> IO a) -> IO a
catchGErrorJustDomain

-- | Handle exceptions of type `ThreadError`. This is a specialized version of `Data.GI.Base.GError.handleGErrorJustDomain`.
handleThreadError ::
    (ThreadError -> GErrorMessage -> IO a) ->
    IO a ->
    IO a
handleThreadError :: forall a. (ThreadError -> Text -> IO a) -> IO a -> IO a
handleThreadError = (ThreadError -> Text -> IO a) -> IO a -> IO a
forall err a.
GErrorClass err =>
(err -> Text -> IO a) -> IO a -> IO a
handleGErrorJustDomain

-- Enum TestResult
-- | /No description available in the introspection data./
data TestResult = 
      TestResultSuccess
    -- ^ /No description available in the introspection data./
    | TestResultSkipped
    -- ^ /No description available in the introspection data./
    | TestResultFailure
    -- ^ /No description available in the introspection data./
    | TestResultIncomplete
    -- ^ /No description available in the introspection data./
    | AnotherTestResult Int
    -- ^ Catch-all for unknown values
    deriving (Int -> TestResult -> ShowS
[TestResult] -> ShowS
TestResult -> String
(Int -> TestResult -> ShowS)
-> (TestResult -> String)
-> ([TestResult] -> ShowS)
-> Show TestResult
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TestResult -> ShowS
showsPrec :: Int -> TestResult -> ShowS
$cshow :: TestResult -> String
show :: TestResult -> String
$cshowList :: [TestResult] -> ShowS
showList :: [TestResult] -> ShowS
Show, TestResult -> TestResult -> Bool
(TestResult -> TestResult -> Bool)
-> (TestResult -> TestResult -> Bool) -> Eq TestResult
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TestResult -> TestResult -> Bool
== :: TestResult -> TestResult -> Bool
$c/= :: TestResult -> TestResult -> Bool
/= :: TestResult -> TestResult -> Bool
Eq)

instance P.Enum TestResult where
    fromEnum :: TestResult -> Int
fromEnum TestResult
TestResultSuccess = Int
0
    fromEnum TestResult
TestResultSkipped = Int
1
    fromEnum TestResult
TestResultFailure = Int
2
    fromEnum TestResult
TestResultIncomplete = Int
3
    fromEnum (AnotherTestResult Int
k) = Int
k

    toEnum :: Int -> TestResult
toEnum Int
0 = TestResult
TestResultSuccess
    toEnum Int
1 = TestResult
TestResultSkipped
    toEnum Int
2 = TestResult
TestResultFailure
    toEnum Int
3 = TestResult
TestResultIncomplete
    toEnum Int
k = Int -> TestResult
AnotherTestResult Int
k

instance P.Ord TestResult where
    compare :: TestResult -> TestResult -> Ordering
compare TestResult
a TestResult
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (TestResult -> Int
forall a. Enum a => a -> Int
P.fromEnum TestResult
a) (TestResult -> Int
forall a. Enum a => a -> Int
P.fromEnum TestResult
b)

-- Enum TestLogType
-- | /No description available in the introspection data./
data TestLogType = 
      TestLogTypeNone
    -- ^ /No description available in the introspection data./
    | TestLogTypeError
    -- ^ /No description available in the introspection data./
    | TestLogTypeStartBinary
    -- ^ /No description available in the introspection data./
    | TestLogTypeListCase
    -- ^ /No description available in the introspection data./
    | TestLogTypeSkipCase
    -- ^ /No description available in the introspection data./
    | TestLogTypeStartCase
    -- ^ /No description available in the introspection data./
    | TestLogTypeStopCase
    -- ^ /No description available in the introspection data./
    | TestLogTypeMinResult
    -- ^ /No description available in the introspection data./
    | TestLogTypeMaxResult
    -- ^ /No description available in the introspection data./
    | TestLogTypeMessage
    -- ^ /No description available in the introspection data./
    | TestLogTypeStartSuite
    -- ^ /No description available in the introspection data./
    | TestLogTypeStopSuite
    -- ^ /No description available in the introspection data./
    | AnotherTestLogType Int
    -- ^ Catch-all for unknown values
    deriving (Int -> TestLogType -> ShowS
[TestLogType] -> ShowS
TestLogType -> String
(Int -> TestLogType -> ShowS)
-> (TestLogType -> String)
-> ([TestLogType] -> ShowS)
-> Show TestLogType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TestLogType -> ShowS
showsPrec :: Int -> TestLogType -> ShowS
$cshow :: TestLogType -> String
show :: TestLogType -> String
$cshowList :: [TestLogType] -> ShowS
showList :: [TestLogType] -> ShowS
Show, TestLogType -> TestLogType -> Bool
(TestLogType -> TestLogType -> Bool)
-> (TestLogType -> TestLogType -> Bool) -> Eq TestLogType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TestLogType -> TestLogType -> Bool
== :: TestLogType -> TestLogType -> Bool
$c/= :: TestLogType -> TestLogType -> Bool
/= :: TestLogType -> TestLogType -> Bool
Eq)

instance P.Enum TestLogType where
    fromEnum :: TestLogType -> Int
fromEnum TestLogType
TestLogTypeNone = Int
0
    fromEnum TestLogType
TestLogTypeError = Int
1
    fromEnum TestLogType
TestLogTypeStartBinary = Int
2
    fromEnum TestLogType
TestLogTypeListCase = Int
3
    fromEnum TestLogType
TestLogTypeSkipCase = Int
4
    fromEnum TestLogType
TestLogTypeStartCase = Int
5
    fromEnum TestLogType
TestLogTypeStopCase = Int
6
    fromEnum TestLogType
TestLogTypeMinResult = Int
7
    fromEnum TestLogType
TestLogTypeMaxResult = Int
8
    fromEnum TestLogType
TestLogTypeMessage = Int
9
    fromEnum TestLogType
TestLogTypeStartSuite = Int
10
    fromEnum TestLogType
TestLogTypeStopSuite = Int
11
    fromEnum (AnotherTestLogType Int
k) = Int
k

    toEnum :: Int -> TestLogType
toEnum Int
0 = TestLogType
TestLogTypeNone
    toEnum Int
1 = TestLogType
TestLogTypeError
    toEnum Int
2 = TestLogType
TestLogTypeStartBinary
    toEnum Int
3 = TestLogType
TestLogTypeListCase
    toEnum Int
4 = TestLogType
TestLogTypeSkipCase
    toEnum Int
5 = TestLogType
TestLogTypeStartCase
    toEnum Int
6 = TestLogType
TestLogTypeStopCase
    toEnum Int
7 = TestLogType
TestLogTypeMinResult
    toEnum Int
8 = TestLogType
TestLogTypeMaxResult
    toEnum Int
9 = TestLogType
TestLogTypeMessage
    toEnum Int
10 = TestLogType
TestLogTypeStartSuite
    toEnum Int
11 = TestLogType
TestLogTypeStopSuite
    toEnum Int
k = Int -> TestLogType
AnotherTestLogType Int
k

instance P.Ord TestLogType where
    compare :: TestLogType -> TestLogType -> Ordering
compare TestLogType
a TestLogType
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (TestLogType -> Int
forall a. Enum a => a -> Int
P.fromEnum TestLogType
a) (TestLogType -> Int
forall a. Enum a => a -> Int
P.fromEnum TestLogType
b)

-- Enum TestFileType
-- | The type of file to return the filename for, when used with
-- @/g_test_build_filename()/@.
-- 
-- These two options correspond rather directly to the \'dist\' and
-- \'built\' terminology that automake uses and are explicitly used to
-- distinguish between the \'srcdir\' and \'builddir\' being separate.  All
-- files in your project should either be dist (in the
-- @EXTRA_DIST@ or @dist_schema_DATA@
-- sense, in which case they will always be in the srcdir) or built (in
-- the @BUILT_SOURCES@ sense, in which case they will
-- always be in the builddir).
-- 
-- Note: as a general rule of automake, files that are generated only as
-- part of the build-from-git process (but then are distributed with the
-- tarball) always go in srcdir (even if doing a srcdir != builddir
-- build from git) and are considered as distributed files.
-- 
-- /Since: 2.38/
data TestFileType = 
      TestFileTypeDist
    -- ^ a file that was included in the distribution tarball
    | TestFileTypeBuilt
    -- ^ a file that was built on the compiling machine
    | AnotherTestFileType Int
    -- ^ Catch-all for unknown values
    deriving (Int -> TestFileType -> ShowS
[TestFileType] -> ShowS
TestFileType -> String
(Int -> TestFileType -> ShowS)
-> (TestFileType -> String)
-> ([TestFileType] -> ShowS)
-> Show TestFileType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TestFileType -> ShowS
showsPrec :: Int -> TestFileType -> ShowS
$cshow :: TestFileType -> String
show :: TestFileType -> String
$cshowList :: [TestFileType] -> ShowS
showList :: [TestFileType] -> ShowS
Show, TestFileType -> TestFileType -> Bool
(TestFileType -> TestFileType -> Bool)
-> (TestFileType -> TestFileType -> Bool) -> Eq TestFileType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TestFileType -> TestFileType -> Bool
== :: TestFileType -> TestFileType -> Bool
$c/= :: TestFileType -> TestFileType -> Bool
/= :: TestFileType -> TestFileType -> Bool
Eq)

instance P.Enum TestFileType where
    fromEnum :: TestFileType -> Int
fromEnum TestFileType
TestFileTypeDist = Int
0
    fromEnum TestFileType
TestFileTypeBuilt = Int
1
    fromEnum (AnotherTestFileType Int
k) = Int
k

    toEnum :: Int -> TestFileType
toEnum Int
0 = TestFileType
TestFileTypeDist
    toEnum Int
1 = TestFileType
TestFileTypeBuilt
    toEnum Int
k = Int -> TestFileType
AnotherTestFileType Int
k

instance P.Ord TestFileType where
    compare :: TestFileType -> TestFileType -> Ordering
compare TestFileType
a TestFileType
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (TestFileType -> Int
forall a. Enum a => a -> Int
P.fromEnum TestFileType
a) (TestFileType -> Int
forall a. Enum a => a -> Int
P.fromEnum TestFileType
b)

-- Enum SpawnError
-- | Error codes returned by spawning processes.
data SpawnError = 
      SpawnErrorFork
    -- ^ Fork failed due to lack of memory.
    | SpawnErrorRead
    -- ^ Read or select on pipes failed.
    | SpawnErrorChdir
    -- ^ Changing to working directory failed.
    | SpawnErrorAcces
    -- ^ @/execv()/@ returned @EACCES@
    | SpawnErrorPerm
    -- ^ @/execv()/@ returned @EPERM@
    | SpawnErrorTooBig
    -- ^ @/execv()/@ returned @E2BIG@
    | SpawnError2big
    -- ^ deprecated alias for 'GI.GLib.Enums.SpawnErrorTooBig' (deprecated since GLib 2.32)
    | SpawnErrorNoexec
    -- ^ @/execv()/@ returned @ENOEXEC@
    | SpawnErrorNametoolong
    -- ^ @/execv()/@ returned @ENAMETOOLONG@
    | SpawnErrorNoent
    -- ^ @/execv()/@ returned @ENOENT@
    | SpawnErrorNomem
    -- ^ @/execv()/@ returned @ENOMEM@
    | SpawnErrorNotdir
    -- ^ @/execv()/@ returned @ENOTDIR@
    | SpawnErrorLoop
    -- ^ @/execv()/@ returned @ELOOP@
    | SpawnErrorTxtbusy
    -- ^ @/execv()/@ returned @ETXTBUSY@
    | SpawnErrorIo
    -- ^ @/execv()/@ returned @EIO@
    | SpawnErrorNfile
    -- ^ @/execv()/@ returned @ENFILE@
    | SpawnErrorMfile
    -- ^ @/execv()/@ returned @EMFILE@
    | SpawnErrorInval
    -- ^ @/execv()/@ returned @EINVAL@
    | SpawnErrorIsdir
    -- ^ @/execv()/@ returned @EISDIR@
    | SpawnErrorLibbad
    -- ^ @/execv()/@ returned @ELIBBAD@
    | SpawnErrorFailed
    -- ^ Some other fatal failure,
    --   @error->message@ should explain.
    | AnotherSpawnError Int
    -- ^ Catch-all for unknown values
    deriving (Int -> SpawnError -> ShowS
[SpawnError] -> ShowS
SpawnError -> String
(Int -> SpawnError -> ShowS)
-> (SpawnError -> String)
-> ([SpawnError] -> ShowS)
-> Show SpawnError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SpawnError -> ShowS
showsPrec :: Int -> SpawnError -> ShowS
$cshow :: SpawnError -> String
show :: SpawnError -> String
$cshowList :: [SpawnError] -> ShowS
showList :: [SpawnError] -> ShowS
Show, SpawnError -> SpawnError -> Bool
(SpawnError -> SpawnError -> Bool)
-> (SpawnError -> SpawnError -> Bool) -> Eq SpawnError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SpawnError -> SpawnError -> Bool
== :: SpawnError -> SpawnError -> Bool
$c/= :: SpawnError -> SpawnError -> Bool
/= :: SpawnError -> SpawnError -> Bool
Eq)

instance P.Enum SpawnError where
    fromEnum :: SpawnError -> Int
fromEnum SpawnError
SpawnErrorFork = Int
0
    fromEnum SpawnError
SpawnErrorRead = Int
1
    fromEnum SpawnError
SpawnErrorChdir = Int
2
    fromEnum SpawnError
SpawnErrorAcces = Int
3
    fromEnum SpawnError
SpawnErrorPerm = Int
4
    fromEnum SpawnError
SpawnErrorTooBig = Int
5
    fromEnum SpawnError
SpawnError2big = Int
5
    fromEnum SpawnError
SpawnErrorNoexec = Int
6
    fromEnum SpawnError
SpawnErrorNametoolong = Int
7
    fromEnum SpawnError
SpawnErrorNoent = Int
8
    fromEnum SpawnError
SpawnErrorNomem = Int
9
    fromEnum SpawnError
SpawnErrorNotdir = Int
10
    fromEnum SpawnError
SpawnErrorLoop = Int
11
    fromEnum SpawnError
SpawnErrorTxtbusy = Int
12
    fromEnum SpawnError
SpawnErrorIo = Int
13
    fromEnum SpawnError
SpawnErrorNfile = Int
14
    fromEnum SpawnError
SpawnErrorMfile = Int
15
    fromEnum SpawnError
SpawnErrorInval = Int
16
    fromEnum SpawnError
SpawnErrorIsdir = Int
17
    fromEnum SpawnError
SpawnErrorLibbad = Int
18
    fromEnum SpawnError
SpawnErrorFailed = Int
19
    fromEnum (AnotherSpawnError Int
k) = Int
k

    toEnum :: Int -> SpawnError
toEnum Int
0 = SpawnError
SpawnErrorFork
    toEnum Int
1 = SpawnError
SpawnErrorRead
    toEnum Int
2 = SpawnError
SpawnErrorChdir
    toEnum Int
3 = SpawnError
SpawnErrorAcces
    toEnum Int
4 = SpawnError
SpawnErrorPerm
    toEnum Int
5 = SpawnError
SpawnErrorTooBig
    toEnum Int
6 = SpawnError
SpawnErrorNoexec
    toEnum Int
7 = SpawnError
SpawnErrorNametoolong
    toEnum Int
8 = SpawnError
SpawnErrorNoent
    toEnum Int
9 = SpawnError
SpawnErrorNomem
    toEnum Int
10 = SpawnError
SpawnErrorNotdir
    toEnum Int
11 = SpawnError
SpawnErrorLoop
    toEnum Int
12 = SpawnError
SpawnErrorTxtbusy
    toEnum Int
13 = SpawnError
SpawnErrorIo
    toEnum Int
14 = SpawnError
SpawnErrorNfile
    toEnum Int
15 = SpawnError
SpawnErrorMfile
    toEnum Int
16 = SpawnError
SpawnErrorInval
    toEnum Int
17 = SpawnError
SpawnErrorIsdir
    toEnum Int
18 = SpawnError
SpawnErrorLibbad
    toEnum Int
19 = SpawnError
SpawnErrorFailed
    toEnum Int
k = Int -> SpawnError
AnotherSpawnError Int
k

instance P.Ord SpawnError where
    compare :: SpawnError -> SpawnError -> Ordering
compare SpawnError
a SpawnError
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (SpawnError -> Int
forall a. Enum a => a -> Int
P.fromEnum SpawnError
a) (SpawnError -> Int
forall a. Enum a => a -> Int
P.fromEnum SpawnError
b)

instance GErrorClass SpawnError where
    gerrorClassDomain :: SpawnError -> Text
gerrorClassDomain SpawnError
_ = Text
"g-exec-error-quark"

-- | Catch exceptions of type `SpawnError`. This is a specialized version of `Data.GI.Base.GError.catchGErrorJustDomain`.
catchSpawnError ::
    IO a ->
    (SpawnError -> GErrorMessage -> IO a) ->
    IO a
catchSpawnError :: forall a. IO a -> (SpawnError -> Text -> IO a) -> IO a
catchSpawnError = IO a -> (SpawnError -> Text -> IO a) -> IO a
forall err a.
GErrorClass err =>
IO a -> (err -> Text -> IO a) -> IO a
catchGErrorJustDomain

-- | Handle exceptions of type `SpawnError`. This is a specialized version of `Data.GI.Base.GError.handleGErrorJustDomain`.
handleSpawnError ::
    (SpawnError -> GErrorMessage -> IO a) ->
    IO a ->
    IO a
handleSpawnError :: forall a. (SpawnError -> Text -> IO a) -> IO a -> IO a
handleSpawnError = (SpawnError -> Text -> IO a) -> IO a -> IO a
forall err a.
GErrorClass err =>
(err -> Text -> IO a) -> IO a -> IO a
handleGErrorJustDomain

-- Enum SliceConfig
-- | /No description available in the introspection data./
data SliceConfig = 
      SliceConfigAlwaysMalloc
    -- ^ /No description available in the introspection data./
    | SliceConfigBypassMagazines
    -- ^ /No description available in the introspection data./
    | SliceConfigWorkingSetMsecs
    -- ^ /No description available in the introspection data./
    | SliceConfigColorIncrement
    -- ^ /No description available in the introspection data./
    | SliceConfigChunkSizes
    -- ^ /No description available in the introspection data./
    | SliceConfigContentionCounter
    -- ^ /No description available in the introspection data./
    | AnotherSliceConfig Int
    -- ^ Catch-all for unknown values
    deriving (Int -> SliceConfig -> ShowS
[SliceConfig] -> ShowS
SliceConfig -> String
(Int -> SliceConfig -> ShowS)
-> (SliceConfig -> String)
-> ([SliceConfig] -> ShowS)
-> Show SliceConfig
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SliceConfig -> ShowS
showsPrec :: Int -> SliceConfig -> ShowS
$cshow :: SliceConfig -> String
show :: SliceConfig -> String
$cshowList :: [SliceConfig] -> ShowS
showList :: [SliceConfig] -> ShowS
Show, SliceConfig -> SliceConfig -> Bool
(SliceConfig -> SliceConfig -> Bool)
-> (SliceConfig -> SliceConfig -> Bool) -> Eq SliceConfig
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SliceConfig -> SliceConfig -> Bool
== :: SliceConfig -> SliceConfig -> Bool
$c/= :: SliceConfig -> SliceConfig -> Bool
/= :: SliceConfig -> SliceConfig -> Bool
Eq)

instance P.Enum SliceConfig where
    fromEnum :: SliceConfig -> Int
fromEnum SliceConfig
SliceConfigAlwaysMalloc = Int
1
    fromEnum SliceConfig
SliceConfigBypassMagazines = Int
2
    fromEnum SliceConfig
SliceConfigWorkingSetMsecs = Int
3
    fromEnum SliceConfig
SliceConfigColorIncrement = Int
4
    fromEnum SliceConfig
SliceConfigChunkSizes = Int
5
    fromEnum SliceConfig
SliceConfigContentionCounter = Int
6
    fromEnum (AnotherSliceConfig Int
k) = Int
k

    toEnum :: Int -> SliceConfig
toEnum Int
1 = SliceConfig
SliceConfigAlwaysMalloc
    toEnum Int
2 = SliceConfig
SliceConfigBypassMagazines
    toEnum Int
3 = SliceConfig
SliceConfigWorkingSetMsecs
    toEnum Int
4 = SliceConfig
SliceConfigColorIncrement
    toEnum Int
5 = SliceConfig
SliceConfigChunkSizes
    toEnum Int
6 = SliceConfig
SliceConfigContentionCounter
    toEnum Int
k = Int -> SliceConfig
AnotherSliceConfig Int
k

instance P.Ord SliceConfig where
    compare :: SliceConfig -> SliceConfig -> Ordering
compare SliceConfig
a SliceConfig
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (SliceConfig -> Int
forall a. Enum a => a -> Int
P.fromEnum SliceConfig
a) (SliceConfig -> Int
forall a. Enum a => a -> Int
P.fromEnum SliceConfig
b)

-- Enum ShellError
-- | Error codes returned by shell functions.
data ShellError = 
      ShellErrorBadQuoting
    -- ^ Mismatched or otherwise mangled quoting.
    | ShellErrorEmptyString
    -- ^ String to be parsed was empty.
    | ShellErrorFailed
    -- ^ Some other error.
    | AnotherShellError Int
    -- ^ Catch-all for unknown values
    deriving (Int -> ShellError -> ShowS
[ShellError] -> ShowS
ShellError -> String
(Int -> ShellError -> ShowS)
-> (ShellError -> String)
-> ([ShellError] -> ShowS)
-> Show ShellError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ShellError -> ShowS
showsPrec :: Int -> ShellError -> ShowS
$cshow :: ShellError -> String
show :: ShellError -> String
$cshowList :: [ShellError] -> ShowS
showList :: [ShellError] -> ShowS
Show, ShellError -> ShellError -> Bool
(ShellError -> ShellError -> Bool)
-> (ShellError -> ShellError -> Bool) -> Eq ShellError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ShellError -> ShellError -> Bool
== :: ShellError -> ShellError -> Bool
$c/= :: ShellError -> ShellError -> Bool
/= :: ShellError -> ShellError -> Bool
Eq)

instance P.Enum ShellError where
    fromEnum :: ShellError -> Int
fromEnum ShellError
ShellErrorBadQuoting = Int
0
    fromEnum ShellError
ShellErrorEmptyString = Int
1
    fromEnum ShellError
ShellErrorFailed = Int
2
    fromEnum (AnotherShellError Int
k) = Int
k

    toEnum :: Int -> ShellError
toEnum Int
0 = ShellError
ShellErrorBadQuoting
    toEnum Int
1 = ShellError
ShellErrorEmptyString
    toEnum Int
2 = ShellError
ShellErrorFailed
    toEnum Int
k = Int -> ShellError
AnotherShellError Int
k

instance P.Ord ShellError where
    compare :: ShellError -> ShellError -> Ordering
compare ShellError
a ShellError
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (ShellError -> Int
forall a. Enum a => a -> Int
P.fromEnum ShellError
a) (ShellError -> Int
forall a. Enum a => a -> Int
P.fromEnum ShellError
b)

instance GErrorClass ShellError where
    gerrorClassDomain :: ShellError -> Text
gerrorClassDomain ShellError
_ = Text
"g-shell-error-quark"

-- | Catch exceptions of type `ShellError`. This is a specialized version of `Data.GI.Base.GError.catchGErrorJustDomain`.
catchShellError ::
    IO a ->
    (ShellError -> GErrorMessage -> IO a) ->
    IO a
catchShellError :: forall a. IO a -> (ShellError -> Text -> IO a) -> IO a
catchShellError = IO a -> (ShellError -> Text -> IO a) -> IO a
forall err a.
GErrorClass err =>
IO a -> (err -> Text -> IO a) -> IO a
catchGErrorJustDomain

-- | Handle exceptions of type `ShellError`. This is a specialized version of `Data.GI.Base.GError.handleGErrorJustDomain`.
handleShellError ::
    (ShellError -> GErrorMessage -> IO a) ->
    IO a ->
    IO a
handleShellError :: forall a. (ShellError -> Text -> IO a) -> IO a -> IO a
handleShellError = (ShellError -> Text -> IO a) -> IO a -> IO a
forall err a.
GErrorClass err =>
(err -> Text -> IO a) -> IO a -> IO a
handleGErrorJustDomain

-- Enum SeekType
-- | An enumeration specifying the base position for a
-- 'GI.GLib.Structs.IOChannel.iOChannelSeekPosition' operation.
data SeekType = 
      SeekTypeCur
    -- ^ the current position in the file.
    | SeekTypeSet
    -- ^ the start of the file.
    | SeekTypeEnd
    -- ^ the end of the file.
    | AnotherSeekType Int
    -- ^ Catch-all for unknown values
    deriving (Int -> SeekType -> ShowS
[SeekType] -> ShowS
SeekType -> String
(Int -> SeekType -> ShowS)
-> (SeekType -> String) -> ([SeekType] -> ShowS) -> Show SeekType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SeekType -> ShowS
showsPrec :: Int -> SeekType -> ShowS
$cshow :: SeekType -> String
show :: SeekType -> String
$cshowList :: [SeekType] -> ShowS
showList :: [SeekType] -> ShowS
Show, SeekType -> SeekType -> Bool
(SeekType -> SeekType -> Bool)
-> (SeekType -> SeekType -> Bool) -> Eq SeekType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SeekType -> SeekType -> Bool
== :: SeekType -> SeekType -> Bool
$c/= :: SeekType -> SeekType -> Bool
/= :: SeekType -> SeekType -> Bool
Eq)

instance P.Enum SeekType where
    fromEnum :: SeekType -> Int
fromEnum SeekType
SeekTypeCur = Int
0
    fromEnum SeekType
SeekTypeSet = Int
1
    fromEnum SeekType
SeekTypeEnd = Int
2
    fromEnum (AnotherSeekType Int
k) = Int
k

    toEnum :: Int -> SeekType
toEnum Int
0 = SeekType
SeekTypeCur
    toEnum Int
1 = SeekType
SeekTypeSet
    toEnum Int
2 = SeekType
SeekTypeEnd
    toEnum Int
k = Int -> SeekType
AnotherSeekType Int
k

instance P.Ord SeekType where
    compare :: SeekType -> SeekType -> Ordering
compare SeekType
a SeekType
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (SeekType -> Int
forall a. Enum a => a -> Int
P.fromEnum SeekType
a) (SeekType -> Int
forall a. Enum a => a -> Int
P.fromEnum SeekType
b)

-- Enum RegexError
-- | Error codes returned by regular expressions functions.
-- 
-- /Since: 2.14/
data RegexError = 
      RegexErrorCompile
    -- ^ Compilation of the regular expression failed.
    | RegexErrorOptimize
    -- ^ Optimization of the regular expression failed.
    | RegexErrorReplace
    -- ^ Replacement failed due to an ill-formed replacement
    --     string.
    | RegexErrorMatch
    -- ^ The match process failed.
    | RegexErrorInternal
    -- ^ Internal error of the regular expression engine.
    --     Since 2.16
    | RegexErrorStrayBackslash
    -- ^ \"\\\" at end of pattern. Since 2.16
    | RegexErrorMissingControlChar
    -- ^ \"\\c\" at end of pattern. Since 2.16
    | RegexErrorUnrecognizedEscape
    -- ^ Unrecognized character follows \"\\\".
    --     Since 2.16
    | RegexErrorQuantifiersOutOfOrder
    -- ^ Numbers out of order in \"{}\"
    --     quantifier. Since 2.16
    | RegexErrorQuantifierTooBig
    -- ^ Number too big in \"{}\" quantifier.
    --     Since 2.16
    | RegexErrorUnterminatedCharacterClass
    -- ^ Missing terminating \"]\" for
    --     character class. Since 2.16
    | RegexErrorInvalidEscapeInCharacterClass
    -- ^ Invalid escape sequence
    --     in character class. Since 2.16
    | RegexErrorRangeOutOfOrder
    -- ^ Range out of order in character class.
    --     Since 2.16
    | RegexErrorNothingToRepeat
    -- ^ Nothing to repeat. Since 2.16
    | RegexErrorUnrecognizedCharacter
    -- ^ Unrecognized character after \"(?\",
    --     \"(?\<\" or \"(?P\". Since 2.16
    | RegexErrorPosixNamedClassOutsideClass
    -- ^ POSIX named classes are
    --     supported only within a class. Since 2.16
    | RegexErrorUnmatchedParenthesis
    -- ^ Missing terminating \")\" or \")\"
    --     without opening \"(\". Since 2.16
    | RegexErrorInexistentSubpatternReference
    -- ^ Reference to non-existent
    --     subpattern. Since 2.16
    | RegexErrorUnterminatedComment
    -- ^ Missing terminating \")\" after comment.
    --     Since 2.16
    | RegexErrorExpressionTooLarge
    -- ^ Regular expression too large.
    --     Since 2.16
    | RegexErrorMemoryError
    -- ^ Failed to get memory. Since 2.16
    | RegexErrorVariableLengthLookbehind
    -- ^ Lookbehind assertion is not
    --     fixed length. Since 2.16
    | RegexErrorMalformedCondition
    -- ^ Malformed number or name after \"(?(\".
    --     Since 2.16
    | RegexErrorTooManyConditionalBranches
    -- ^ Conditional group contains
    --     more than two branches. Since 2.16
    | RegexErrorAssertionExpected
    -- ^ Assertion expected after \"(?(\".
    --     Since 2.16
    | RegexErrorUnknownPosixClassName
    -- ^ Unknown POSIX class name.
    --     Since 2.16
    | RegexErrorPosixCollatingElementsNotSupported
    -- ^ POSIX collating
    --     elements are not supported. Since 2.16
    | RegexErrorHexCodeTooLarge
    -- ^ Character value in \"\\x{...}\" sequence
    --     is too large. Since 2.16
    | RegexErrorInvalidCondition
    -- ^ Invalid condition \"(?(0)\". Since 2.16
    | RegexErrorSingleByteMatchInLookbehind
    -- ^ \\C not allowed in
    --     lookbehind assertion. Since 2.16
    | RegexErrorInfiniteLoop
    -- ^ Recursive call could loop indefinitely.
    --     Since 2.16
    | RegexErrorMissingSubpatternNameTerminator
    -- ^ Missing terminator
    --     in subpattern name. Since 2.16
    | RegexErrorDuplicateSubpatternName
    -- ^ Two named subpatterns have
    --     the same name. Since 2.16
    | RegexErrorMalformedProperty
    -- ^ Malformed \"\\P\" or \"\\p\" sequence.
    --     Since 2.16
    | RegexErrorUnknownProperty
    -- ^ Unknown property name after \"\\P\" or
    --     \"\\p\". Since 2.16
    | RegexErrorSubpatternNameTooLong
    -- ^ Subpattern name is too long
    --     (maximum 32 characters). Since 2.16
    | RegexErrorTooManySubpatterns
    -- ^ Too many named subpatterns (maximum
    --     10,000). Since 2.16
    | RegexErrorInvalidOctalValue
    -- ^ Octal value is greater than \"\\377\".
    --     Since 2.16
    | RegexErrorTooManyBranchesInDefine
    -- ^ \"DEFINE\" group contains more
    --     than one branch. Since 2.16
    | RegexErrorDefineRepetion
    -- ^ Repeating a \"DEFINE\" group is not allowed.
    --     This error is never raised. Since: 2.16 Deprecated: 2.34
    | RegexErrorInconsistentNewlineOptions
    -- ^ Inconsistent newline options.
    --     Since 2.16
    | RegexErrorMissingBackReference
    -- ^ \"\\g\" is not followed by a braced,
    --      angle-bracketed, or quoted name or number, or by a plain number. Since: 2.16
    | RegexErrorInvalidRelativeReference
    -- ^ relative reference must not be zero. Since: 2.34
    | RegexErrorBacktrackingControlVerbArgumentForbidden
    -- ^ the backtracing
    --     control verb used does not allow an argument. Since: 2.34
    | RegexErrorUnknownBacktrackingControlVerb
    -- ^ unknown backtracing
    --     control verb. Since: 2.34
    | RegexErrorNumberTooBig
    -- ^ number is too big in escape sequence. Since: 2.34
    | RegexErrorMissingSubpatternName
    -- ^ Missing subpattern name. Since: 2.34
    | RegexErrorMissingDigit
    -- ^ Missing digit. Since 2.34
    | RegexErrorInvalidDataCharacter
    -- ^ In JavaScript compatibility mode,
    --     \"[\" is an invalid data character. Since: 2.34
    | RegexErrorExtraSubpatternName
    -- ^ different names for subpatterns of the
    --     same number are not allowed. Since: 2.34
    | RegexErrorBacktrackingControlVerbArgumentRequired
    -- ^ the backtracing control
    --     verb requires an argument. Since: 2.34
    | RegexErrorInvalidControlChar
    -- ^ \"\\c\" must be followed by an ASCII
    --     character. Since: 2.34
    | RegexErrorMissingName
    -- ^ \"\\k\" is not followed by a braced, angle-bracketed, or
    --     quoted name. Since: 2.34
    | RegexErrorNotSupportedInClass
    -- ^ \"\\N\" is not supported in a class. Since: 2.34
    | RegexErrorTooManyForwardReferences
    -- ^ too many forward references. Since: 2.34
    | RegexErrorNameTooLong
    -- ^ the name is too long in \"(*MARK)\", \"(*PRUNE)\",
    --     \"(*SKIP)\", or \"(*THEN)\". Since: 2.34
    | RegexErrorCharacterValueTooLarge
    -- ^ the character value in the \\u sequence is
    --     too large. Since: 2.34
    | AnotherRegexError Int
    -- ^ Catch-all for unknown values
    deriving (Int -> RegexError -> ShowS
[RegexError] -> ShowS
RegexError -> String
(Int -> RegexError -> ShowS)
-> (RegexError -> String)
-> ([RegexError] -> ShowS)
-> Show RegexError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RegexError -> ShowS
showsPrec :: Int -> RegexError -> ShowS
$cshow :: RegexError -> String
show :: RegexError -> String
$cshowList :: [RegexError] -> ShowS
showList :: [RegexError] -> ShowS
Show, RegexError -> RegexError -> Bool
(RegexError -> RegexError -> Bool)
-> (RegexError -> RegexError -> Bool) -> Eq RegexError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RegexError -> RegexError -> Bool
== :: RegexError -> RegexError -> Bool
$c/= :: RegexError -> RegexError -> Bool
/= :: RegexError -> RegexError -> Bool
Eq)

instance P.Enum RegexError where
    fromEnum :: RegexError -> Int
fromEnum RegexError
RegexErrorCompile = Int
0
    fromEnum RegexError
RegexErrorOptimize = Int
1
    fromEnum RegexError
RegexErrorReplace = Int
2
    fromEnum RegexError
RegexErrorMatch = Int
3
    fromEnum RegexError
RegexErrorInternal = Int
4
    fromEnum RegexError
RegexErrorStrayBackslash = Int
101
    fromEnum RegexError
RegexErrorMissingControlChar = Int
102
    fromEnum RegexError
RegexErrorUnrecognizedEscape = Int
103
    fromEnum RegexError
RegexErrorQuantifiersOutOfOrder = Int
104
    fromEnum RegexError
RegexErrorQuantifierTooBig = Int
105
    fromEnum RegexError
RegexErrorUnterminatedCharacterClass = Int
106
    fromEnum RegexError
RegexErrorInvalidEscapeInCharacterClass = Int
107
    fromEnum RegexError
RegexErrorRangeOutOfOrder = Int
108
    fromEnum RegexError
RegexErrorNothingToRepeat = Int
109
    fromEnum RegexError
RegexErrorUnrecognizedCharacter = Int
112
    fromEnum RegexError
RegexErrorPosixNamedClassOutsideClass = Int
113
    fromEnum RegexError
RegexErrorUnmatchedParenthesis = Int
114
    fromEnum RegexError
RegexErrorInexistentSubpatternReference = Int
115
    fromEnum RegexError
RegexErrorUnterminatedComment = Int
118
    fromEnum RegexError
RegexErrorExpressionTooLarge = Int
120
    fromEnum RegexError
RegexErrorMemoryError = Int
121
    fromEnum RegexError
RegexErrorVariableLengthLookbehind = Int
125
    fromEnum RegexError
RegexErrorMalformedCondition = Int
126
    fromEnum RegexError
RegexErrorTooManyConditionalBranches = Int
127
    fromEnum RegexError
RegexErrorAssertionExpected = Int
128
    fromEnum RegexError
RegexErrorUnknownPosixClassName = Int
130
    fromEnum RegexError
RegexErrorPosixCollatingElementsNotSupported = Int
131
    fromEnum RegexError
RegexErrorHexCodeTooLarge = Int
134
    fromEnum RegexError
RegexErrorInvalidCondition = Int
135
    fromEnum RegexError
RegexErrorSingleByteMatchInLookbehind = Int
136
    fromEnum RegexError
RegexErrorInfiniteLoop = Int
140
    fromEnum RegexError
RegexErrorMissingSubpatternNameTerminator = Int
142
    fromEnum RegexError
RegexErrorDuplicateSubpatternName = Int
143
    fromEnum RegexError
RegexErrorMalformedProperty = Int
146
    fromEnum RegexError
RegexErrorUnknownProperty = Int
147
    fromEnum RegexError
RegexErrorSubpatternNameTooLong = Int
148
    fromEnum RegexError
RegexErrorTooManySubpatterns = Int
149
    fromEnum RegexError
RegexErrorInvalidOctalValue = Int
151
    fromEnum RegexError
RegexErrorTooManyBranchesInDefine = Int
154
    fromEnum RegexError
RegexErrorDefineRepetion = Int
155
    fromEnum RegexError
RegexErrorInconsistentNewlineOptions = Int
156
    fromEnum RegexError
RegexErrorMissingBackReference = Int
157
    fromEnum RegexError
RegexErrorInvalidRelativeReference = Int
158
    fromEnum RegexError
RegexErrorBacktrackingControlVerbArgumentForbidden = Int
159
    fromEnum RegexError
RegexErrorUnknownBacktrackingControlVerb = Int
160
    fromEnum RegexError
RegexErrorNumberTooBig = Int
161
    fromEnum RegexError
RegexErrorMissingSubpatternName = Int
162
    fromEnum RegexError
RegexErrorMissingDigit = Int
163
    fromEnum RegexError
RegexErrorInvalidDataCharacter = Int
164
    fromEnum RegexError
RegexErrorExtraSubpatternName = Int
165
    fromEnum RegexError
RegexErrorBacktrackingControlVerbArgumentRequired = Int
166
    fromEnum RegexError
RegexErrorInvalidControlChar = Int
168
    fromEnum RegexError
RegexErrorMissingName = Int
169
    fromEnum RegexError
RegexErrorNotSupportedInClass = Int
171
    fromEnum RegexError
RegexErrorTooManyForwardReferences = Int
172
    fromEnum RegexError
RegexErrorNameTooLong = Int
175
    fromEnum RegexError
RegexErrorCharacterValueTooLarge = Int
176
    fromEnum (AnotherRegexError Int
k) = Int
k

    toEnum :: Int -> RegexError
toEnum Int
0 = RegexError
RegexErrorCompile
    toEnum Int
1 = RegexError
RegexErrorOptimize
    toEnum Int
2 = RegexError
RegexErrorReplace
    toEnum Int
3 = RegexError
RegexErrorMatch
    toEnum Int
4 = RegexError
RegexErrorInternal
    toEnum Int
101 = RegexError
RegexErrorStrayBackslash
    toEnum Int
102 = RegexError
RegexErrorMissingControlChar
    toEnum Int
103 = RegexError
RegexErrorUnrecognizedEscape
    toEnum Int
104 = RegexError
RegexErrorQuantifiersOutOfOrder
    toEnum Int
105 = RegexError
RegexErrorQuantifierTooBig
    toEnum Int
106 = RegexError
RegexErrorUnterminatedCharacterClass
    toEnum Int
107 = RegexError
RegexErrorInvalidEscapeInCharacterClass
    toEnum Int
108 = RegexError
RegexErrorRangeOutOfOrder
    toEnum Int
109 = RegexError
RegexErrorNothingToRepeat
    toEnum Int
112 = RegexError
RegexErrorUnrecognizedCharacter
    toEnum Int
113 = RegexError
RegexErrorPosixNamedClassOutsideClass
    toEnum Int
114 = RegexError
RegexErrorUnmatchedParenthesis
    toEnum Int
115 = RegexError
RegexErrorInexistentSubpatternReference
    toEnum Int
118 = RegexError
RegexErrorUnterminatedComment
    toEnum Int
120 = RegexError
RegexErrorExpressionTooLarge
    toEnum Int
121 = RegexError
RegexErrorMemoryError
    toEnum Int
125 = RegexError
RegexErrorVariableLengthLookbehind
    toEnum Int
126 = RegexError
RegexErrorMalformedCondition
    toEnum Int
127 = RegexError
RegexErrorTooManyConditionalBranches
    toEnum Int
128 = RegexError
RegexErrorAssertionExpected
    toEnum Int
130 = RegexError
RegexErrorUnknownPosixClassName
    toEnum Int
131 = RegexError
RegexErrorPosixCollatingElementsNotSupported
    toEnum Int
134 = RegexError
RegexErrorHexCodeTooLarge
    toEnum Int
135 = RegexError
RegexErrorInvalidCondition
    toEnum Int
136 = RegexError
RegexErrorSingleByteMatchInLookbehind
    toEnum Int
140 = RegexError
RegexErrorInfiniteLoop
    toEnum Int
142 = RegexError
RegexErrorMissingSubpatternNameTerminator
    toEnum Int
143 = RegexError
RegexErrorDuplicateSubpatternName
    toEnum Int
146 = RegexError
RegexErrorMalformedProperty
    toEnum Int
147 = RegexError
RegexErrorUnknownProperty
    toEnum Int
148 = RegexError
RegexErrorSubpatternNameTooLong
    toEnum Int
149 = RegexError
RegexErrorTooManySubpatterns
    toEnum Int
151 = RegexError
RegexErrorInvalidOctalValue
    toEnum Int
154 = RegexError
RegexErrorTooManyBranchesInDefine
    toEnum Int
155 = RegexError
RegexErrorDefineRepetion
    toEnum Int
156 = RegexError
RegexErrorInconsistentNewlineOptions
    toEnum Int
157 = RegexError
RegexErrorMissingBackReference
    toEnum Int
158 = RegexError
RegexErrorInvalidRelativeReference
    toEnum Int
159 = RegexError
RegexErrorBacktrackingControlVerbArgumentForbidden
    toEnum Int
160 = RegexError
RegexErrorUnknownBacktrackingControlVerb
    toEnum Int
161 = RegexError
RegexErrorNumberTooBig
    toEnum Int
162 = RegexError
RegexErrorMissingSubpatternName
    toEnum Int
163 = RegexError
RegexErrorMissingDigit
    toEnum Int
164 = RegexError
RegexErrorInvalidDataCharacter
    toEnum Int
165 = RegexError
RegexErrorExtraSubpatternName
    toEnum Int
166 = RegexError
RegexErrorBacktrackingControlVerbArgumentRequired
    toEnum Int
168 = RegexError
RegexErrorInvalidControlChar
    toEnum Int
169 = RegexError
RegexErrorMissingName
    toEnum Int
171 = RegexError
RegexErrorNotSupportedInClass
    toEnum Int
172 = RegexError
RegexErrorTooManyForwardReferences
    toEnum Int
175 = RegexError
RegexErrorNameTooLong
    toEnum Int
176 = RegexError
RegexErrorCharacterValueTooLarge
    toEnum Int
k = Int -> RegexError
AnotherRegexError Int
k

instance P.Ord RegexError where
    compare :: RegexError -> RegexError -> Ordering
compare RegexError
a RegexError
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (RegexError -> Int
forall a. Enum a => a -> Int
P.fromEnum RegexError
a) (RegexError -> Int
forall a. Enum a => a -> Int
P.fromEnum RegexError
b)

instance GErrorClass RegexError where
    gerrorClassDomain :: RegexError -> Text
gerrorClassDomain RegexError
_ = Text
"g-regex-error-quark"

-- | Catch exceptions of type `RegexError`. This is a specialized version of `Data.GI.Base.GError.catchGErrorJustDomain`.
catchRegexError ::
    IO a ->
    (RegexError -> GErrorMessage -> IO a) ->
    IO a
catchRegexError :: forall a. IO a -> (RegexError -> Text -> IO a) -> IO a
catchRegexError = IO a -> (RegexError -> Text -> IO a) -> IO a
forall err a.
GErrorClass err =>
IO a -> (err -> Text -> IO a) -> IO a
catchGErrorJustDomain

-- | Handle exceptions of type `RegexError`. This is a specialized version of `Data.GI.Base.GError.handleGErrorJustDomain`.
handleRegexError ::
    (RegexError -> GErrorMessage -> IO a) ->
    IO a ->
    IO a
handleRegexError :: forall a. (RegexError -> Text -> IO a) -> IO a -> IO a
handleRegexError = (RegexError -> Text -> IO a) -> IO a -> IO a
forall err a.
GErrorClass err =>
(err -> Text -> IO a) -> IO a -> IO a
handleGErrorJustDomain

-- Enum OptionError
-- | Error codes returned by option parsing.
data OptionError = 
      OptionErrorUnknownOption
    -- ^ An option was not known to the parser.
    --  This error will only be reported, if the parser hasn\'t been instructed
    --  to ignore unknown options, see 'GI.GLib.Structs.OptionContext.optionContextSetIgnoreUnknownOptions'.
    | OptionErrorBadValue
    -- ^ A value couldn\'t be parsed.
    | OptionErrorFailed
    -- ^ A t'GI.GLib.Callbacks.OptionArgFunc' callback failed.
    | AnotherOptionError Int
    -- ^ Catch-all for unknown values
    deriving (Int -> OptionError -> ShowS
[OptionError] -> ShowS
OptionError -> String
(Int -> OptionError -> ShowS)
-> (OptionError -> String)
-> ([OptionError] -> ShowS)
-> Show OptionError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> OptionError -> ShowS
showsPrec :: Int -> OptionError -> ShowS
$cshow :: OptionError -> String
show :: OptionError -> String
$cshowList :: [OptionError] -> ShowS
showList :: [OptionError] -> ShowS
Show, OptionError -> OptionError -> Bool
(OptionError -> OptionError -> Bool)
-> (OptionError -> OptionError -> Bool) -> Eq OptionError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: OptionError -> OptionError -> Bool
== :: OptionError -> OptionError -> Bool
$c/= :: OptionError -> OptionError -> Bool
/= :: OptionError -> OptionError -> Bool
Eq)

instance P.Enum OptionError where
    fromEnum :: OptionError -> Int
fromEnum OptionError
OptionErrorUnknownOption = Int
0
    fromEnum OptionError
OptionErrorBadValue = Int
1
    fromEnum OptionError
OptionErrorFailed = Int
2
    fromEnum (AnotherOptionError Int
k) = Int
k

    toEnum :: Int -> OptionError
toEnum Int
0 = OptionError
OptionErrorUnknownOption
    toEnum Int
1 = OptionError
OptionErrorBadValue
    toEnum Int
2 = OptionError
OptionErrorFailed
    toEnum Int
k = Int -> OptionError
AnotherOptionError Int
k

instance P.Ord OptionError where
    compare :: OptionError -> OptionError -> Ordering
compare OptionError
a OptionError
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (OptionError -> Int
forall a. Enum a => a -> Int
P.fromEnum OptionError
a) (OptionError -> Int
forall a. Enum a => a -> Int
P.fromEnum OptionError
b)

instance GErrorClass OptionError where
    gerrorClassDomain :: OptionError -> Text
gerrorClassDomain OptionError
_ = Text
"g-option-context-error-quark"

-- | Catch exceptions of type `OptionError`. This is a specialized version of `Data.GI.Base.GError.catchGErrorJustDomain`.
catchOptionError ::
    IO a ->
    (OptionError -> GErrorMessage -> IO a) ->
    IO a
catchOptionError :: forall a. IO a -> (OptionError -> Text -> IO a) -> IO a
catchOptionError = IO a -> (OptionError -> Text -> IO a) -> IO a
forall err a.
GErrorClass err =>
IO a -> (err -> Text -> IO a) -> IO a
catchGErrorJustDomain

-- | Handle exceptions of type `OptionError`. This is a specialized version of `Data.GI.Base.GError.handleGErrorJustDomain`.
handleOptionError ::
    (OptionError -> GErrorMessage -> IO a) ->
    IO a ->
    IO a
handleOptionError :: forall a. (OptionError -> Text -> IO a) -> IO a -> IO a
handleOptionError = (OptionError -> Text -> IO a) -> IO a -> IO a
forall err a.
GErrorClass err =>
(err -> Text -> IO a) -> IO a -> IO a
handleGErrorJustDomain

-- Enum OptionArg
-- | The t'GI.GLib.Enums.OptionArg' enum values determine which type of extra argument the
-- options expect to find. If an option expects an extra argument, it can
-- be specified in several ways; with a short option: @-x arg@, with a long
-- option: @--name arg@ or combined in a single argument: @--name=arg@.
data OptionArg = 
      OptionArgNone
    -- ^ No extra argument. This is useful for simple flags or booleans.
    | OptionArgString
    -- ^ The option takes a UTF-8 string argument.
    | OptionArgInt
    -- ^ The option takes an integer argument.
    | OptionArgCallback
    -- ^ The option provides a callback (of type
    --     t'GI.GLib.Callbacks.OptionArgFunc') to parse the extra argument.
    | OptionArgFilename
    -- ^ The option takes a filename as argument, which will
    --        be in the GLib filename encoding rather than UTF-8.
    | OptionArgStringArray
    -- ^ The option takes a string argument, multiple
    --     uses of the option are collected into an array of strings.
    | OptionArgFilenameArray
    -- ^ The option takes a filename as argument,
    --     multiple uses of the option are collected into an array of strings.
    | OptionArgDouble
    -- ^ The option takes a double argument. The argument
    --     can be formatted either for the user\'s locale or for the \"C\" locale.
    --     Since 2.12
    | OptionArgInt64
    -- ^ The option takes a 64-bit integer. Like
    --     'GI.GLib.Enums.OptionArgInt' but for larger numbers. The number can be in
    --     decimal base, or in hexadecimal (when prefixed with @0x@, for
    --     example, @0xffffffff@). Since 2.12
    | AnotherOptionArg Int
    -- ^ Catch-all for unknown values
    deriving (Int -> OptionArg -> ShowS
[OptionArg] -> ShowS
OptionArg -> String
(Int -> OptionArg -> ShowS)
-> (OptionArg -> String)
-> ([OptionArg] -> ShowS)
-> Show OptionArg
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> OptionArg -> ShowS
showsPrec :: Int -> OptionArg -> ShowS
$cshow :: OptionArg -> String
show :: OptionArg -> String
$cshowList :: [OptionArg] -> ShowS
showList :: [OptionArg] -> ShowS
Show, OptionArg -> OptionArg -> Bool
(OptionArg -> OptionArg -> Bool)
-> (OptionArg -> OptionArg -> Bool) -> Eq OptionArg
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: OptionArg -> OptionArg -> Bool
== :: OptionArg -> OptionArg -> Bool
$c/= :: OptionArg -> OptionArg -> Bool
/= :: OptionArg -> OptionArg -> Bool
Eq)

instance P.Enum OptionArg where
    fromEnum :: OptionArg -> Int
fromEnum OptionArg
OptionArgNone = Int
0
    fromEnum OptionArg
OptionArgString = Int
1
    fromEnum OptionArg
OptionArgInt = Int
2
    fromEnum OptionArg
OptionArgCallback = Int
3
    fromEnum OptionArg
OptionArgFilename = Int
4
    fromEnum OptionArg
OptionArgStringArray = Int
5
    fromEnum OptionArg
OptionArgFilenameArray = Int
6
    fromEnum OptionArg
OptionArgDouble = Int
7
    fromEnum OptionArg
OptionArgInt64 = Int
8
    fromEnum (AnotherOptionArg Int
k) = Int
k

    toEnum :: Int -> OptionArg
toEnum Int
0 = OptionArg
OptionArgNone
    toEnum Int
1 = OptionArg
OptionArgString
    toEnum Int
2 = OptionArg
OptionArgInt
    toEnum Int
3 = OptionArg
OptionArgCallback
    toEnum Int
4 = OptionArg
OptionArgFilename
    toEnum Int
5 = OptionArg
OptionArgStringArray
    toEnum Int
6 = OptionArg
OptionArgFilenameArray
    toEnum Int
7 = OptionArg
OptionArgDouble
    toEnum Int
8 = OptionArg
OptionArgInt64
    toEnum Int
k = Int -> OptionArg
AnotherOptionArg Int
k

instance P.Ord OptionArg where
    compare :: OptionArg -> OptionArg -> Ordering
compare OptionArg
a OptionArg
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (OptionArg -> Int
forall a. Enum a => a -> Int
P.fromEnum OptionArg
a) (OptionArg -> Int
forall a. Enum a => a -> Int
P.fromEnum OptionArg
b)

-- Enum OnceStatus
-- | The possible statuses of a one-time initialization function
-- controlled by a t'GI.GLib.Structs.Once.Once' struct.
-- 
-- /Since: 2.4/
data OnceStatus = 
      OnceStatusNotcalled
    -- ^ the function has not been called yet.
    | OnceStatusProgress
    -- ^ the function call is currently in progress.
    | OnceStatusReady
    -- ^ the function has been called.
    | AnotherOnceStatus Int
    -- ^ Catch-all for unknown values
    deriving (Int -> OnceStatus -> ShowS
[OnceStatus] -> ShowS
OnceStatus -> String
(Int -> OnceStatus -> ShowS)
-> (OnceStatus -> String)
-> ([OnceStatus] -> ShowS)
-> Show OnceStatus
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> OnceStatus -> ShowS
showsPrec :: Int -> OnceStatus -> ShowS
$cshow :: OnceStatus -> String
show :: OnceStatus -> String
$cshowList :: [OnceStatus] -> ShowS
showList :: [OnceStatus] -> ShowS
Show, OnceStatus -> OnceStatus -> Bool
(OnceStatus -> OnceStatus -> Bool)
-> (OnceStatus -> OnceStatus -> Bool) -> Eq OnceStatus
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: OnceStatus -> OnceStatus -> Bool
== :: OnceStatus -> OnceStatus -> Bool
$c/= :: OnceStatus -> OnceStatus -> Bool
/= :: OnceStatus -> OnceStatus -> Bool
Eq)

instance P.Enum OnceStatus where
    fromEnum :: OnceStatus -> Int
fromEnum OnceStatus
OnceStatusNotcalled = Int
0
    fromEnum OnceStatus
OnceStatusProgress = Int
1
    fromEnum OnceStatus
OnceStatusReady = Int
2
    fromEnum (AnotherOnceStatus Int
k) = Int
k

    toEnum :: Int -> OnceStatus
toEnum Int
0 = OnceStatus
OnceStatusNotcalled
    toEnum Int
1 = OnceStatus
OnceStatusProgress
    toEnum Int
2 = OnceStatus
OnceStatusReady
    toEnum Int
k = Int -> OnceStatus
AnotherOnceStatus Int
k

instance P.Ord OnceStatus where
    compare :: OnceStatus -> OnceStatus -> Ordering
compare OnceStatus
a OnceStatus
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (OnceStatus -> Int
forall a. Enum a => a -> Int
P.fromEnum OnceStatus
a) (OnceStatus -> Int
forall a. Enum a => a -> Int
P.fromEnum OnceStatus
b)

-- Enum NumberParserError
-- | Error codes returned by functions converting a string to a number.
-- 
-- /Since: 2.54/
data NumberParserError = 
      NumberParserErrorInvalid
    -- ^ String was not a valid number.
    | NumberParserErrorOutOfBounds
    -- ^ String was a number, but out of bounds.
    | AnotherNumberParserError Int
    -- ^ Catch-all for unknown values
    deriving (Int -> NumberParserError -> ShowS
[NumberParserError] -> ShowS
NumberParserError -> String
(Int -> NumberParserError -> ShowS)
-> (NumberParserError -> String)
-> ([NumberParserError] -> ShowS)
-> Show NumberParserError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> NumberParserError -> ShowS
showsPrec :: Int -> NumberParserError -> ShowS
$cshow :: NumberParserError -> String
show :: NumberParserError -> String
$cshowList :: [NumberParserError] -> ShowS
showList :: [NumberParserError] -> ShowS
Show, NumberParserError -> NumberParserError -> Bool
(NumberParserError -> NumberParserError -> Bool)
-> (NumberParserError -> NumberParserError -> Bool)
-> Eq NumberParserError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NumberParserError -> NumberParserError -> Bool
== :: NumberParserError -> NumberParserError -> Bool
$c/= :: NumberParserError -> NumberParserError -> Bool
/= :: NumberParserError -> NumberParserError -> Bool
Eq)

instance P.Enum NumberParserError where
    fromEnum :: NumberParserError -> Int
fromEnum NumberParserError
NumberParserErrorInvalid = Int
0
    fromEnum NumberParserError
NumberParserErrorOutOfBounds = Int
1
    fromEnum (AnotherNumberParserError Int
k) = Int
k

    toEnum :: Int -> NumberParserError
toEnum Int
0 = NumberParserError
NumberParserErrorInvalid
    toEnum Int
1 = NumberParserError
NumberParserErrorOutOfBounds
    toEnum Int
k = Int -> NumberParserError
AnotherNumberParserError Int
k

instance P.Ord NumberParserError where
    compare :: NumberParserError -> NumberParserError -> Ordering
compare NumberParserError
a NumberParserError
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (NumberParserError -> Int
forall a. Enum a => a -> Int
P.fromEnum NumberParserError
a) (NumberParserError -> Int
forall a. Enum a => a -> Int
P.fromEnum NumberParserError
b)

instance GErrorClass NumberParserError where
    gerrorClassDomain :: NumberParserError -> Text
gerrorClassDomain NumberParserError
_ = Text
"g-number-parser-error-quark"

-- | Catch exceptions of type `NumberParserError`. This is a specialized version of `Data.GI.Base.GError.catchGErrorJustDomain`.
catchNumberParserError ::
    IO a ->
    (NumberParserError -> GErrorMessage -> IO a) ->
    IO a
catchNumberParserError :: forall a. IO a -> (NumberParserError -> Text -> IO a) -> IO a
catchNumberParserError = IO a -> (NumberParserError -> Text -> IO a) -> IO a
forall err a.
GErrorClass err =>
IO a -> (err -> Text -> IO a) -> IO a
catchGErrorJustDomain

-- | Handle exceptions of type `NumberParserError`. This is a specialized version of `Data.GI.Base.GError.handleGErrorJustDomain`.
handleNumberParserError ::
    (NumberParserError -> GErrorMessage -> IO a) ->
    IO a ->
    IO a
handleNumberParserError :: forall a. (NumberParserError -> Text -> IO a) -> IO a -> IO a
handleNumberParserError = (NumberParserError -> Text -> IO a) -> IO a -> IO a
forall err a.
GErrorClass err =>
(err -> Text -> IO a) -> IO a -> IO a
handleGErrorJustDomain

-- Enum NormalizeMode
-- | Defines how a Unicode string is transformed in a canonical
-- form, standardizing such issues as whether a character with
-- an accent is represented as a base character and combining
-- accent or as a single precomposed character. Unicode strings
-- should generally be normalized before comparing them.
data NormalizeMode = 
      NormalizeModeDefault
    -- ^ standardize differences that do not affect the
    --     text content, such as the above-mentioned accent representation
    | NormalizeModeNfd
    -- ^ another name for 'GI.GLib.Enums.NormalizeModeDefault'
    | NormalizeModeDefaultCompose
    -- ^ like 'GI.GLib.Enums.NormalizeModeDefault', but with
    --     composed forms rather than a maximally decomposed form
    | NormalizeModeNfc
    -- ^ another name for 'GI.GLib.Enums.NormalizeModeDefaultCompose'
    | NormalizeModeAll
    -- ^ beyond 'GI.GLib.Enums.NormalizeModeDefault' also standardize the
    --     \"compatibility\" characters in Unicode, such as SUPERSCRIPT THREE
    --     to the standard forms (in this case DIGIT THREE). Formatting
    --     information may be lost but for most text operations such
    --     characters should be considered the same
    | NormalizeModeNfkd
    -- ^ another name for 'GI.GLib.Enums.NormalizeModeAll'
    | NormalizeModeAllCompose
    -- ^ like 'GI.GLib.Enums.NormalizeModeAll', but with composed
    --     forms rather than a maximally decomposed form
    | NormalizeModeNfkc
    -- ^ another name for 'GI.GLib.Enums.NormalizeModeAllCompose'
    | AnotherNormalizeMode Int
    -- ^ Catch-all for unknown values
    deriving (Int -> NormalizeMode -> ShowS
[NormalizeMode] -> ShowS
NormalizeMode -> String
(Int -> NormalizeMode -> ShowS)
-> (NormalizeMode -> String)
-> ([NormalizeMode] -> ShowS)
-> Show NormalizeMode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> NormalizeMode -> ShowS
showsPrec :: Int -> NormalizeMode -> ShowS
$cshow :: NormalizeMode -> String
show :: NormalizeMode -> String
$cshowList :: [NormalizeMode] -> ShowS
showList :: [NormalizeMode] -> ShowS
Show, NormalizeMode -> NormalizeMode -> Bool
(NormalizeMode -> NormalizeMode -> Bool)
-> (NormalizeMode -> NormalizeMode -> Bool) -> Eq NormalizeMode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NormalizeMode -> NormalizeMode -> Bool
== :: NormalizeMode -> NormalizeMode -> Bool
$c/= :: NormalizeMode -> NormalizeMode -> Bool
/= :: NormalizeMode -> NormalizeMode -> Bool
Eq)

instance P.Enum NormalizeMode where
    fromEnum :: NormalizeMode -> Int
fromEnum NormalizeMode
NormalizeModeDefault = Int
0
    fromEnum NormalizeMode
NormalizeModeNfd = Int
0
    fromEnum NormalizeMode
NormalizeModeDefaultCompose = Int
1
    fromEnum NormalizeMode
NormalizeModeNfc = Int
1
    fromEnum NormalizeMode
NormalizeModeAll = Int
2
    fromEnum NormalizeMode
NormalizeModeNfkd = Int
2
    fromEnum NormalizeMode
NormalizeModeAllCompose = Int
3
    fromEnum NormalizeMode
NormalizeModeNfkc = Int
3
    fromEnum (AnotherNormalizeMode Int
k) = Int
k

    toEnum :: Int -> NormalizeMode
toEnum Int
0 = NormalizeMode
NormalizeModeDefault
    toEnum Int
1 = NormalizeMode
NormalizeModeDefaultCompose
    toEnum Int
2 = NormalizeMode
NormalizeModeAll
    toEnum Int
3 = NormalizeMode
NormalizeModeAllCompose
    toEnum Int
k = Int -> NormalizeMode
AnotherNormalizeMode Int
k

instance P.Ord NormalizeMode where
    compare :: NormalizeMode -> NormalizeMode -> Ordering
compare NormalizeMode
a NormalizeMode
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (NormalizeMode -> Int
forall a. Enum a => a -> Int
P.fromEnum NormalizeMode
a) (NormalizeMode -> Int
forall a. Enum a => a -> Int
P.fromEnum NormalizeMode
b)

-- Enum MarkupError
-- | Error codes returned by markup parsing.
data MarkupError = 
      MarkupErrorBadUtf8
    -- ^ text being parsed was not valid UTF-8
    | MarkupErrorEmpty
    -- ^ document contained nothing, or only whitespace
    | MarkupErrorParse
    -- ^ document was ill-formed
    | MarkupErrorUnknownElement
    -- ^ error should be set by t'GI.GLib.Structs.MarkupParser.MarkupParser'
    --     functions; element wasn\'t known
    | MarkupErrorUnknownAttribute
    -- ^ error should be set by t'GI.GLib.Structs.MarkupParser.MarkupParser'
    --     functions; attribute wasn\'t known
    | MarkupErrorInvalidContent
    -- ^ error should be set by t'GI.GLib.Structs.MarkupParser.MarkupParser'
    --     functions; content was invalid
    | MarkupErrorMissingAttribute
    -- ^ error should be set by t'GI.GLib.Structs.MarkupParser.MarkupParser'
    --     functions; a required attribute was missing
    | AnotherMarkupError Int
    -- ^ Catch-all for unknown values
    deriving (Int -> MarkupError -> ShowS
[MarkupError] -> ShowS
MarkupError -> String
(Int -> MarkupError -> ShowS)
-> (MarkupError -> String)
-> ([MarkupError] -> ShowS)
-> Show MarkupError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> MarkupError -> ShowS
showsPrec :: Int -> MarkupError -> ShowS
$cshow :: MarkupError -> String
show :: MarkupError -> String
$cshowList :: [MarkupError] -> ShowS
showList :: [MarkupError] -> ShowS
Show, MarkupError -> MarkupError -> Bool
(MarkupError -> MarkupError -> Bool)
-> (MarkupError -> MarkupError -> Bool) -> Eq MarkupError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: MarkupError -> MarkupError -> Bool
== :: MarkupError -> MarkupError -> Bool
$c/= :: MarkupError -> MarkupError -> Bool
/= :: MarkupError -> MarkupError -> Bool
Eq)

instance P.Enum MarkupError where
    fromEnum :: MarkupError -> Int
fromEnum MarkupError
MarkupErrorBadUtf8 = Int
0
    fromEnum MarkupError
MarkupErrorEmpty = Int
1
    fromEnum MarkupError
MarkupErrorParse = Int
2
    fromEnum MarkupError
MarkupErrorUnknownElement = Int
3
    fromEnum MarkupError
MarkupErrorUnknownAttribute = Int
4
    fromEnum MarkupError
MarkupErrorInvalidContent = Int
5
    fromEnum MarkupError
MarkupErrorMissingAttribute = Int
6
    fromEnum (AnotherMarkupError Int
k) = Int
k

    toEnum :: Int -> MarkupError
toEnum Int
0 = MarkupError
MarkupErrorBadUtf8
    toEnum Int
1 = MarkupError
MarkupErrorEmpty
    toEnum Int
2 = MarkupError
MarkupErrorParse
    toEnum Int
3 = MarkupError
MarkupErrorUnknownElement
    toEnum Int
4 = MarkupError
MarkupErrorUnknownAttribute
    toEnum Int
5 = MarkupError
MarkupErrorInvalidContent
    toEnum Int
6 = MarkupError
MarkupErrorMissingAttribute
    toEnum Int
k = Int -> MarkupError
AnotherMarkupError Int
k

instance P.Ord MarkupError where
    compare :: MarkupError -> MarkupError -> Ordering
compare MarkupError
a MarkupError
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (MarkupError -> Int
forall a. Enum a => a -> Int
P.fromEnum MarkupError
a) (MarkupError -> Int
forall a. Enum a => a -> Int
P.fromEnum MarkupError
b)

instance GErrorClass MarkupError where
    gerrorClassDomain :: MarkupError -> Text
gerrorClassDomain MarkupError
_ = Text
"g-markup-error-quark"

-- | Catch exceptions of type `MarkupError`. This is a specialized version of `Data.GI.Base.GError.catchGErrorJustDomain`.
catchMarkupError ::
    IO a ->
    (MarkupError -> GErrorMessage -> IO a) ->
    IO a
catchMarkupError :: forall a. IO a -> (MarkupError -> Text -> IO a) -> IO a
catchMarkupError = IO a -> (MarkupError -> Text -> IO a) -> IO a
forall err a.
GErrorClass err =>
IO a -> (err -> Text -> IO a) -> IO a
catchGErrorJustDomain

-- | Handle exceptions of type `MarkupError`. This is a specialized version of `Data.GI.Base.GError.handleGErrorJustDomain`.
handleMarkupError ::
    (MarkupError -> GErrorMessage -> IO a) ->
    IO a ->
    IO a
handleMarkupError :: forall a. (MarkupError -> Text -> IO a) -> IO a -> IO a
handleMarkupError = (MarkupError -> Text -> IO a) -> IO a -> IO a
forall err a.
GErrorClass err =>
(err -> Text -> IO a) -> IO a -> IO a
handleGErrorJustDomain

-- Enum LogWriterOutput
-- | Return values from @/GLogWriterFuncs/@ to indicate whether the given log entry
-- was successfully handled by the writer, or whether there was an error in
-- handling it (and hence a fallback writer should be used).
-- 
-- If a t'GI.GLib.Callbacks.LogWriterFunc' ignores a log entry, it should return
-- 'GI.GLib.Enums.LogWriterOutputHandled'.
-- 
-- /Since: 2.50/
data LogWriterOutput = 
      LogWriterOutputHandled
    -- ^ Log writer has handled the log entry.
    | LogWriterOutputUnhandled
    -- ^ Log writer could not handle the log entry.
    | AnotherLogWriterOutput Int
    -- ^ Catch-all for unknown values
    deriving (Int -> LogWriterOutput -> ShowS
[LogWriterOutput] -> ShowS
LogWriterOutput -> String
(Int -> LogWriterOutput -> ShowS)
-> (LogWriterOutput -> String)
-> ([LogWriterOutput] -> ShowS)
-> Show LogWriterOutput
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LogWriterOutput -> ShowS
showsPrec :: Int -> LogWriterOutput -> ShowS
$cshow :: LogWriterOutput -> String
show :: LogWriterOutput -> String
$cshowList :: [LogWriterOutput] -> ShowS
showList :: [LogWriterOutput] -> ShowS
Show, LogWriterOutput -> LogWriterOutput -> Bool
(LogWriterOutput -> LogWriterOutput -> Bool)
-> (LogWriterOutput -> LogWriterOutput -> Bool)
-> Eq LogWriterOutput
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LogWriterOutput -> LogWriterOutput -> Bool
== :: LogWriterOutput -> LogWriterOutput -> Bool
$c/= :: LogWriterOutput -> LogWriterOutput -> Bool
/= :: LogWriterOutput -> LogWriterOutput -> Bool
Eq)

instance P.Enum LogWriterOutput where
    fromEnum :: LogWriterOutput -> Int
fromEnum LogWriterOutput
LogWriterOutputHandled = Int
1
    fromEnum LogWriterOutput
LogWriterOutputUnhandled = Int
0
    fromEnum (AnotherLogWriterOutput Int
k) = Int
k

    toEnum :: Int -> LogWriterOutput
toEnum Int
1 = LogWriterOutput
LogWriterOutputHandled
    toEnum Int
0 = LogWriterOutput
LogWriterOutputUnhandled
    toEnum Int
k = Int -> LogWriterOutput
AnotherLogWriterOutput Int
k

instance P.Ord LogWriterOutput where
    compare :: LogWriterOutput -> LogWriterOutput -> Ordering
compare LogWriterOutput
a LogWriterOutput
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (LogWriterOutput -> Int
forall a. Enum a => a -> Int
P.fromEnum LogWriterOutput
a) (LogWriterOutput -> Int
forall a. Enum a => a -> Int
P.fromEnum LogWriterOutput
b)

-- Enum KeyFileError
-- | Error codes returned by key file parsing.
data KeyFileError = 
      KeyFileErrorUnknownEncoding
    -- ^ the text being parsed was in
    --   an unknown encoding
    | KeyFileErrorParse
    -- ^ document was ill-formed
    | KeyFileErrorNotFound
    -- ^ the file was not found
    | KeyFileErrorKeyNotFound
    -- ^ a requested key was not found
    | KeyFileErrorGroupNotFound
    -- ^ a requested group was not found
    | KeyFileErrorInvalidValue
    -- ^ a value could not be parsed
    | AnotherKeyFileError Int
    -- ^ Catch-all for unknown values
    deriving (Int -> KeyFileError -> ShowS
[KeyFileError] -> ShowS
KeyFileError -> String
(Int -> KeyFileError -> ShowS)
-> (KeyFileError -> String)
-> ([KeyFileError] -> ShowS)
-> Show KeyFileError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> KeyFileError -> ShowS
showsPrec :: Int -> KeyFileError -> ShowS
$cshow :: KeyFileError -> String
show :: KeyFileError -> String
$cshowList :: [KeyFileError] -> ShowS
showList :: [KeyFileError] -> ShowS
Show, KeyFileError -> KeyFileError -> Bool
(KeyFileError -> KeyFileError -> Bool)
-> (KeyFileError -> KeyFileError -> Bool) -> Eq KeyFileError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: KeyFileError -> KeyFileError -> Bool
== :: KeyFileError -> KeyFileError -> Bool
$c/= :: KeyFileError -> KeyFileError -> Bool
/= :: KeyFileError -> KeyFileError -> Bool
Eq)

instance P.Enum KeyFileError where
    fromEnum :: KeyFileError -> Int
fromEnum KeyFileError
KeyFileErrorUnknownEncoding = Int
0
    fromEnum KeyFileError
KeyFileErrorParse = Int
1
    fromEnum KeyFileError
KeyFileErrorNotFound = Int
2
    fromEnum KeyFileError
KeyFileErrorKeyNotFound = Int
3
    fromEnum KeyFileError
KeyFileErrorGroupNotFound = Int
4
    fromEnum KeyFileError
KeyFileErrorInvalidValue = Int
5
    fromEnum (AnotherKeyFileError Int
k) = Int
k

    toEnum :: Int -> KeyFileError
toEnum Int
0 = KeyFileError
KeyFileErrorUnknownEncoding
    toEnum Int
1 = KeyFileError
KeyFileErrorParse
    toEnum Int
2 = KeyFileError
KeyFileErrorNotFound
    toEnum Int
3 = KeyFileError
KeyFileErrorKeyNotFound
    toEnum Int
4 = KeyFileError
KeyFileErrorGroupNotFound
    toEnum Int
5 = KeyFileError
KeyFileErrorInvalidValue
    toEnum Int
k = Int -> KeyFileError
AnotherKeyFileError Int
k

instance P.Ord KeyFileError where
    compare :: KeyFileError -> KeyFileError -> Ordering
compare KeyFileError
a KeyFileError
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (KeyFileError -> Int
forall a. Enum a => a -> Int
P.fromEnum KeyFileError
a) (KeyFileError -> Int
forall a. Enum a => a -> Int
P.fromEnum KeyFileError
b)

instance GErrorClass KeyFileError where
    gerrorClassDomain :: KeyFileError -> Text
gerrorClassDomain KeyFileError
_ = Text
"g-key-file-error-quark"

-- | Catch exceptions of type `KeyFileError`. This is a specialized version of `Data.GI.Base.GError.catchGErrorJustDomain`.
catchKeyFileError ::
    IO a ->
    (KeyFileError -> GErrorMessage -> IO a) ->
    IO a
catchKeyFileError :: forall a. IO a -> (KeyFileError -> Text -> IO a) -> IO a
catchKeyFileError = IO a -> (KeyFileError -> Text -> IO a) -> IO a
forall err a.
GErrorClass err =>
IO a -> (err -> Text -> IO a) -> IO a
catchGErrorJustDomain

-- | Handle exceptions of type `KeyFileError`. This is a specialized version of `Data.GI.Base.GError.handleGErrorJustDomain`.
handleKeyFileError ::
    (KeyFileError -> GErrorMessage -> IO a) ->
    IO a ->
    IO a
handleKeyFileError :: forall a. (KeyFileError -> Text -> IO a) -> IO a -> IO a
handleKeyFileError = (KeyFileError -> Text -> IO a) -> IO a -> IO a
forall err a.
GErrorClass err =>
(err -> Text -> IO a) -> IO a -> IO a
handleGErrorJustDomain

-- Enum IOStatus
-- | Statuses returned by most of the t'GI.GLib.Structs.IOFuncs.IOFuncs' functions.
data IOStatus = 
      IOStatusError
    -- ^ An error occurred.
    | IOStatusNormal
    -- ^ Success.
    | IOStatusEof
    -- ^ End of file.
    | IOStatusAgain
    -- ^ Resource temporarily unavailable.
    | AnotherIOStatus Int
    -- ^ Catch-all for unknown values
    deriving (Int -> IOStatus -> ShowS
[IOStatus] -> ShowS
IOStatus -> String
(Int -> IOStatus -> ShowS)
-> (IOStatus -> String) -> ([IOStatus] -> ShowS) -> Show IOStatus
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> IOStatus -> ShowS
showsPrec :: Int -> IOStatus -> ShowS
$cshow :: IOStatus -> String
show :: IOStatus -> String
$cshowList :: [IOStatus] -> ShowS
showList :: [IOStatus] -> ShowS
Show, IOStatus -> IOStatus -> Bool
(IOStatus -> IOStatus -> Bool)
-> (IOStatus -> IOStatus -> Bool) -> Eq IOStatus
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: IOStatus -> IOStatus -> Bool
== :: IOStatus -> IOStatus -> Bool
$c/= :: IOStatus -> IOStatus -> Bool
/= :: IOStatus -> IOStatus -> Bool
Eq)

instance P.Enum IOStatus where
    fromEnum :: IOStatus -> Int
fromEnum IOStatus
IOStatusError = Int
0
    fromEnum IOStatus
IOStatusNormal = Int
1
    fromEnum IOStatus
IOStatusEof = Int
2
    fromEnum IOStatus
IOStatusAgain = Int
3
    fromEnum (AnotherIOStatus Int
k) = Int
k

    toEnum :: Int -> IOStatus
toEnum Int
0 = IOStatus
IOStatusError
    toEnum Int
1 = IOStatus
IOStatusNormal
    toEnum Int
2 = IOStatus
IOStatusEof
    toEnum Int
3 = IOStatus
IOStatusAgain
    toEnum Int
k = Int -> IOStatus
AnotherIOStatus Int
k

instance P.Ord IOStatus where
    compare :: IOStatus -> IOStatus -> Ordering
compare IOStatus
a IOStatus
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (IOStatus -> Int
forall a. Enum a => a -> Int
P.fromEnum IOStatus
a) (IOStatus -> Int
forall a. Enum a => a -> Int
P.fromEnum IOStatus
b)

-- Enum IOError
-- | t'GI.GLib.Enums.IOError' is only used by the deprecated functions
-- 'GI.GLib.Structs.IOChannel.iOChannelRead', 'GI.GLib.Structs.IOChannel.iOChannelWrite', and 'GI.GLib.Structs.IOChannel.iOChannelSeek'.
data IOError = 
      IOErrorNone
    -- ^ no error
    | IOErrorAgain
    -- ^ an EAGAIN error occurred
    | IOErrorInval
    -- ^ an EINVAL error occurred
    | IOErrorUnknown
    -- ^ another error occurred
    | AnotherIOError Int
    -- ^ Catch-all for unknown values
    deriving (Int -> IOError -> ShowS
[IOError] -> ShowS
IOError -> String
(Int -> IOError -> ShowS)
-> (IOError -> String) -> ([IOError] -> ShowS) -> Show IOError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> IOError -> ShowS
showsPrec :: Int -> IOError -> ShowS
$cshow :: IOError -> String
show :: IOError -> String
$cshowList :: [IOError] -> ShowS
showList :: [IOError] -> ShowS
Show, IOError -> IOError -> Bool
(IOError -> IOError -> Bool)
-> (IOError -> IOError -> Bool) -> Eq IOError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: IOError -> IOError -> Bool
== :: IOError -> IOError -> Bool
$c/= :: IOError -> IOError -> Bool
/= :: IOError -> IOError -> Bool
Eq)

instance P.Enum IOError where
    fromEnum :: IOError -> Int
fromEnum IOError
IOErrorNone = Int
0
    fromEnum IOError
IOErrorAgain = Int
1
    fromEnum IOError
IOErrorInval = Int
2
    fromEnum IOError
IOErrorUnknown = Int
3
    fromEnum (AnotherIOError Int
k) = Int
k

    toEnum :: Int -> IOError
toEnum Int
0 = IOError
IOErrorNone
    toEnum Int
1 = IOError
IOErrorAgain
    toEnum Int
2 = IOError
IOErrorInval
    toEnum Int
3 = IOError
IOErrorUnknown
    toEnum Int
k = Int -> IOError
AnotherIOError Int
k

instance P.Ord IOError where
    compare :: IOError -> IOError -> Ordering
compare IOError
a IOError
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (IOError -> Int
forall a. Enum a => a -> Int
P.fromEnum IOError
a) (IOError -> Int
forall a. Enum a => a -> Int
P.fromEnum IOError
b)

-- Enum IOChannelError
-- | Error codes returned by t'GI.GLib.Structs.IOChannel.IOChannel' operations.
data IOChannelError = 
      IOChannelErrorFbig
    -- ^ File too large.
    | IOChannelErrorInval
    -- ^ Invalid argument.
    | IOChannelErrorIo
    -- ^ IO error.
    | IOChannelErrorIsdir
    -- ^ File is a directory.
    | IOChannelErrorNospc
    -- ^ No space left on device.
    | IOChannelErrorNxio
    -- ^ No such device or address.
    | IOChannelErrorOverflow
    -- ^ Value too large for defined datatype.
    | IOChannelErrorPipe
    -- ^ Broken pipe.
    | IOChannelErrorFailed
    -- ^ Some other error.
    | AnotherIOChannelError Int
    -- ^ Catch-all for unknown values
    deriving (Int -> IOChannelError -> ShowS
[IOChannelError] -> ShowS
IOChannelError -> String
(Int -> IOChannelError -> ShowS)
-> (IOChannelError -> String)
-> ([IOChannelError] -> ShowS)
-> Show IOChannelError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> IOChannelError -> ShowS
showsPrec :: Int -> IOChannelError -> ShowS
$cshow :: IOChannelError -> String
show :: IOChannelError -> String
$cshowList :: [IOChannelError] -> ShowS
showList :: [IOChannelError] -> ShowS
Show, IOChannelError -> IOChannelError -> Bool
(IOChannelError -> IOChannelError -> Bool)
-> (IOChannelError -> IOChannelError -> Bool) -> Eq IOChannelError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: IOChannelError -> IOChannelError -> Bool
== :: IOChannelError -> IOChannelError -> Bool
$c/= :: IOChannelError -> IOChannelError -> Bool
/= :: IOChannelError -> IOChannelError -> Bool
Eq)

instance P.Enum IOChannelError where
    fromEnum :: IOChannelError -> Int
fromEnum IOChannelError
IOChannelErrorFbig = Int
0
    fromEnum IOChannelError
IOChannelErrorInval = Int
1
    fromEnum IOChannelError
IOChannelErrorIo = Int
2
    fromEnum IOChannelError
IOChannelErrorIsdir = Int
3
    fromEnum IOChannelError
IOChannelErrorNospc = Int
4
    fromEnum IOChannelError
IOChannelErrorNxio = Int
5
    fromEnum IOChannelError
IOChannelErrorOverflow = Int
6
    fromEnum IOChannelError
IOChannelErrorPipe = Int
7
    fromEnum IOChannelError
IOChannelErrorFailed = Int
8
    fromEnum (AnotherIOChannelError Int
k) = Int
k

    toEnum :: Int -> IOChannelError
toEnum Int
0 = IOChannelError
IOChannelErrorFbig
    toEnum Int
1 = IOChannelError
IOChannelErrorInval
    toEnum Int
2 = IOChannelError
IOChannelErrorIo
    toEnum Int
3 = IOChannelError
IOChannelErrorIsdir
    toEnum Int
4 = IOChannelError
IOChannelErrorNospc
    toEnum Int
5 = IOChannelError
IOChannelErrorNxio
    toEnum Int
6 = IOChannelError
IOChannelErrorOverflow
    toEnum Int
7 = IOChannelError
IOChannelErrorPipe
    toEnum Int
8 = IOChannelError
IOChannelErrorFailed
    toEnum Int
k = Int -> IOChannelError
AnotherIOChannelError Int
k

instance P.Ord IOChannelError where
    compare :: IOChannelError -> IOChannelError -> Ordering
compare IOChannelError
a IOChannelError
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (IOChannelError -> Int
forall a. Enum a => a -> Int
P.fromEnum IOChannelError
a) (IOChannelError -> Int
forall a. Enum a => a -> Int
P.fromEnum IOChannelError
b)

instance GErrorClass IOChannelError where
    gerrorClassDomain :: IOChannelError -> Text
gerrorClassDomain IOChannelError
_ = Text
"g-io-channel-error-quark"

-- | Catch exceptions of type `IOChannelError`. This is a specialized version of `Data.GI.Base.GError.catchGErrorJustDomain`.
catchIOChannelError ::
    IO a ->
    (IOChannelError -> GErrorMessage -> IO a) ->
    IO a
catchIOChannelError :: forall a. IO a -> (IOChannelError -> Text -> IO a) -> IO a
catchIOChannelError = IO a -> (IOChannelError -> Text -> IO a) -> IO a
forall err a.
GErrorClass err =>
IO a -> (err -> Text -> IO a) -> IO a
catchGErrorJustDomain

-- | Handle exceptions of type `IOChannelError`. This is a specialized version of `Data.GI.Base.GError.handleGErrorJustDomain`.
handleIOChannelError ::
    (IOChannelError -> GErrorMessage -> IO a) ->
    IO a ->
    IO a
handleIOChannelError :: forall a. (IOChannelError -> Text -> IO a) -> IO a -> IO a
handleIOChannelError = (IOChannelError -> Text -> IO a) -> IO a -> IO a
forall err a.
GErrorClass err =>
(err -> Text -> IO a) -> IO a -> IO a
handleGErrorJustDomain

-- Enum FileError
-- | Values corresponding to /@errno@/ codes returned from file operations
-- on UNIX. Unlike /@errno@/ codes, GFileError values are available on
-- all systems, even Windows. The exact meaning of each code depends
-- on what sort of file operation you were performing; the UNIX
-- documentation gives more details. The following error code descriptions
-- come from the GNU C Library manual, and are under the copyright
-- of that manual.
-- 
-- It\'s not very portable to make detailed assumptions about exactly
-- which errors will be returned from a given operation. Some errors
-- don\'t occur on some systems, etc., sometimes there are subtle
-- differences in when a system will report a given error, etc.
data FileError = 
      FileErrorExist
    -- ^ Operation not permitted; only the owner of
    --     the file (or other resource) or processes with special privileges
    --     can perform the operation.
    | FileErrorIsdir
    -- ^ File is a directory; you cannot open a directory
    --     for writing, or create or remove hard links to it.
    | FileErrorAcces
    -- ^ Permission denied; the file permissions do not
    --     allow the attempted operation.
    | FileErrorNametoolong
    -- ^ Filename too long.
    | FileErrorNoent
    -- ^ No such file or directory. This is a \"file
    --     doesn\'t exist\" error for ordinary files that are referenced in
    --     contexts where they are expected to already exist.
    | FileErrorNotdir
    -- ^ A file that isn\'t a directory was specified when
    --     a directory is required.
    | FileErrorNxio
    -- ^ No such device or address. The system tried to
    --     use the device represented by a file you specified, and it
    --     couldn\'t find the device. This can mean that the device file was
    --     installed incorrectly, or that the physical device is missing or
    --     not correctly attached to the computer.
    | FileErrorNodev
    -- ^ The underlying file system of the specified file
    --     does not support memory mapping.
    | FileErrorRofs
    -- ^ The directory containing the new link can\'t be
    --     modified because it\'s on a read-only file system.
    | FileErrorTxtbsy
    -- ^ Text file busy.
    | FileErrorFault
    -- ^ You passed in a pointer to bad memory.
    --     (GLib won\'t reliably return this, don\'t pass in pointers to bad
    --     memory.)
    | FileErrorLoop
    -- ^ Too many levels of symbolic links were encountered
    --     in looking up a file name. This often indicates a cycle of symbolic
    --     links.
    | FileErrorNospc
    -- ^ No space left on device; write operation on a
    --     file failed because the disk is full.
    | FileErrorNomem
    -- ^ No memory available. The system cannot allocate
    --     more virtual memory because its capacity is full.
    | FileErrorMfile
    -- ^ The current process has too many files open and
    --     can\'t open any more. Duplicate descriptors do count toward this
    --     limit.
    | FileErrorNfile
    -- ^ There are too many distinct file openings in the
    --     entire system.
    | FileErrorBadf
    -- ^ Bad file descriptor; for example, I\/O on a
    --     descriptor that has been closed or reading from a descriptor open
    --     only for writing (or vice versa).
    | FileErrorInval
    -- ^ Invalid argument. This is used to indicate
    --     various kinds of problems with passing the wrong argument to a
    --     library function.
    | FileErrorPipe
    -- ^ Broken pipe; there is no process reading from the
    --     other end of a pipe. Every library function that returns this
    --     error code also generates a \'SIGPIPE\' signal; this signal
    --     terminates the program if not handled or blocked. Thus, your
    --     program will never actually see this code unless it has handled
    --     or blocked \'SIGPIPE\'.
    | FileErrorAgain
    -- ^ Resource temporarily unavailable; the call might
    --     work if you try again later.
    | FileErrorIntr
    -- ^ Interrupted function call; an asynchronous signal
    --     occurred and prevented completion of the call. When this
    --     happens, you should try the call again.
    | FileErrorIo
    -- ^ Input\/output error; usually used for physical read
    --    or write errors. i.e. the disk or other physical device hardware
    --    is returning errors.
    | FileErrorPerm
    -- ^ Operation not permitted; only the owner of the
    --    file (or other resource) or processes with special privileges can
    --    perform the operation.
    | FileErrorNosys
    -- ^ Function not implemented; this indicates that
    --    the system is missing some functionality.
    | FileErrorFailed
    -- ^ Does not correspond to a UNIX error code; this
    --    is the standard \"failed for unspecified reason\" error code present
    --    in all t'GError' error code enumerations. Returned if no specific
    --    code applies.
    | AnotherFileError Int
    -- ^ Catch-all for unknown values
    deriving (Int -> FileError -> ShowS
[FileError] -> ShowS
FileError -> String
(Int -> FileError -> ShowS)
-> (FileError -> String)
-> ([FileError] -> ShowS)
-> Show FileError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FileError -> ShowS
showsPrec :: Int -> FileError -> ShowS
$cshow :: FileError -> String
show :: FileError -> String
$cshowList :: [FileError] -> ShowS
showList :: [FileError] -> ShowS
Show, FileError -> FileError -> Bool
(FileError -> FileError -> Bool)
-> (FileError -> FileError -> Bool) -> Eq FileError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FileError -> FileError -> Bool
== :: FileError -> FileError -> Bool
$c/= :: FileError -> FileError -> Bool
/= :: FileError -> FileError -> Bool
Eq)

instance P.Enum FileError where
    fromEnum :: FileError -> Int
fromEnum FileError
FileErrorExist = Int
0
    fromEnum FileError
FileErrorIsdir = Int
1
    fromEnum FileError
FileErrorAcces = Int
2
    fromEnum FileError
FileErrorNametoolong = Int
3
    fromEnum FileError
FileErrorNoent = Int
4
    fromEnum FileError
FileErrorNotdir = Int
5
    fromEnum FileError
FileErrorNxio = Int
6
    fromEnum FileError
FileErrorNodev = Int
7
    fromEnum FileError
FileErrorRofs = Int
8
    fromEnum FileError
FileErrorTxtbsy = Int
9
    fromEnum FileError
FileErrorFault = Int
10
    fromEnum FileError
FileErrorLoop = Int
11
    fromEnum FileError
FileErrorNospc = Int
12
    fromEnum FileError
FileErrorNomem = Int
13
    fromEnum FileError
FileErrorMfile = Int
14
    fromEnum FileError
FileErrorNfile = Int
15
    fromEnum FileError
FileErrorBadf = Int
16
    fromEnum FileError
FileErrorInval = Int
17
    fromEnum FileError
FileErrorPipe = Int
18
    fromEnum FileError
FileErrorAgain = Int
19
    fromEnum FileError
FileErrorIntr = Int
20
    fromEnum FileError
FileErrorIo = Int
21
    fromEnum FileError
FileErrorPerm = Int
22
    fromEnum FileError
FileErrorNosys = Int
23
    fromEnum FileError
FileErrorFailed = Int
24
    fromEnum (AnotherFileError Int
k) = Int
k

    toEnum :: Int -> FileError
toEnum Int
0 = FileError
FileErrorExist
    toEnum Int
1 = FileError
FileErrorIsdir
    toEnum Int
2 = FileError
FileErrorAcces
    toEnum Int
3 = FileError
FileErrorNametoolong
    toEnum Int
4 = FileError
FileErrorNoent
    toEnum Int
5 = FileError
FileErrorNotdir
    toEnum Int
6 = FileError
FileErrorNxio
    toEnum Int
7 = FileError
FileErrorNodev
    toEnum Int
8 = FileError
FileErrorRofs
    toEnum Int
9 = FileError
FileErrorTxtbsy
    toEnum Int
10 = FileError
FileErrorFault
    toEnum Int
11 = FileError
FileErrorLoop
    toEnum Int
12 = FileError
FileErrorNospc
    toEnum Int
13 = FileError
FileErrorNomem
    toEnum Int
14 = FileError
FileErrorMfile
    toEnum Int
15 = FileError
FileErrorNfile
    toEnum Int
16 = FileError
FileErrorBadf
    toEnum Int
17 = FileError
FileErrorInval
    toEnum Int
18 = FileError
FileErrorPipe
    toEnum Int
19 = FileError
FileErrorAgain
    toEnum Int
20 = FileError
FileErrorIntr
    toEnum Int
21 = FileError
FileErrorIo
    toEnum Int
22 = FileError
FileErrorPerm
    toEnum Int
23 = FileError
FileErrorNosys
    toEnum Int
24 = FileError
FileErrorFailed
    toEnum Int
k = Int -> FileError
AnotherFileError Int
k

instance P.Ord FileError where
    compare :: FileError -> FileError -> Ordering
compare FileError
a FileError
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (FileError -> Int
forall a. Enum a => a -> Int
P.fromEnum FileError
a) (FileError -> Int
forall a. Enum a => a -> Int
P.fromEnum FileError
b)

instance GErrorClass FileError where
    gerrorClassDomain :: FileError -> Text
gerrorClassDomain FileError
_ = Text
"g-file-error-quark"

-- | Catch exceptions of type `FileError`. This is a specialized version of `Data.GI.Base.GError.catchGErrorJustDomain`.
catchFileError ::
    IO a ->
    (FileError -> GErrorMessage -> IO a) ->
    IO a
catchFileError :: forall a. IO a -> (FileError -> Text -> IO a) -> IO a
catchFileError = IO a -> (FileError -> Text -> IO a) -> IO a
forall err a.
GErrorClass err =>
IO a -> (err -> Text -> IO a) -> IO a
catchGErrorJustDomain

-- | Handle exceptions of type `FileError`. This is a specialized version of `Data.GI.Base.GError.handleGErrorJustDomain`.
handleFileError ::
    (FileError -> GErrorMessage -> IO a) ->
    IO a ->
    IO a
handleFileError :: forall a. (FileError -> Text -> IO a) -> IO a -> IO a
handleFileError = (FileError -> Text -> IO a) -> IO a -> IO a
forall err a.
GErrorClass err =>
(err -> Text -> IO a) -> IO a -> IO a
handleGErrorJustDomain

-- Enum ErrorType
-- | The possible errors, used in the /@vError@/ field
-- of t'GI.GLib.Unions.TokenValue.TokenValue', when the token is a 'GI.GLib.Enums.TokenTypeError'.
data ErrorType = 
      ErrorTypeUnknown
    -- ^ unknown error
    | ErrorTypeUnexpEof
    -- ^ unexpected end of file
    | ErrorTypeUnexpEofInString
    -- ^ unterminated string constant
    | ErrorTypeUnexpEofInComment
    -- ^ unterminated comment
    | ErrorTypeNonDigitInConst
    -- ^ non-digit character in a number
    | ErrorTypeDigitRadix
    -- ^ digit beyond radix in a number
    | ErrorTypeFloatRadix
    -- ^ non-decimal floating point number
    | ErrorTypeFloatMalformed
    -- ^ malformed floating point number
    | AnotherErrorType Int
    -- ^ Catch-all for unknown values
    deriving (Int -> ErrorType -> ShowS
[ErrorType] -> ShowS
ErrorType -> String
(Int -> ErrorType -> ShowS)
-> (ErrorType -> String)
-> ([ErrorType] -> ShowS)
-> Show ErrorType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ErrorType -> ShowS
showsPrec :: Int -> ErrorType -> ShowS
$cshow :: ErrorType -> String
show :: ErrorType -> String
$cshowList :: [ErrorType] -> ShowS
showList :: [ErrorType] -> ShowS
Show, ErrorType -> ErrorType -> Bool
(ErrorType -> ErrorType -> Bool)
-> (ErrorType -> ErrorType -> Bool) -> Eq ErrorType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ErrorType -> ErrorType -> Bool
== :: ErrorType -> ErrorType -> Bool
$c/= :: ErrorType -> ErrorType -> Bool
/= :: ErrorType -> ErrorType -> Bool
Eq)

instance P.Enum ErrorType where
    fromEnum :: ErrorType -> Int
fromEnum ErrorType
ErrorTypeUnknown = Int
0
    fromEnum ErrorType
ErrorTypeUnexpEof = Int
1
    fromEnum ErrorType
ErrorTypeUnexpEofInString = Int
2
    fromEnum ErrorType
ErrorTypeUnexpEofInComment = Int
3
    fromEnum ErrorType
ErrorTypeNonDigitInConst = Int
4
    fromEnum ErrorType
ErrorTypeDigitRadix = Int
5
    fromEnum ErrorType
ErrorTypeFloatRadix = Int
6
    fromEnum ErrorType
ErrorTypeFloatMalformed = Int
7
    fromEnum (AnotherErrorType Int
k) = Int
k

    toEnum :: Int -> ErrorType
toEnum Int
0 = ErrorType
ErrorTypeUnknown
    toEnum Int
1 = ErrorType
ErrorTypeUnexpEof
    toEnum Int
2 = ErrorType
ErrorTypeUnexpEofInString
    toEnum Int
3 = ErrorType
ErrorTypeUnexpEofInComment
    toEnum Int
4 = ErrorType
ErrorTypeNonDigitInConst
    toEnum Int
5 = ErrorType
ErrorTypeDigitRadix
    toEnum Int
6 = ErrorType
ErrorTypeFloatRadix
    toEnum Int
7 = ErrorType
ErrorTypeFloatMalformed
    toEnum Int
k = Int -> ErrorType
AnotherErrorType Int
k

instance P.Ord ErrorType where
    compare :: ErrorType -> ErrorType -> Ordering
compare ErrorType
a ErrorType
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (ErrorType -> Int
forall a. Enum a => a -> Int
P.fromEnum ErrorType
a) (ErrorType -> Int
forall a. Enum a => a -> Int
P.fromEnum ErrorType
b)

-- Enum DateWeekday
-- | Enumeration representing a day of the week; 'GI.GLib.Enums.DateWeekdayMonday',
-- 'GI.GLib.Enums.DateWeekdayTuesday', etc. 'GI.GLib.Enums.DateWeekdayBadWeekday' is an invalid weekday.
data DateWeekday = 
      DateWeekdayBadWeekday
    -- ^ invalid value
    | DateWeekdayMonday
    -- ^ Monday
    | DateWeekdayTuesday
    -- ^ Tuesday
    | DateWeekdayWednesday
    -- ^ Wednesday
    | DateWeekdayThursday
    -- ^ Thursday
    | DateWeekdayFriday
    -- ^ Friday
    | DateWeekdaySaturday
    -- ^ Saturday
    | DateWeekdaySunday
    -- ^ Sunday
    | AnotherDateWeekday Int
    -- ^ Catch-all for unknown values
    deriving (Int -> DateWeekday -> ShowS
[DateWeekday] -> ShowS
DateWeekday -> String
(Int -> DateWeekday -> ShowS)
-> (DateWeekday -> String)
-> ([DateWeekday] -> ShowS)
-> Show DateWeekday
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DateWeekday -> ShowS
showsPrec :: Int -> DateWeekday -> ShowS
$cshow :: DateWeekday -> String
show :: DateWeekday -> String
$cshowList :: [DateWeekday] -> ShowS
showList :: [DateWeekday] -> ShowS
Show, DateWeekday -> DateWeekday -> Bool
(DateWeekday -> DateWeekday -> Bool)
-> (DateWeekday -> DateWeekday -> Bool) -> Eq DateWeekday
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DateWeekday -> DateWeekday -> Bool
== :: DateWeekday -> DateWeekday -> Bool
$c/= :: DateWeekday -> DateWeekday -> Bool
/= :: DateWeekday -> DateWeekday -> Bool
Eq)

instance P.Enum DateWeekday where
    fromEnum :: DateWeekday -> Int
fromEnum DateWeekday
DateWeekdayBadWeekday = Int
0
    fromEnum DateWeekday
DateWeekdayMonday = Int
1
    fromEnum DateWeekday
DateWeekdayTuesday = Int
2
    fromEnum DateWeekday
DateWeekdayWednesday = Int
3
    fromEnum DateWeekday
DateWeekdayThursday = Int
4
    fromEnum DateWeekday
DateWeekdayFriday = Int
5
    fromEnum DateWeekday
DateWeekdaySaturday = Int
6
    fromEnum DateWeekday
DateWeekdaySunday = Int
7
    fromEnum (AnotherDateWeekday Int
k) = Int
k

    toEnum :: Int -> DateWeekday
toEnum Int
0 = DateWeekday
DateWeekdayBadWeekday
    toEnum Int
1 = DateWeekday
DateWeekdayMonday
    toEnum Int
2 = DateWeekday
DateWeekdayTuesday
    toEnum Int
3 = DateWeekday
DateWeekdayWednesday
    toEnum Int
4 = DateWeekday
DateWeekdayThursday
    toEnum Int
5 = DateWeekday
DateWeekdayFriday
    toEnum Int
6 = DateWeekday
DateWeekdaySaturday
    toEnum Int
7 = DateWeekday
DateWeekdaySunday
    toEnum Int
k = Int -> DateWeekday
AnotherDateWeekday Int
k

instance P.Ord DateWeekday where
    compare :: DateWeekday -> DateWeekday -> Ordering
compare DateWeekday
a DateWeekday
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (DateWeekday -> Int
forall a. Enum a => a -> Int
P.fromEnum DateWeekday
a) (DateWeekday -> Int
forall a. Enum a => a -> Int
P.fromEnum DateWeekday
b)

-- Enum DateMonth
-- | Enumeration representing a month; values are 'GI.GLib.Enums.DateMonthJanuary',
-- 'GI.GLib.Enums.DateMonthFebruary', etc. 'GI.GLib.Enums.DateMonthBadMonth' is the invalid value.
data DateMonth = 
      DateMonthBadMonth
    -- ^ invalid value
    | DateMonthJanuary
    -- ^ January
    | DateMonthFebruary
    -- ^ February
    | DateMonthMarch
    -- ^ March
    | DateMonthApril
    -- ^ April
    | DateMonthMay
    -- ^ May
    | DateMonthJune
    -- ^ June
    | DateMonthJuly
    -- ^ July
    | DateMonthAugust
    -- ^ August
    | DateMonthSeptember
    -- ^ September
    | DateMonthOctober
    -- ^ October
    | DateMonthNovember
    -- ^ November
    | DateMonthDecember
    -- ^ December
    | AnotherDateMonth Int
    -- ^ Catch-all for unknown values
    deriving (Int -> DateMonth -> ShowS
[DateMonth] -> ShowS
DateMonth -> String
(Int -> DateMonth -> ShowS)
-> (DateMonth -> String)
-> ([DateMonth] -> ShowS)
-> Show DateMonth
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DateMonth -> ShowS
showsPrec :: Int -> DateMonth -> ShowS
$cshow :: DateMonth -> String
show :: DateMonth -> String
$cshowList :: [DateMonth] -> ShowS
showList :: [DateMonth] -> ShowS
Show, DateMonth -> DateMonth -> Bool
(DateMonth -> DateMonth -> Bool)
-> (DateMonth -> DateMonth -> Bool) -> Eq DateMonth
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DateMonth -> DateMonth -> Bool
== :: DateMonth -> DateMonth -> Bool
$c/= :: DateMonth -> DateMonth -> Bool
/= :: DateMonth -> DateMonth -> Bool
Eq)

instance P.Enum DateMonth where
    fromEnum :: DateMonth -> Int
fromEnum DateMonth
DateMonthBadMonth = Int
0
    fromEnum DateMonth
DateMonthJanuary = Int
1
    fromEnum DateMonth
DateMonthFebruary = Int
2
    fromEnum DateMonth
DateMonthMarch = Int
3
    fromEnum DateMonth
DateMonthApril = Int
4
    fromEnum DateMonth
DateMonthMay = Int
5
    fromEnum DateMonth
DateMonthJune = Int
6
    fromEnum DateMonth
DateMonthJuly = Int
7
    fromEnum DateMonth
DateMonthAugust = Int
8
    fromEnum DateMonth
DateMonthSeptember = Int
9
    fromEnum DateMonth
DateMonthOctober = Int
10
    fromEnum DateMonth
DateMonthNovember = Int
11
    fromEnum DateMonth
DateMonthDecember = Int
12
    fromEnum (AnotherDateMonth Int
k) = Int
k

    toEnum :: Int -> DateMonth
toEnum Int
0 = DateMonth
DateMonthBadMonth
    toEnum Int
1 = DateMonth
DateMonthJanuary
    toEnum Int
2 = DateMonth
DateMonthFebruary
    toEnum Int
3 = DateMonth
DateMonthMarch
    toEnum Int
4 = DateMonth
DateMonthApril
    toEnum Int
5 = DateMonth
DateMonthMay
    toEnum Int
6 = DateMonth
DateMonthJune
    toEnum Int
7 = DateMonth
DateMonthJuly
    toEnum Int
8 = DateMonth
DateMonthAugust
    toEnum Int
9 = DateMonth
DateMonthSeptember
    toEnum Int
10 = DateMonth
DateMonthOctober
    toEnum Int
11 = DateMonth
DateMonthNovember
    toEnum Int
12 = DateMonth
DateMonthDecember
    toEnum Int
k = Int -> DateMonth
AnotherDateMonth Int
k

instance P.Ord DateMonth where
    compare :: DateMonth -> DateMonth -> Ordering
compare DateMonth
a DateMonth
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (DateMonth -> Int
forall a. Enum a => a -> Int
P.fromEnum DateMonth
a) (DateMonth -> Int
forall a. Enum a => a -> Int
P.fromEnum DateMonth
b)

-- Enum DateDMY
-- | This enumeration isn\'t used in the API, but may be useful if you need
-- to mark a number as a day, month, or year.
data DateDMY = 
      DateDMYDay
    -- ^ a day
    | DateDMYMonth
    -- ^ a month
    | DateDMYYear
    -- ^ a year
    | AnotherDateDMY Int
    -- ^ Catch-all for unknown values
    deriving (Int -> DateDMY -> ShowS
[DateDMY] -> ShowS
DateDMY -> String
(Int -> DateDMY -> ShowS)
-> (DateDMY -> String) -> ([DateDMY] -> ShowS) -> Show DateDMY
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DateDMY -> ShowS
showsPrec :: Int -> DateDMY -> ShowS
$cshow :: DateDMY -> String
show :: DateDMY -> String
$cshowList :: [DateDMY] -> ShowS
showList :: [DateDMY] -> ShowS
Show, DateDMY -> DateDMY -> Bool
(DateDMY -> DateDMY -> Bool)
-> (DateDMY -> DateDMY -> Bool) -> Eq DateDMY
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DateDMY -> DateDMY -> Bool
== :: DateDMY -> DateDMY -> Bool
$c/= :: DateDMY -> DateDMY -> Bool
/= :: DateDMY -> DateDMY -> Bool
Eq)

instance P.Enum DateDMY where
    fromEnum :: DateDMY -> Int
fromEnum DateDMY
DateDMYDay = Int
0
    fromEnum DateDMY
DateDMYMonth = Int
1
    fromEnum DateDMY
DateDMYYear = Int
2
    fromEnum (AnotherDateDMY Int
k) = Int
k

    toEnum :: Int -> DateDMY
toEnum Int
0 = DateDMY
DateDMYDay
    toEnum Int
1 = DateDMY
DateDMYMonth
    toEnum Int
2 = DateDMY
DateDMYYear
    toEnum Int
k = Int -> DateDMY
AnotherDateDMY Int
k

instance P.Ord DateDMY where
    compare :: DateDMY -> DateDMY -> Ordering
compare DateDMY
a DateDMY
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (DateDMY -> Int
forall a. Enum a => a -> Int
P.fromEnum DateDMY
a) (DateDMY -> Int
forall a. Enum a => a -> Int
P.fromEnum DateDMY
b)

-- Enum ConvertError
-- | Error codes returned by character set conversion routines.
data ConvertError = 
      ConvertErrorNoConversion
    -- ^ Conversion between the requested character
    --     sets is not supported.
    | ConvertErrorIllegalSequence
    -- ^ Invalid byte sequence in conversion input;
    --    or the character sequence could not be represented in the target
    --    character set.
    | ConvertErrorFailed
    -- ^ Conversion failed for some reason.
    | ConvertErrorPartialInput
    -- ^ Partial character sequence at end of input.
    | ConvertErrorBadUri
    -- ^ URI is invalid.
    | ConvertErrorNotAbsolutePath
    -- ^ Pathname is not an absolute path.
    | ConvertErrorNoMemory
    -- ^ No memory available. Since: 2.40
    | ConvertErrorEmbeddedNul
    -- ^ An embedded NUL character is present in
    --     conversion output where a NUL-terminated string is expected.
    --     Since: 2.56
    | AnotherConvertError Int
    -- ^ Catch-all for unknown values
    deriving (Int -> ConvertError -> ShowS
[ConvertError] -> ShowS
ConvertError -> String
(Int -> ConvertError -> ShowS)
-> (ConvertError -> String)
-> ([ConvertError] -> ShowS)
-> Show ConvertError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ConvertError -> ShowS
showsPrec :: Int -> ConvertError -> ShowS
$cshow :: ConvertError -> String
show :: ConvertError -> String
$cshowList :: [ConvertError] -> ShowS
showList :: [ConvertError] -> ShowS
Show, ConvertError -> ConvertError -> Bool
(ConvertError -> ConvertError -> Bool)
-> (ConvertError -> ConvertError -> Bool) -> Eq ConvertError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ConvertError -> ConvertError -> Bool
== :: ConvertError -> ConvertError -> Bool
$c/= :: ConvertError -> ConvertError -> Bool
/= :: ConvertError -> ConvertError -> Bool
Eq)

instance P.Enum ConvertError where
    fromEnum :: ConvertError -> Int
fromEnum ConvertError
ConvertErrorNoConversion = Int
0
    fromEnum ConvertError
ConvertErrorIllegalSequence = Int
1
    fromEnum ConvertError
ConvertErrorFailed = Int
2
    fromEnum ConvertError
ConvertErrorPartialInput = Int
3
    fromEnum ConvertError
ConvertErrorBadUri = Int
4
    fromEnum ConvertError
ConvertErrorNotAbsolutePath = Int
5
    fromEnum ConvertError
ConvertErrorNoMemory = Int
6
    fromEnum ConvertError
ConvertErrorEmbeddedNul = Int
7
    fromEnum (AnotherConvertError Int
k) = Int
k

    toEnum :: Int -> ConvertError
toEnum Int
0 = ConvertError
ConvertErrorNoConversion
    toEnum Int
1 = ConvertError
ConvertErrorIllegalSequence
    toEnum Int
2 = ConvertError
ConvertErrorFailed
    toEnum Int
3 = ConvertError
ConvertErrorPartialInput
    toEnum Int
4 = ConvertError
ConvertErrorBadUri
    toEnum Int
5 = ConvertError
ConvertErrorNotAbsolutePath
    toEnum Int
6 = ConvertError
ConvertErrorNoMemory
    toEnum Int
7 = ConvertError
ConvertErrorEmbeddedNul
    toEnum Int
k = Int -> ConvertError
AnotherConvertError Int
k

instance P.Ord ConvertError where
    compare :: ConvertError -> ConvertError -> Ordering
compare ConvertError
a ConvertError
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (ConvertError -> Int
forall a. Enum a => a -> Int
P.fromEnum ConvertError
a) (ConvertError -> Int
forall a. Enum a => a -> Int
P.fromEnum ConvertError
b)

instance GErrorClass ConvertError where
    gerrorClassDomain :: ConvertError -> Text
gerrorClassDomain ConvertError
_ = Text
"g_convert_error"

-- | Catch exceptions of type `ConvertError`. This is a specialized version of `Data.GI.Base.GError.catchGErrorJustDomain`.
catchConvertError ::
    IO a ->
    (ConvertError -> GErrorMessage -> IO a) ->
    IO a
catchConvertError :: forall a. IO a -> (ConvertError -> Text -> IO a) -> IO a
catchConvertError = IO a -> (ConvertError -> Text -> IO a) -> IO a
forall err a.
GErrorClass err =>
IO a -> (err -> Text -> IO a) -> IO a
catchGErrorJustDomain

-- | Handle exceptions of type `ConvertError`. This is a specialized version of `Data.GI.Base.GError.handleGErrorJustDomain`.
handleConvertError ::
    (ConvertError -> GErrorMessage -> IO a) ->
    IO a ->
    IO a
handleConvertError :: forall a. (ConvertError -> Text -> IO a) -> IO a -> IO a
handleConvertError = (ConvertError -> Text -> IO a) -> IO a -> IO a
forall err a.
GErrorClass err =>
(err -> Text -> IO a) -> IO a -> IO a
handleGErrorJustDomain

-- Enum ChecksumType
-- | The hashing algorithm to be used by t'GI.GLib.Structs.Checksum.Checksum' when performing the
-- digest of some data.
-- 
-- Note that the t'GI.GLib.Enums.ChecksumType' enumeration may be extended at a later
-- date to include new hashing algorithm types.
-- 
-- /Since: 2.16/
data ChecksumType = 
      ChecksumTypeMd5
    -- ^ Use the MD5 hashing algorithm
    | ChecksumTypeSha1
    -- ^ Use the SHA-1 hashing algorithm
    | ChecksumTypeSha256
    -- ^ Use the SHA-256 hashing algorithm
    | ChecksumTypeSha512
    -- ^ Use the SHA-512 hashing algorithm (Since: 2.36)
    | ChecksumTypeSha384
    -- ^ Use the SHA-384 hashing algorithm (Since: 2.51)
    | AnotherChecksumType Int
    -- ^ Catch-all for unknown values
    deriving (Int -> ChecksumType -> ShowS
[ChecksumType] -> ShowS
ChecksumType -> String
(Int -> ChecksumType -> ShowS)
-> (ChecksumType -> String)
-> ([ChecksumType] -> ShowS)
-> Show ChecksumType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ChecksumType -> ShowS
showsPrec :: Int -> ChecksumType -> ShowS
$cshow :: ChecksumType -> String
show :: ChecksumType -> String
$cshowList :: [ChecksumType] -> ShowS
showList :: [ChecksumType] -> ShowS
Show, ChecksumType -> ChecksumType -> Bool
(ChecksumType -> ChecksumType -> Bool)
-> (ChecksumType -> ChecksumType -> Bool) -> Eq ChecksumType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ChecksumType -> ChecksumType -> Bool
== :: ChecksumType -> ChecksumType -> Bool
$c/= :: ChecksumType -> ChecksumType -> Bool
/= :: ChecksumType -> ChecksumType -> Bool
Eq)

instance P.Enum ChecksumType where
    fromEnum :: ChecksumType -> Int
fromEnum ChecksumType
ChecksumTypeMd5 = Int
0
    fromEnum ChecksumType
ChecksumTypeSha1 = Int
1
    fromEnum ChecksumType
ChecksumTypeSha256 = Int
2
    fromEnum ChecksumType
ChecksumTypeSha512 = Int
3
    fromEnum ChecksumType
ChecksumTypeSha384 = Int
4
    fromEnum (AnotherChecksumType Int
k) = Int
k

    toEnum :: Int -> ChecksumType
toEnum Int
0 = ChecksumType
ChecksumTypeMd5
    toEnum Int
1 = ChecksumType
ChecksumTypeSha1
    toEnum Int
2 = ChecksumType
ChecksumTypeSha256
    toEnum Int
3 = ChecksumType
ChecksumTypeSha512
    toEnum Int
4 = ChecksumType
ChecksumTypeSha384
    toEnum Int
k = Int -> ChecksumType
AnotherChecksumType Int
k

instance P.Ord ChecksumType where
    compare :: ChecksumType -> ChecksumType -> Ordering
compare ChecksumType
a ChecksumType
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (ChecksumType -> Int
forall a. Enum a => a -> Int
P.fromEnum ChecksumType
a) (ChecksumType -> Int
forall a. Enum a => a -> Int
P.fromEnum ChecksumType
b)

-- Enum BookmarkFileError
-- | Error codes returned by bookmark file parsing.
data BookmarkFileError = 
      BookmarkFileErrorInvalidUri
    -- ^ URI was ill-formed
    | BookmarkFileErrorInvalidValue
    -- ^ a requested field was not found
    | BookmarkFileErrorAppNotRegistered
    -- ^ a requested application did
    --     not register a bookmark
    | BookmarkFileErrorUriNotFound
    -- ^ a requested URI was not found
    | BookmarkFileErrorRead
    -- ^ document was ill formed
    | BookmarkFileErrorUnknownEncoding
    -- ^ the text being parsed was
    --     in an unknown encoding
    | BookmarkFileErrorWrite
    -- ^ an error occurred while writing
    | BookmarkFileErrorFileNotFound
    -- ^ requested file was not found
    | AnotherBookmarkFileError Int
    -- ^ Catch-all for unknown values
    deriving (Int -> BookmarkFileError -> ShowS
[BookmarkFileError] -> ShowS
BookmarkFileError -> String
(Int -> BookmarkFileError -> ShowS)
-> (BookmarkFileError -> String)
-> ([BookmarkFileError] -> ShowS)
-> Show BookmarkFileError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> BookmarkFileError -> ShowS
showsPrec :: Int -> BookmarkFileError -> ShowS
$cshow :: BookmarkFileError -> String
show :: BookmarkFileError -> String
$cshowList :: [BookmarkFileError] -> ShowS
showList :: [BookmarkFileError] -> ShowS
Show, BookmarkFileError -> BookmarkFileError -> Bool
(BookmarkFileError -> BookmarkFileError -> Bool)
-> (BookmarkFileError -> BookmarkFileError -> Bool)
-> Eq BookmarkFileError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: BookmarkFileError -> BookmarkFileError -> Bool
== :: BookmarkFileError -> BookmarkFileError -> Bool
$c/= :: BookmarkFileError -> BookmarkFileError -> Bool
/= :: BookmarkFileError -> BookmarkFileError -> Bool
Eq)

instance P.Enum BookmarkFileError where
    fromEnum :: BookmarkFileError -> Int
fromEnum BookmarkFileError
BookmarkFileErrorInvalidUri = Int
0
    fromEnum BookmarkFileError
BookmarkFileErrorInvalidValue = Int
1
    fromEnum BookmarkFileError
BookmarkFileErrorAppNotRegistered = Int
2
    fromEnum BookmarkFileError
BookmarkFileErrorUriNotFound = Int
3
    fromEnum BookmarkFileError
BookmarkFileErrorRead = Int
4
    fromEnum BookmarkFileError
BookmarkFileErrorUnknownEncoding = Int
5
    fromEnum BookmarkFileError
BookmarkFileErrorWrite = Int
6
    fromEnum BookmarkFileError
BookmarkFileErrorFileNotFound = Int
7
    fromEnum (AnotherBookmarkFileError Int
k) = Int
k

    toEnum :: Int -> BookmarkFileError
toEnum Int
0 = BookmarkFileError
BookmarkFileErrorInvalidUri
    toEnum Int
1 = BookmarkFileError
BookmarkFileErrorInvalidValue
    toEnum Int
2 = BookmarkFileError
BookmarkFileErrorAppNotRegistered
    toEnum Int
3 = BookmarkFileError
BookmarkFileErrorUriNotFound
    toEnum Int
4 = BookmarkFileError
BookmarkFileErrorRead
    toEnum Int
5 = BookmarkFileError
BookmarkFileErrorUnknownEncoding
    toEnum Int
6 = BookmarkFileError
BookmarkFileErrorWrite
    toEnum Int
7 = BookmarkFileError
BookmarkFileErrorFileNotFound
    toEnum Int
k = Int -> BookmarkFileError
AnotherBookmarkFileError Int
k

instance P.Ord BookmarkFileError where
    compare :: BookmarkFileError -> BookmarkFileError -> Ordering
compare BookmarkFileError
a BookmarkFileError
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (BookmarkFileError -> Int
forall a. Enum a => a -> Int
P.fromEnum BookmarkFileError
a) (BookmarkFileError -> Int
forall a. Enum a => a -> Int
P.fromEnum BookmarkFileError
b)

instance GErrorClass BookmarkFileError where
    gerrorClassDomain :: BookmarkFileError -> Text
gerrorClassDomain BookmarkFileError
_ = Text
"g-bookmark-file-error-quark"

-- | Catch exceptions of type `BookmarkFileError`. This is a specialized version of `Data.GI.Base.GError.catchGErrorJustDomain`.
catchBookmarkFileError ::
    IO a ->
    (BookmarkFileError -> GErrorMessage -> IO a) ->
    IO a
catchBookmarkFileError :: forall a. IO a -> (BookmarkFileError -> Text -> IO a) -> IO a
catchBookmarkFileError = IO a -> (BookmarkFileError -> Text -> IO a) -> IO a
forall err a.
GErrorClass err =>
IO a -> (err -> Text -> IO a) -> IO a
catchGErrorJustDomain

-- | Handle exceptions of type `BookmarkFileError`. This is a specialized version of `Data.GI.Base.GError.handleGErrorJustDomain`.
handleBookmarkFileError ::
    (BookmarkFileError -> GErrorMessage -> IO a) ->
    IO a ->
    IO a
handleBookmarkFileError :: forall a. (BookmarkFileError -> Text -> IO a) -> IO a -> IO a
handleBookmarkFileError = (BookmarkFileError -> Text -> IO a) -> IO a -> IO a
forall err a.
GErrorClass err =>
(err -> Text -> IO a) -> IO a -> IO a
handleGErrorJustDomain