-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- 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.Flags
    ( 

 -- * Flags
-- ** AsciiType #flag:AsciiType#

    AsciiType(..)                           ,


-- ** FileTest #flag:FileTest#

    FileTest(..)                            ,


-- ** FormatSizeFlags #flag:FormatSizeFlags#

    FormatSizeFlags(..)                     ,


-- ** HookFlagMask #flag:HookFlagMask#

    HookFlagMask(..)                        ,


-- ** IOCondition #flag:IOCondition#

    IOCondition(..)                         ,


-- ** IOFlags #flag:IOFlags#

    IOFlags(..)                             ,


-- ** KeyFileFlags #flag:KeyFileFlags#

    KeyFileFlags(..)                        ,


-- ** LogLevelFlags #flag:LogLevelFlags#

    LogLevelFlags(..)                       ,


-- ** MarkupCollectType #flag:MarkupCollectType#

    MarkupCollectType(..)                   ,


-- ** MarkupParseFlags #flag:MarkupParseFlags#

    MarkupParseFlags(..)                    ,


-- ** OptionFlags #flag:OptionFlags#

    OptionFlags(..)                         ,


-- ** RegexCompileFlags #flag:RegexCompileFlags#

    RegexCompileFlags(..)                   ,


-- ** RegexMatchFlags #flag:RegexMatchFlags#

    RegexMatchFlags(..)                     ,


-- ** SpawnFlags #flag:SpawnFlags#

    SpawnFlags(..)                          ,


-- ** TestSubprocessFlags #flag:TestSubprocessFlags#

    TestSubprocessFlags(..)                 ,


-- ** TestTrapFlags #flag:TestTrapFlags#

    TestTrapFlags(..)                       ,


-- ** TraverseFlags #flag:TraverseFlags#

    TraverseFlags(..)                       ,




    ) 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.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL


-- Flags TraverseFlags
-- | Specifies which nodes are visited during several of the tree
-- functions, including @/g_node_traverse()/@ and @/g_node_find()/@.
data TraverseFlags = 
      TraverseFlagsLeaves
    -- ^ only leaf nodes should be visited. This name has
    --                     been introduced in 2.6, for older version use
    --                     'GI.GLib.Flags.TraverseFlagsLeafs'.
    | TraverseFlagsNonLeaves
    -- ^ only non-leaf nodes should be visited. This
    --                         name has been introduced in 2.6, for older
    --                         version use 'GI.GLib.Flags.TraverseFlagsNonLeafs'.
    | TraverseFlagsAll
    -- ^ all nodes should be visited.
    | TraverseFlagsMask
    -- ^ a mask of all traverse flags.
    | TraverseFlagsLeafs
    -- ^ identical to 'GI.GLib.Flags.TraverseFlagsLeaves'.
    | TraverseFlagsNonLeafs
    -- ^ identical to 'GI.GLib.Flags.TraverseFlagsNonLeaves'.
    | AnotherTraverseFlags Int
    -- ^ Catch-all for unknown values
    deriving (Int -> TraverseFlags -> ShowS
[TraverseFlags] -> ShowS
TraverseFlags -> String
(Int -> TraverseFlags -> ShowS)
-> (TraverseFlags -> String)
-> ([TraverseFlags] -> ShowS)
-> Show TraverseFlags
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TraverseFlags] -> ShowS
$cshowList :: [TraverseFlags] -> ShowS
show :: TraverseFlags -> String
$cshow :: TraverseFlags -> String
showsPrec :: Int -> TraverseFlags -> ShowS
$cshowsPrec :: Int -> TraverseFlags -> ShowS
Show, TraverseFlags -> TraverseFlags -> Bool
(TraverseFlags -> TraverseFlags -> Bool)
-> (TraverseFlags -> TraverseFlags -> Bool) -> Eq TraverseFlags
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TraverseFlags -> TraverseFlags -> Bool
$c/= :: TraverseFlags -> TraverseFlags -> Bool
== :: TraverseFlags -> TraverseFlags -> Bool
$c== :: TraverseFlags -> TraverseFlags -> Bool
Eq)

instance P.Enum TraverseFlags where
    fromEnum :: TraverseFlags -> Int
fromEnum TraverseFlags
TraverseFlagsLeaves = Int
1
    fromEnum TraverseFlags
TraverseFlagsNonLeaves = Int
2
    fromEnum TraverseFlags
TraverseFlagsAll = Int
3
    fromEnum TraverseFlags
TraverseFlagsMask = Int
3
    fromEnum TraverseFlags
TraverseFlagsLeafs = Int
1
    fromEnum TraverseFlags
TraverseFlagsNonLeafs = Int
2
    fromEnum (AnotherTraverseFlags Int
k) = Int
k

    toEnum :: Int -> TraverseFlags
toEnum Int
1 = TraverseFlags
TraverseFlagsLeaves
    toEnum Int
2 = TraverseFlags
TraverseFlagsNonLeaves
    toEnum Int
3 = TraverseFlags
TraverseFlagsAll
    toEnum Int
k = Int -> TraverseFlags
AnotherTraverseFlags Int
k

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

instance IsGFlag TraverseFlags

-- Flags TestTrapFlags
{-# DEPRECATED TestTrapFlags ["(Since version 2.38)","t'GI.GLib.Flags.TestTrapFlags' is used only with 'GI.GLib.Functions.testTrapFork',","which is deprecated. 'GI.GLib.Functions.testTrapSubprocess' uses","t'GI.GLib.Flags.TestSubprocessFlags'."] #-}
-- | Test traps are guards around forked tests.
-- These flags determine what traps to set.
data TestTrapFlags = 
      TestTrapFlagsSilenceStdout
    -- ^ Redirect stdout of the test child to
    --     @\/dev\/null@ so it cannot be observed on the console during test
    --     runs. The actual output is still captured though to allow later
    --     tests with @/g_test_trap_assert_stdout()/@.
    | TestTrapFlagsSilenceStderr
    -- ^ Redirect stderr of the test child to
    --     @\/dev\/null@ so it cannot be observed on the console during test
    --     runs. The actual output is still captured though to allow later
    --     tests with @/g_test_trap_assert_stderr()/@.
    | TestTrapFlagsInheritStdin
    -- ^ If this flag is given, stdin of the
    --     child process is shared with stdin of its parent process.
    --     It is redirected to @\/dev\/null@ otherwise.
    | AnotherTestTrapFlags Int
    -- ^ Catch-all for unknown values
    deriving (Int -> TestTrapFlags -> ShowS
[TestTrapFlags] -> ShowS
TestTrapFlags -> String
(Int -> TestTrapFlags -> ShowS)
-> (TestTrapFlags -> String)
-> ([TestTrapFlags] -> ShowS)
-> Show TestTrapFlags
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TestTrapFlags] -> ShowS
$cshowList :: [TestTrapFlags] -> ShowS
show :: TestTrapFlags -> String
$cshow :: TestTrapFlags -> String
showsPrec :: Int -> TestTrapFlags -> ShowS
$cshowsPrec :: Int -> TestTrapFlags -> ShowS
Show, TestTrapFlags -> TestTrapFlags -> Bool
(TestTrapFlags -> TestTrapFlags -> Bool)
-> (TestTrapFlags -> TestTrapFlags -> Bool) -> Eq TestTrapFlags
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TestTrapFlags -> TestTrapFlags -> Bool
$c/= :: TestTrapFlags -> TestTrapFlags -> Bool
== :: TestTrapFlags -> TestTrapFlags -> Bool
$c== :: TestTrapFlags -> TestTrapFlags -> Bool
Eq)

instance P.Enum TestTrapFlags where
    fromEnum :: TestTrapFlags -> Int
fromEnum TestTrapFlags
TestTrapFlagsSilenceStdout = Int
128
    fromEnum TestTrapFlags
TestTrapFlagsSilenceStderr = Int
256
    fromEnum TestTrapFlags
TestTrapFlagsInheritStdin = Int
512
    fromEnum (AnotherTestTrapFlags Int
k) = Int
k

    toEnum :: Int -> TestTrapFlags
toEnum Int
128 = TestTrapFlags
TestTrapFlagsSilenceStdout
    toEnum Int
256 = TestTrapFlags
TestTrapFlagsSilenceStderr
    toEnum Int
512 = TestTrapFlags
TestTrapFlagsInheritStdin
    toEnum Int
k = Int -> TestTrapFlags
AnotherTestTrapFlags Int
k

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

instance IsGFlag TestTrapFlags

-- Flags TestSubprocessFlags
-- | Flags to pass to 'GI.GLib.Functions.testTrapSubprocess' to control input and output.
-- 
-- Note that in contrast with 'GI.GLib.Functions.testTrapFork', the default is to
-- not show stdout and stderr.
data TestSubprocessFlags = 
      TestSubprocessFlagsStdin
    -- ^ If this flag is given, the child
    --     process will inherit the parent\'s stdin. Otherwise, the child\'s
    --     stdin is redirected to @\/dev\/null@.
    | TestSubprocessFlagsStdout
    -- ^ If this flag is given, the child
    --     process will inherit the parent\'s stdout. Otherwise, the child\'s
    --     stdout will not be visible, but it will be captured to allow
    --     later tests with @/g_test_trap_assert_stdout()/@.
    | TestSubprocessFlagsStderr
    -- ^ If this flag is given, the child
    --     process will inherit the parent\'s stderr. Otherwise, the child\'s
    --     stderr will not be visible, but it will be captured to allow
    --     later tests with @/g_test_trap_assert_stderr()/@.
    | AnotherTestSubprocessFlags Int
    -- ^ Catch-all for unknown values
    deriving (Int -> TestSubprocessFlags -> ShowS
[TestSubprocessFlags] -> ShowS
TestSubprocessFlags -> String
(Int -> TestSubprocessFlags -> ShowS)
-> (TestSubprocessFlags -> String)
-> ([TestSubprocessFlags] -> ShowS)
-> Show TestSubprocessFlags
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TestSubprocessFlags] -> ShowS
$cshowList :: [TestSubprocessFlags] -> ShowS
show :: TestSubprocessFlags -> String
$cshow :: TestSubprocessFlags -> String
showsPrec :: Int -> TestSubprocessFlags -> ShowS
$cshowsPrec :: Int -> TestSubprocessFlags -> ShowS
Show, TestSubprocessFlags -> TestSubprocessFlags -> Bool
(TestSubprocessFlags -> TestSubprocessFlags -> Bool)
-> (TestSubprocessFlags -> TestSubprocessFlags -> Bool)
-> Eq TestSubprocessFlags
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TestSubprocessFlags -> TestSubprocessFlags -> Bool
$c/= :: TestSubprocessFlags -> TestSubprocessFlags -> Bool
== :: TestSubprocessFlags -> TestSubprocessFlags -> Bool
$c== :: TestSubprocessFlags -> TestSubprocessFlags -> Bool
Eq)

instance P.Enum TestSubprocessFlags where
    fromEnum :: TestSubprocessFlags -> Int
fromEnum TestSubprocessFlags
TestSubprocessFlagsStdin = Int
1
    fromEnum TestSubprocessFlags
TestSubprocessFlagsStdout = Int
2
    fromEnum TestSubprocessFlags
TestSubprocessFlagsStderr = Int
4
    fromEnum (AnotherTestSubprocessFlags Int
k) = Int
k

    toEnum :: Int -> TestSubprocessFlags
toEnum Int
1 = TestSubprocessFlags
TestSubprocessFlagsStdin
    toEnum Int
2 = TestSubprocessFlags
TestSubprocessFlagsStdout
    toEnum Int
4 = TestSubprocessFlags
TestSubprocessFlagsStderr
    toEnum Int
k = Int -> TestSubprocessFlags
AnotherTestSubprocessFlags Int
k

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

instance IsGFlag TestSubprocessFlags

-- Flags SpawnFlags
-- | Flags passed to 'GI.GLib.Functions.spawnSync', 'GI.GLib.Functions.spawnAsync' and 'GI.GLib.Functions.spawnAsyncWithPipes'.
data SpawnFlags = 
      SpawnFlagsDefault
    -- ^ no flags, default behaviour
    | SpawnFlagsLeaveDescriptorsOpen
    -- ^ the parent\'s open file descriptors will
    --     be inherited by the child; otherwise all descriptors except stdin,
    --     stdout and stderr will be closed before calling @/exec()/@ in the child.
    | SpawnFlagsDoNotReapChild
    -- ^ the child will not be automatically reaped;
    --     you must use @/g_child_watch_add()/@ yourself (or call @/waitpid()/@ or handle
    --     @SIGCHLD@ yourself), or the child will become a zombie.
    | SpawnFlagsSearchPath
    -- ^ @argv[0]@ need not be an absolute path, it will be
    --     looked for in the user\'s @PATH@.
    | SpawnFlagsStdoutToDevNull
    -- ^ the child\'s standard output will be discarded,
    --     instead of going to the same location as the parent\'s standard output.
    | SpawnFlagsStderrToDevNull
    -- ^ the child\'s standard error will be discarded.
    | SpawnFlagsChildInheritsStdin
    -- ^ the child will inherit the parent\'s standard
    --     input (by default, the child\'s standard input is attached to @\/dev\/null@).
    | SpawnFlagsFileAndArgvZero
    -- ^ the first element of @argv@ is the file to
    --     execute, while the remaining elements are the actual argument vector
    --     to pass to the file. Normally 'GI.GLib.Functions.spawnAsyncWithPipes' uses @argv[0]@
    --     as the file to execute, and passes all of @argv@ to the child.
    | SpawnFlagsSearchPathFromEnvp
    -- ^ if @argv[0]@ is not an abolute path,
    --     it will be looked for in the @PATH@ from the passed child environment.
    --     Since: 2.34
    | SpawnFlagsCloexecPipes
    -- ^ create all pipes with the @O_CLOEXEC@ flag set.
    --     Since: 2.40
    | AnotherSpawnFlags Int
    -- ^ Catch-all for unknown values
    deriving (Int -> SpawnFlags -> ShowS
[SpawnFlags] -> ShowS
SpawnFlags -> String
(Int -> SpawnFlags -> ShowS)
-> (SpawnFlags -> String)
-> ([SpawnFlags] -> ShowS)
-> Show SpawnFlags
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SpawnFlags] -> ShowS
$cshowList :: [SpawnFlags] -> ShowS
show :: SpawnFlags -> String
$cshow :: SpawnFlags -> String
showsPrec :: Int -> SpawnFlags -> ShowS
$cshowsPrec :: Int -> SpawnFlags -> ShowS
Show, SpawnFlags -> SpawnFlags -> Bool
(SpawnFlags -> SpawnFlags -> Bool)
-> (SpawnFlags -> SpawnFlags -> Bool) -> Eq SpawnFlags
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SpawnFlags -> SpawnFlags -> Bool
$c/= :: SpawnFlags -> SpawnFlags -> Bool
== :: SpawnFlags -> SpawnFlags -> Bool
$c== :: SpawnFlags -> SpawnFlags -> Bool
Eq)

instance P.Enum SpawnFlags where
    fromEnum :: SpawnFlags -> Int
fromEnum SpawnFlags
SpawnFlagsDefault = Int
0
    fromEnum SpawnFlags
SpawnFlagsLeaveDescriptorsOpen = Int
1
    fromEnum SpawnFlags
SpawnFlagsDoNotReapChild = Int
2
    fromEnum SpawnFlags
SpawnFlagsSearchPath = Int
4
    fromEnum SpawnFlags
SpawnFlagsStdoutToDevNull = Int
8
    fromEnum SpawnFlags
SpawnFlagsStderrToDevNull = Int
16
    fromEnum SpawnFlags
SpawnFlagsChildInheritsStdin = Int
32
    fromEnum SpawnFlags
SpawnFlagsFileAndArgvZero = Int
64
    fromEnum SpawnFlags
SpawnFlagsSearchPathFromEnvp = Int
128
    fromEnum SpawnFlags
SpawnFlagsCloexecPipes = Int
256
    fromEnum (AnotherSpawnFlags Int
k) = Int
k

    toEnum :: Int -> SpawnFlags
toEnum Int
0 = SpawnFlags
SpawnFlagsDefault
    toEnum Int
1 = SpawnFlags
SpawnFlagsLeaveDescriptorsOpen
    toEnum Int
2 = SpawnFlags
SpawnFlagsDoNotReapChild
    toEnum Int
4 = SpawnFlags
SpawnFlagsSearchPath
    toEnum Int
8 = SpawnFlags
SpawnFlagsStdoutToDevNull
    toEnum Int
16 = SpawnFlags
SpawnFlagsStderrToDevNull
    toEnum Int
32 = SpawnFlags
SpawnFlagsChildInheritsStdin
    toEnum Int
64 = SpawnFlags
SpawnFlagsFileAndArgvZero
    toEnum Int
128 = SpawnFlags
SpawnFlagsSearchPathFromEnvp
    toEnum Int
256 = SpawnFlags
SpawnFlagsCloexecPipes
    toEnum Int
k = Int -> SpawnFlags
AnotherSpawnFlags Int
k

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

instance IsGFlag SpawnFlags

-- Flags RegexMatchFlags
-- | Flags specifying match-time options.
-- 
-- /Since: 2.14/
data RegexMatchFlags = 
      RegexMatchFlagsAnchored
    -- ^ The pattern is forced to be \"anchored\", that is,
    --     it is constrained to match only at the first matching point in the
    --     string that is being searched. This effect can also be achieved by
    --     appropriate constructs in the pattern itself such as the \"^\"
    --     metacharacter.
    | RegexMatchFlagsNotbol
    -- ^ Specifies that first character of the string is
    --     not the beginning of a line, so the circumflex metacharacter should
    --     not match before it. Setting this without @/G_REGEX_MULTILINE/@ (at
    --     compile time) causes circumflex never to match. This option affects
    --     only the behaviour of the circumflex metacharacter, it does not
    --     affect \"\\A\".
    | RegexMatchFlagsNoteol
    -- ^ Specifies that the end of the subject string is
    --     not the end of a line, so the dollar metacharacter should not match
    --     it nor (except in multiline mode) a newline immediately before it.
    --     Setting this without @/G_REGEX_MULTILINE/@ (at compile time) causes
    --     dollar never to match. This option affects only the behaviour of
    --     the dollar metacharacter, it does not affect \"\\Z\" or \"\\z\".
    | RegexMatchFlagsNotempty
    -- ^ An empty string is not considered to be a valid
    --     match if this option is set. If there are alternatives in the pattern,
    --     they are tried. If all the alternatives match the empty string, the
    --     entire match fails. For example, if the pattern \"a?b?\" is applied to
    --     a string not beginning with \"a\" or \"b\", it matches the empty string
    --     at the start of the string. With this flag set, this match is not
    --     valid, so GRegex searches further into the string for occurrences
    --     of \"a\" or \"b\".
    | RegexMatchFlagsPartial
    -- ^ Turns on the partial matching feature, for more
    --     documentation on partial matching see 'GI.GLib.Structs.MatchInfo.matchInfoIsPartialMatch'.
    | RegexMatchFlagsNewlineCr
    -- ^ Overrides the newline definition set when
    --     creating a new t'GI.GLib.Structs.Regex.Regex', setting the \'\\r\' character as line terminator.
    | RegexMatchFlagsNewlineLf
    -- ^ Overrides the newline definition set when
    --     creating a new t'GI.GLib.Structs.Regex.Regex', setting the \'\\n\' character as line terminator.
    | RegexMatchFlagsNewlineCrlf
    -- ^ Overrides the newline definition set when
    --     creating a new t'GI.GLib.Structs.Regex.Regex', setting the \'\\r\\n\' characters sequence as line terminator.
    | RegexMatchFlagsNewlineAny
    -- ^ Overrides the newline definition set when
    --     creating a new t'GI.GLib.Structs.Regex.Regex', any Unicode newline sequence
    --     is recognised as a newline. These are \'\\r\', \'\\n\' and \'\\rn\', and the
    --     single characters U+000B LINE TABULATION, U+000C FORM FEED (FF),
    --     U+0085 NEXT LINE (NEL), U+2028 LINE SEPARATOR and
    --     U+2029 PARAGRAPH SEPARATOR.
    | RegexMatchFlagsNewlineAnycrlf
    -- ^ Overrides the newline definition set when
    --     creating a new t'GI.GLib.Structs.Regex.Regex'; any \'\\r\', \'\\n\', or \'\\r\\n\' character sequence
    --     is recognized as a newline. Since: 2.34
    | RegexMatchFlagsBsrAnycrlf
    -- ^ Overrides the newline definition for \"\\R\" set when
    --     creating a new t'GI.GLib.Structs.Regex.Regex'; only \'\\r\', \'\\n\', or \'\\r\\n\' character sequences
    --     are recognized as a newline by \"\\R\". Since: 2.34
    | RegexMatchFlagsBsrAny
    -- ^ Overrides the newline definition for \"\\R\" set when
    --     creating a new t'GI.GLib.Structs.Regex.Regex'; any Unicode newline character or character sequence
    --     are recognized as a newline by \"\\R\". These are \'\\r\', \'\\n\' and \'\\rn\', and the
    --     single characters U+000B LINE TABULATION, U+000C FORM FEED (FF),
    --     U+0085 NEXT LINE (NEL), U+2028 LINE SEPARATOR and
    --     U+2029 PARAGRAPH SEPARATOR. Since: 2.34
    | RegexMatchFlagsPartialSoft
    -- ^ An alias for @/G_REGEX_MATCH_PARTIAL/@. Since: 2.34
    | RegexMatchFlagsPartialHard
    -- ^ Turns on the partial matching feature. In contrast to
    --     to @/G_REGEX_MATCH_PARTIAL_SOFT/@, this stops matching as soon as a partial match
    --     is found, without continuing to search for a possible complete match. See
    --     'GI.GLib.Structs.MatchInfo.matchInfoIsPartialMatch' for more information. Since: 2.34
    | RegexMatchFlagsNotemptyAtstart
    -- ^ Like @/G_REGEX_MATCH_NOTEMPTY/@, but only applied to
    --     the start of the matched string. For anchored
    --     patterns this can only happen for pattern containing \"\\K\". Since: 2.34
    | AnotherRegexMatchFlags Int
    -- ^ Catch-all for unknown values
    deriving (Int -> RegexMatchFlags -> ShowS
[RegexMatchFlags] -> ShowS
RegexMatchFlags -> String
(Int -> RegexMatchFlags -> ShowS)
-> (RegexMatchFlags -> String)
-> ([RegexMatchFlags] -> ShowS)
-> Show RegexMatchFlags
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RegexMatchFlags] -> ShowS
$cshowList :: [RegexMatchFlags] -> ShowS
show :: RegexMatchFlags -> String
$cshow :: RegexMatchFlags -> String
showsPrec :: Int -> RegexMatchFlags -> ShowS
$cshowsPrec :: Int -> RegexMatchFlags -> ShowS
Show, RegexMatchFlags -> RegexMatchFlags -> Bool
(RegexMatchFlags -> RegexMatchFlags -> Bool)
-> (RegexMatchFlags -> RegexMatchFlags -> Bool)
-> Eq RegexMatchFlags
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RegexMatchFlags -> RegexMatchFlags -> Bool
$c/= :: RegexMatchFlags -> RegexMatchFlags -> Bool
== :: RegexMatchFlags -> RegexMatchFlags -> Bool
$c== :: RegexMatchFlags -> RegexMatchFlags -> Bool
Eq)

instance P.Enum RegexMatchFlags where
    fromEnum :: RegexMatchFlags -> Int
fromEnum RegexMatchFlags
RegexMatchFlagsAnchored = Int
16
    fromEnum RegexMatchFlags
RegexMatchFlagsNotbol = Int
128
    fromEnum RegexMatchFlags
RegexMatchFlagsNoteol = Int
256
    fromEnum RegexMatchFlags
RegexMatchFlagsNotempty = Int
1024
    fromEnum RegexMatchFlags
RegexMatchFlagsPartial = Int
32768
    fromEnum RegexMatchFlags
RegexMatchFlagsNewlineCr = Int
1048576
    fromEnum RegexMatchFlags
RegexMatchFlagsNewlineLf = Int
2097152
    fromEnum RegexMatchFlags
RegexMatchFlagsNewlineCrlf = Int
3145728
    fromEnum RegexMatchFlags
RegexMatchFlagsNewlineAny = Int
4194304
    fromEnum RegexMatchFlags
RegexMatchFlagsNewlineAnycrlf = Int
5242880
    fromEnum RegexMatchFlags
RegexMatchFlagsBsrAnycrlf = Int
8388608
    fromEnum RegexMatchFlags
RegexMatchFlagsBsrAny = Int
16777216
    fromEnum RegexMatchFlags
RegexMatchFlagsPartialSoft = Int
32768
    fromEnum RegexMatchFlags
RegexMatchFlagsPartialHard = Int
134217728
    fromEnum RegexMatchFlags
RegexMatchFlagsNotemptyAtstart = Int
268435456
    fromEnum (AnotherRegexMatchFlags Int
k) = Int
k

    toEnum :: Int -> RegexMatchFlags
toEnum Int
16 = RegexMatchFlags
RegexMatchFlagsAnchored
    toEnum Int
128 = RegexMatchFlags
RegexMatchFlagsNotbol
    toEnum Int
256 = RegexMatchFlags
RegexMatchFlagsNoteol
    toEnum Int
1024 = RegexMatchFlags
RegexMatchFlagsNotempty
    toEnum Int
32768 = RegexMatchFlags
RegexMatchFlagsPartial
    toEnum Int
1048576 = RegexMatchFlags
RegexMatchFlagsNewlineCr
    toEnum Int
2097152 = RegexMatchFlags
RegexMatchFlagsNewlineLf
    toEnum Int
3145728 = RegexMatchFlags
RegexMatchFlagsNewlineCrlf
    toEnum Int
4194304 = RegexMatchFlags
RegexMatchFlagsNewlineAny
    toEnum Int
5242880 = RegexMatchFlags
RegexMatchFlagsNewlineAnycrlf
    toEnum Int
8388608 = RegexMatchFlags
RegexMatchFlagsBsrAnycrlf
    toEnum Int
16777216 = RegexMatchFlags
RegexMatchFlagsBsrAny
    toEnum Int
134217728 = RegexMatchFlags
RegexMatchFlagsPartialHard
    toEnum Int
268435456 = RegexMatchFlags
RegexMatchFlagsNotemptyAtstart
    toEnum Int
k = Int -> RegexMatchFlags
AnotherRegexMatchFlags Int
k

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

instance IsGFlag RegexMatchFlags

-- Flags RegexCompileFlags
-- | Flags specifying compile-time options.
-- 
-- /Since: 2.14/
data RegexCompileFlags = 
      RegexCompileFlagsCaseless
    -- ^ Letters in the pattern match both upper- and
    --     lowercase letters. This option can be changed within a pattern
    --     by a \"(?i)\" option setting.
    | RegexCompileFlagsMultiline
    -- ^ By default, GRegex treats the strings as consisting
    --     of a single line of characters (even if it actually contains
    --     newlines). The \"start of line\" metacharacter (\"^\") matches only
    --     at the start of the string, while the \"end of line\" metacharacter
    --     (\"$\") matches only at the end of the string, or before a terminating
    --     newline (unless @/G_REGEX_DOLLAR_ENDONLY/@ is set). When
    --     @/G_REGEX_MULTILINE/@ is set, the \"start of line\" and \"end of line\"
    --     constructs match immediately following or immediately before any
    --     newline in the string, respectively, as well as at the very start
    --     and end. This can be changed within a pattern by a \"(?m)\" option
    --     setting.
    | RegexCompileFlagsDotall
    -- ^ A dot metacharacter (\".\") in the pattern matches all
    --     characters, including newlines. Without it, newlines are excluded.
    --     This option can be changed within a pattern by a (\"?s\") option setting.
    | RegexCompileFlagsExtended
    -- ^ Whitespace data characters in the pattern are
    --     totally ignored except when escaped or inside a character class.
    --     Whitespace does not include the VT character (code 11). In addition,
    --     characters between an unescaped \"#\" outside a character class and
    --     the next newline character, inclusive, are also ignored. This can
    --     be changed within a pattern by a \"(?x)\" option setting.
    | RegexCompileFlagsAnchored
    -- ^ The pattern is forced to be \"anchored\", that is,
    --     it is constrained to match only at the first matching point in the
    --     string that is being searched. This effect can also be achieved by
    --     appropriate constructs in the pattern itself such as the \"^\"
    --     metacharacter.
    | RegexCompileFlagsDollarEndonly
    -- ^ A dollar metacharacter (\"$\") in the pattern
    --     matches only at the end of the string. Without this option, a
    --     dollar also matches immediately before the final character if
    --     it is a newline (but not before any other newlines). This option
    --     is ignored if @/G_REGEX_MULTILINE/@ is set.
    | RegexCompileFlagsUngreedy
    -- ^ Inverts the \"greediness\" of the quantifiers so that
    --     they are not greedy by default, but become greedy if followed by \"?\".
    --     It can also be set by a \"(?U)\" option setting within the pattern.
    | RegexCompileFlagsRaw
    -- ^ Usually strings must be valid UTF-8 strings, using this
    --     flag they are considered as a raw sequence of bytes.
    | RegexCompileFlagsNoAutoCapture
    -- ^ Disables the use of numbered capturing
    --     parentheses in the pattern. Any opening parenthesis that is not
    --     followed by \"?\" behaves as if it were followed by \"?:\" but named
    --     parentheses can still be used for capturing (and they acquire numbers
    --     in the usual way).
    | RegexCompileFlagsOptimize
    -- ^ Optimize the regular expression. If the pattern will
    --     be used many times, then it may be worth the effort to optimize it
    --     to improve the speed of matches.
    | RegexCompileFlagsFirstline
    -- ^ Limits an unanchored pattern to match before (or at) the
    --     first newline. Since: 2.34
    | RegexCompileFlagsDupnames
    -- ^ Names used to identify capturing subpatterns need not
    --     be unique. This can be helpful for certain types of pattern when it
    --     is known that only one instance of the named subpattern can ever be
    --     matched.
    | RegexCompileFlagsNewlineCr
    -- ^ Usually any newline character or character sequence is
    --     recognized. If this option is set, the only recognized newline character
    --     is \'\\r\'.
    | RegexCompileFlagsNewlineLf
    -- ^ Usually any newline character or character sequence is
    --     recognized. If this option is set, the only recognized newline character
    --     is \'\\n\'.
    | RegexCompileFlagsNewlineCrlf
    -- ^ Usually any newline character or character sequence is
    --     recognized. If this option is set, the only recognized newline character
    --     sequence is \'\\r\\n\'.
    | RegexCompileFlagsNewlineAnycrlf
    -- ^ Usually any newline character or character sequence
    --     is recognized. If this option is set, the only recognized newline character
    --     sequences are \'\\r\', \'\\n\', and \'\\r\\n\'. Since: 2.34
    | RegexCompileFlagsBsrAnycrlf
    -- ^ Usually any newline character or character sequence
    --     is recognised. If this option is set, then \"\\R\" only recognizes the newline
    --    characters \'\\r\', \'\\n\' and \'\\r\\n\'. Since: 2.34
    | RegexCompileFlagsJavascriptCompat
    -- ^ Changes behaviour so that it is compatible with
    --     JavaScript rather than PCRE. Since: 2.34
    | AnotherRegexCompileFlags Int
    -- ^ Catch-all for unknown values
    deriving (Int -> RegexCompileFlags -> ShowS
[RegexCompileFlags] -> ShowS
RegexCompileFlags -> String
(Int -> RegexCompileFlags -> ShowS)
-> (RegexCompileFlags -> String)
-> ([RegexCompileFlags] -> ShowS)
-> Show RegexCompileFlags
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RegexCompileFlags] -> ShowS
$cshowList :: [RegexCompileFlags] -> ShowS
show :: RegexCompileFlags -> String
$cshow :: RegexCompileFlags -> String
showsPrec :: Int -> RegexCompileFlags -> ShowS
$cshowsPrec :: Int -> RegexCompileFlags -> ShowS
Show, RegexCompileFlags -> RegexCompileFlags -> Bool
(RegexCompileFlags -> RegexCompileFlags -> Bool)
-> (RegexCompileFlags -> RegexCompileFlags -> Bool)
-> Eq RegexCompileFlags
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RegexCompileFlags -> RegexCompileFlags -> Bool
$c/= :: RegexCompileFlags -> RegexCompileFlags -> Bool
== :: RegexCompileFlags -> RegexCompileFlags -> Bool
$c== :: RegexCompileFlags -> RegexCompileFlags -> Bool
Eq)

instance P.Enum RegexCompileFlags where
    fromEnum :: RegexCompileFlags -> Int
fromEnum RegexCompileFlags
RegexCompileFlagsCaseless = Int
1
    fromEnum RegexCompileFlags
RegexCompileFlagsMultiline = Int
2
    fromEnum RegexCompileFlags
RegexCompileFlagsDotall = Int
4
    fromEnum RegexCompileFlags
RegexCompileFlagsExtended = Int
8
    fromEnum RegexCompileFlags
RegexCompileFlagsAnchored = Int
16
    fromEnum RegexCompileFlags
RegexCompileFlagsDollarEndonly = Int
32
    fromEnum RegexCompileFlags
RegexCompileFlagsUngreedy = Int
512
    fromEnum RegexCompileFlags
RegexCompileFlagsRaw = Int
2048
    fromEnum RegexCompileFlags
RegexCompileFlagsNoAutoCapture = Int
4096
    fromEnum RegexCompileFlags
RegexCompileFlagsOptimize = Int
8192
    fromEnum RegexCompileFlags
RegexCompileFlagsFirstline = Int
262144
    fromEnum RegexCompileFlags
RegexCompileFlagsDupnames = Int
524288
    fromEnum RegexCompileFlags
RegexCompileFlagsNewlineCr = Int
1048576
    fromEnum RegexCompileFlags
RegexCompileFlagsNewlineLf = Int
2097152
    fromEnum RegexCompileFlags
RegexCompileFlagsNewlineCrlf = Int
3145728
    fromEnum RegexCompileFlags
RegexCompileFlagsNewlineAnycrlf = Int
5242880
    fromEnum RegexCompileFlags
RegexCompileFlagsBsrAnycrlf = Int
8388608
    fromEnum RegexCompileFlags
RegexCompileFlagsJavascriptCompat = Int
33554432
    fromEnum (AnotherRegexCompileFlags Int
k) = Int
k

    toEnum :: Int -> RegexCompileFlags
toEnum Int
1 = RegexCompileFlags
RegexCompileFlagsCaseless
    toEnum Int
2 = RegexCompileFlags
RegexCompileFlagsMultiline
    toEnum Int
4 = RegexCompileFlags
RegexCompileFlagsDotall
    toEnum Int
8 = RegexCompileFlags
RegexCompileFlagsExtended
    toEnum Int
16 = RegexCompileFlags
RegexCompileFlagsAnchored
    toEnum Int
32 = RegexCompileFlags
RegexCompileFlagsDollarEndonly
    toEnum Int
512 = RegexCompileFlags
RegexCompileFlagsUngreedy
    toEnum Int
2048 = RegexCompileFlags
RegexCompileFlagsRaw
    toEnum Int
4096 = RegexCompileFlags
RegexCompileFlagsNoAutoCapture
    toEnum Int
8192 = RegexCompileFlags
RegexCompileFlagsOptimize
    toEnum Int
262144 = RegexCompileFlags
RegexCompileFlagsFirstline
    toEnum Int
524288 = RegexCompileFlags
RegexCompileFlagsDupnames
    toEnum Int
1048576 = RegexCompileFlags
RegexCompileFlagsNewlineCr
    toEnum Int
2097152 = RegexCompileFlags
RegexCompileFlagsNewlineLf
    toEnum Int
3145728 = RegexCompileFlags
RegexCompileFlagsNewlineCrlf
    toEnum Int
5242880 = RegexCompileFlags
RegexCompileFlagsNewlineAnycrlf
    toEnum Int
8388608 = RegexCompileFlags
RegexCompileFlagsBsrAnycrlf
    toEnum Int
33554432 = RegexCompileFlags
RegexCompileFlagsJavascriptCompat
    toEnum Int
k = Int -> RegexCompileFlags
AnotherRegexCompileFlags Int
k

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

instance IsGFlag RegexCompileFlags

-- Flags OptionFlags
-- | Flags which modify individual options.
data OptionFlags = 
      OptionFlagsNone
    -- ^ No flags. Since: 2.42.
    | OptionFlagsHidden
    -- ^ The option doesn\'t appear in @--help@ output.
    | OptionFlagsInMain
    -- ^ The option appears in the main section of the
    --     @--help@ output, even if it is defined in a group.
    | OptionFlagsReverse
    -- ^ For options of the 'GI.GLib.Enums.OptionArgNone' kind, this
    --     flag indicates that the sense of the option is reversed.
    | OptionFlagsNoArg
    -- ^ For options of the 'GI.GLib.Enums.OptionArgCallback' kind,
    --     this flag indicates that the callback does not take any argument
    --     (like a 'GI.GLib.Enums.OptionArgNone' option). Since 2.8
    | OptionFlagsFilename
    -- ^ For options of the 'GI.GLib.Enums.OptionArgCallback'
    --     kind, this flag indicates that the argument should be passed to the
    --     callback in the GLib filename encoding rather than UTF-8. Since 2.8
    | OptionFlagsOptionalArg
    -- ^ For options of the 'GI.GLib.Enums.OptionArgCallback'
    --     kind, this flag indicates that the argument supply is optional.
    --     If no argument is given then data of @/GOptionParseFunc/@ will be
    --     set to NULL. Since 2.8
    | OptionFlagsNoalias
    -- ^ This flag turns off the automatic conflict
    --     resolution which prefixes long option names with @groupname-@ if
    --     there is a conflict. This option should only be used in situations
    --     where aliasing is necessary to model some legacy commandline interface.
    --     It is not safe to use this option, unless all option groups are under
    --     your direct control. Since 2.8.
    | AnotherOptionFlags Int
    -- ^ Catch-all for unknown values
    deriving (Int -> OptionFlags -> ShowS
[OptionFlags] -> ShowS
OptionFlags -> String
(Int -> OptionFlags -> ShowS)
-> (OptionFlags -> String)
-> ([OptionFlags] -> ShowS)
-> Show OptionFlags
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OptionFlags] -> ShowS
$cshowList :: [OptionFlags] -> ShowS
show :: OptionFlags -> String
$cshow :: OptionFlags -> String
showsPrec :: Int -> OptionFlags -> ShowS
$cshowsPrec :: Int -> OptionFlags -> ShowS
Show, OptionFlags -> OptionFlags -> Bool
(OptionFlags -> OptionFlags -> Bool)
-> (OptionFlags -> OptionFlags -> Bool) -> Eq OptionFlags
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OptionFlags -> OptionFlags -> Bool
$c/= :: OptionFlags -> OptionFlags -> Bool
== :: OptionFlags -> OptionFlags -> Bool
$c== :: OptionFlags -> OptionFlags -> Bool
Eq)

instance P.Enum OptionFlags where
    fromEnum :: OptionFlags -> Int
fromEnum OptionFlags
OptionFlagsNone = Int
0
    fromEnum OptionFlags
OptionFlagsHidden = Int
1
    fromEnum OptionFlags
OptionFlagsInMain = Int
2
    fromEnum OptionFlags
OptionFlagsReverse = Int
4
    fromEnum OptionFlags
OptionFlagsNoArg = Int
8
    fromEnum OptionFlags
OptionFlagsFilename = Int
16
    fromEnum OptionFlags
OptionFlagsOptionalArg = Int
32
    fromEnum OptionFlags
OptionFlagsNoalias = Int
64
    fromEnum (AnotherOptionFlags Int
k) = Int
k

    toEnum :: Int -> OptionFlags
toEnum Int
0 = OptionFlags
OptionFlagsNone
    toEnum Int
1 = OptionFlags
OptionFlagsHidden
    toEnum Int
2 = OptionFlags
OptionFlagsInMain
    toEnum Int
4 = OptionFlags
OptionFlagsReverse
    toEnum Int
8 = OptionFlags
OptionFlagsNoArg
    toEnum Int
16 = OptionFlags
OptionFlagsFilename
    toEnum Int
32 = OptionFlags
OptionFlagsOptionalArg
    toEnum Int
64 = OptionFlags
OptionFlagsNoalias
    toEnum Int
k = Int -> OptionFlags
AnotherOptionFlags Int
k

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

instance IsGFlag OptionFlags

-- Flags MarkupParseFlags
-- | Flags that affect the behaviour of the parser.
data MarkupParseFlags = 
      MarkupParseFlagsDoNotUseThisUnsupportedFlag
    -- ^ flag you should not use
    | MarkupParseFlagsTreatCdataAsText
    -- ^ When this flag is set, CDATA marked
    --     sections are not passed literally to the /@passthrough@/ function of
    --     the parser. Instead, the content of the section (without the
    --     @\<![CDATA[@ and @]]>@) is
    --     passed to the /@text@/ function. This flag was added in GLib 2.12
    | MarkupParseFlagsPrefixErrorPosition
    -- ^ Normally errors caught by GMarkup
    --     itself have line\/column information prefixed to them to let the
    --     caller know the location of the error. When this flag is set the
    --     location information is also prefixed to errors generated by the
    --     t'GI.GLib.Structs.MarkupParser.MarkupParser' implementation functions
    | MarkupParseFlagsIgnoreQualified
    -- ^ Ignore (don\'t report) qualified
    --     attributes and tags, along with their contents.  A qualified
    --     attribute or tag is one that contains \':\' in its name (ie: is in
    --     another namespace).  Since: 2.40.
    | AnotherMarkupParseFlags Int
    -- ^ Catch-all for unknown values
    deriving (Int -> MarkupParseFlags -> ShowS
[MarkupParseFlags] -> ShowS
MarkupParseFlags -> String
(Int -> MarkupParseFlags -> ShowS)
-> (MarkupParseFlags -> String)
-> ([MarkupParseFlags] -> ShowS)
-> Show MarkupParseFlags
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MarkupParseFlags] -> ShowS
$cshowList :: [MarkupParseFlags] -> ShowS
show :: MarkupParseFlags -> String
$cshow :: MarkupParseFlags -> String
showsPrec :: Int -> MarkupParseFlags -> ShowS
$cshowsPrec :: Int -> MarkupParseFlags -> ShowS
Show, MarkupParseFlags -> MarkupParseFlags -> Bool
(MarkupParseFlags -> MarkupParseFlags -> Bool)
-> (MarkupParseFlags -> MarkupParseFlags -> Bool)
-> Eq MarkupParseFlags
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MarkupParseFlags -> MarkupParseFlags -> Bool
$c/= :: MarkupParseFlags -> MarkupParseFlags -> Bool
== :: MarkupParseFlags -> MarkupParseFlags -> Bool
$c== :: MarkupParseFlags -> MarkupParseFlags -> Bool
Eq)

instance P.Enum MarkupParseFlags where
    fromEnum :: MarkupParseFlags -> Int
fromEnum MarkupParseFlags
MarkupParseFlagsDoNotUseThisUnsupportedFlag = Int
1
    fromEnum MarkupParseFlags
MarkupParseFlagsTreatCdataAsText = Int
2
    fromEnum MarkupParseFlags
MarkupParseFlagsPrefixErrorPosition = Int
4
    fromEnum MarkupParseFlags
MarkupParseFlagsIgnoreQualified = Int
8
    fromEnum (AnotherMarkupParseFlags Int
k) = Int
k

    toEnum :: Int -> MarkupParseFlags
toEnum Int
1 = MarkupParseFlags
MarkupParseFlagsDoNotUseThisUnsupportedFlag
    toEnum Int
2 = MarkupParseFlags
MarkupParseFlagsTreatCdataAsText
    toEnum Int
4 = MarkupParseFlags
MarkupParseFlagsPrefixErrorPosition
    toEnum Int
8 = MarkupParseFlags
MarkupParseFlagsIgnoreQualified
    toEnum Int
k = Int -> MarkupParseFlags
AnotherMarkupParseFlags Int
k

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

instance IsGFlag MarkupParseFlags

-- Flags MarkupCollectType
-- | A mixed enumerated type and flags field. You must specify one type
-- (string, strdup, boolean, tristate).  Additionally, you may  optionally
-- bitwise OR the type with the flag 'GI.GLib.Flags.MarkupCollectTypeOptional'.
-- 
-- It is likely that this enum will be extended in the future to
-- support other types.
data MarkupCollectType = 
      MarkupCollectTypeInvalid
    -- ^ used to terminate the list of attributes
    --     to collect
    | MarkupCollectTypeString
    -- ^ collect the string pointer directly from
    --     the attribute_values[] array. Expects a parameter of type (const
    --     char **). If 'GI.GLib.Flags.MarkupCollectTypeOptional' is specified and the
    --     attribute isn\'t present then the pointer will be set to 'P.Nothing'
    | MarkupCollectTypeStrdup
    -- ^ as with 'GI.GLib.Flags.MarkupCollectTypeString', but
    --     expects a parameter of type (char **) and 'GI.GLib.Functions.strdup's the
    --     returned pointer. The pointer must be freed with 'GI.GLib.Functions.free'
    | MarkupCollectTypeBoolean
    -- ^ expects a parameter of type (gboolean *)
    --     and parses the attribute value as a boolean. Sets 'P.False' if the
    --     attribute isn\'t present. Valid boolean values consist of
    --     (case-insensitive) \"false\", \"f\", \"no\", \"n\", \"0\" and \"true\", \"t\",
    --     \"yes\", \"y\", \"1\"
    | MarkupCollectTypeTristate
    -- ^ as with 'GI.GLib.Flags.MarkupCollectTypeBoolean', but
    --     in the case of a missing attribute a value is set that compares
    --     equal to neither 'P.False' nor 'P.True' G_MARKUP_COLLECT_OPTIONAL is
    --     implied
    | MarkupCollectTypeOptional
    -- ^ can be bitwise ORed with the other fields.
    --     If present, allows the attribute not to appear. A default value
    --     is set depending on what value type is used
    | AnotherMarkupCollectType Int
    -- ^ Catch-all for unknown values
    deriving (Int -> MarkupCollectType -> ShowS
[MarkupCollectType] -> ShowS
MarkupCollectType -> String
(Int -> MarkupCollectType -> ShowS)
-> (MarkupCollectType -> String)
-> ([MarkupCollectType] -> ShowS)
-> Show MarkupCollectType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MarkupCollectType] -> ShowS
$cshowList :: [MarkupCollectType] -> ShowS
show :: MarkupCollectType -> String
$cshow :: MarkupCollectType -> String
showsPrec :: Int -> MarkupCollectType -> ShowS
$cshowsPrec :: Int -> MarkupCollectType -> ShowS
Show, MarkupCollectType -> MarkupCollectType -> Bool
(MarkupCollectType -> MarkupCollectType -> Bool)
-> (MarkupCollectType -> MarkupCollectType -> Bool)
-> Eq MarkupCollectType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MarkupCollectType -> MarkupCollectType -> Bool
$c/= :: MarkupCollectType -> MarkupCollectType -> Bool
== :: MarkupCollectType -> MarkupCollectType -> Bool
$c== :: MarkupCollectType -> MarkupCollectType -> Bool
Eq)

instance P.Enum MarkupCollectType where
    fromEnum :: MarkupCollectType -> Int
fromEnum MarkupCollectType
MarkupCollectTypeInvalid = Int
0
    fromEnum MarkupCollectType
MarkupCollectTypeString = Int
1
    fromEnum MarkupCollectType
MarkupCollectTypeStrdup = Int
2
    fromEnum MarkupCollectType
MarkupCollectTypeBoolean = Int
3
    fromEnum MarkupCollectType
MarkupCollectTypeTristate = Int
4
    fromEnum MarkupCollectType
MarkupCollectTypeOptional = Int
65536
    fromEnum (AnotherMarkupCollectType Int
k) = Int
k

    toEnum :: Int -> MarkupCollectType
toEnum Int
0 = MarkupCollectType
MarkupCollectTypeInvalid
    toEnum Int
1 = MarkupCollectType
MarkupCollectTypeString
    toEnum Int
2 = MarkupCollectType
MarkupCollectTypeStrdup
    toEnum Int
3 = MarkupCollectType
MarkupCollectTypeBoolean
    toEnum Int
4 = MarkupCollectType
MarkupCollectTypeTristate
    toEnum Int
65536 = MarkupCollectType
MarkupCollectTypeOptional
    toEnum Int
k = Int -> MarkupCollectType
AnotherMarkupCollectType Int
k

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

instance IsGFlag MarkupCollectType

-- Flags LogLevelFlags
-- | Flags specifying the level of log messages.
-- 
-- It is possible to change how GLib treats messages of the various
-- levels using @/g_log_set_handler()/@ and 'GI.GLib.Functions.logSetFatalMask'.
data LogLevelFlags = 
      LogLevelFlagsFlagRecursion
    -- ^ internal flag
    | LogLevelFlagsFlagFatal
    -- ^ internal flag
    | LogLevelFlagsLevelError
    -- ^ log level for errors, see @/g_error()/@.
    --     This level is also used for messages produced by @/g_assert()/@.
    | LogLevelFlagsLevelCritical
    -- ^ log level for critical warning messages, see
    --     @/g_critical()/@.
    --     This level is also used for messages produced by @/g_return_if_fail()/@
    --     and @/g_return_val_if_fail()/@.
    | LogLevelFlagsLevelWarning
    -- ^ log level for warnings, see @/g_warning()/@
    | LogLevelFlagsLevelMessage
    -- ^ log level for messages, see @/g_message()/@
    | LogLevelFlagsLevelInfo
    -- ^ log level for informational messages, see @/g_info()/@
    | LogLevelFlagsLevelDebug
    -- ^ log level for debug messages, see @/g_debug()/@
    | LogLevelFlagsLevelMask
    -- ^ a mask including all log levels
    | AnotherLogLevelFlags Int
    -- ^ Catch-all for unknown values
    deriving (Int -> LogLevelFlags -> ShowS
[LogLevelFlags] -> ShowS
LogLevelFlags -> String
(Int -> LogLevelFlags -> ShowS)
-> (LogLevelFlags -> String)
-> ([LogLevelFlags] -> ShowS)
-> Show LogLevelFlags
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LogLevelFlags] -> ShowS
$cshowList :: [LogLevelFlags] -> ShowS
show :: LogLevelFlags -> String
$cshow :: LogLevelFlags -> String
showsPrec :: Int -> LogLevelFlags -> ShowS
$cshowsPrec :: Int -> LogLevelFlags -> ShowS
Show, LogLevelFlags -> LogLevelFlags -> Bool
(LogLevelFlags -> LogLevelFlags -> Bool)
-> (LogLevelFlags -> LogLevelFlags -> Bool) -> Eq LogLevelFlags
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LogLevelFlags -> LogLevelFlags -> Bool
$c/= :: LogLevelFlags -> LogLevelFlags -> Bool
== :: LogLevelFlags -> LogLevelFlags -> Bool
$c== :: LogLevelFlags -> LogLevelFlags -> Bool
Eq)

instance P.Enum LogLevelFlags where
    fromEnum :: LogLevelFlags -> Int
fromEnum LogLevelFlags
LogLevelFlagsFlagRecursion = Int
1
    fromEnum LogLevelFlags
LogLevelFlagsFlagFatal = Int
2
    fromEnum LogLevelFlags
LogLevelFlagsLevelError = Int
4
    fromEnum LogLevelFlags
LogLevelFlagsLevelCritical = Int
8
    fromEnum LogLevelFlags
LogLevelFlagsLevelWarning = Int
16
    fromEnum LogLevelFlags
LogLevelFlagsLevelMessage = Int
32
    fromEnum LogLevelFlags
LogLevelFlagsLevelInfo = Int
64
    fromEnum LogLevelFlags
LogLevelFlagsLevelDebug = Int
128
    fromEnum LogLevelFlags
LogLevelFlagsLevelMask = Int
-4
    fromEnum (AnotherLogLevelFlags Int
k) = Int
k

    toEnum :: Int -> LogLevelFlags
toEnum Int
1 = LogLevelFlags
LogLevelFlagsFlagRecursion
    toEnum Int
2 = LogLevelFlags
LogLevelFlagsFlagFatal
    toEnum Int
4 = LogLevelFlags
LogLevelFlagsLevelError
    toEnum Int
8 = LogLevelFlags
LogLevelFlagsLevelCritical
    toEnum Int
16 = LogLevelFlags
LogLevelFlagsLevelWarning
    toEnum Int
32 = LogLevelFlags
LogLevelFlagsLevelMessage
    toEnum Int
64 = LogLevelFlags
LogLevelFlagsLevelInfo
    toEnum Int
128 = LogLevelFlags
LogLevelFlagsLevelDebug
    toEnum Int
-4 = LogLevelFlags
LogLevelFlagsLevelMask
    toEnum Int
k = Int -> LogLevelFlags
AnotherLogLevelFlags Int
k

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

instance IsGFlag LogLevelFlags

-- Flags KeyFileFlags
-- | Flags which influence the parsing.
data KeyFileFlags = 
      KeyFileFlagsNone
    -- ^ No flags, default behaviour
    | KeyFileFlagsKeepComments
    -- ^ Use this flag if you plan to write the
    --     (possibly modified) contents of the key file back to a file;
    --     otherwise all comments will be lost when the key file is
    --     written back.
    | KeyFileFlagsKeepTranslations
    -- ^ Use this flag if you plan to write the
    --     (possibly modified) contents of the key file back to a file;
    --     otherwise only the translations for the current language will be
    --     written back.
    | AnotherKeyFileFlags Int
    -- ^ Catch-all for unknown values
    deriving (Int -> KeyFileFlags -> ShowS
[KeyFileFlags] -> ShowS
KeyFileFlags -> String
(Int -> KeyFileFlags -> ShowS)
-> (KeyFileFlags -> String)
-> ([KeyFileFlags] -> ShowS)
-> Show KeyFileFlags
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [KeyFileFlags] -> ShowS
$cshowList :: [KeyFileFlags] -> ShowS
show :: KeyFileFlags -> String
$cshow :: KeyFileFlags -> String
showsPrec :: Int -> KeyFileFlags -> ShowS
$cshowsPrec :: Int -> KeyFileFlags -> ShowS
Show, KeyFileFlags -> KeyFileFlags -> Bool
(KeyFileFlags -> KeyFileFlags -> Bool)
-> (KeyFileFlags -> KeyFileFlags -> Bool) -> Eq KeyFileFlags
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: KeyFileFlags -> KeyFileFlags -> Bool
$c/= :: KeyFileFlags -> KeyFileFlags -> Bool
== :: KeyFileFlags -> KeyFileFlags -> Bool
$c== :: KeyFileFlags -> KeyFileFlags -> Bool
Eq)

instance P.Enum KeyFileFlags where
    fromEnum :: KeyFileFlags -> Int
fromEnum KeyFileFlags
KeyFileFlagsNone = Int
0
    fromEnum KeyFileFlags
KeyFileFlagsKeepComments = Int
1
    fromEnum KeyFileFlags
KeyFileFlagsKeepTranslations = Int
2
    fromEnum (AnotherKeyFileFlags Int
k) = Int
k

    toEnum :: Int -> KeyFileFlags
toEnum Int
0 = KeyFileFlags
KeyFileFlagsNone
    toEnum Int
1 = KeyFileFlags
KeyFileFlagsKeepComments
    toEnum Int
2 = KeyFileFlags
KeyFileFlagsKeepTranslations
    toEnum Int
k = Int -> KeyFileFlags
AnotherKeyFileFlags Int
k

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

instance IsGFlag KeyFileFlags

-- Flags IOFlags
-- | Specifies properties of a t'GI.GLib.Structs.IOChannel.IOChannel'. Some of the flags can only be
-- read with 'GI.GLib.Structs.IOChannel.iOChannelGetFlags', but not changed with
-- 'GI.GLib.Structs.IOChannel.iOChannelSetFlags'.
data IOFlags = 
      IOFlagsAppend
    -- ^ turns on append mode, corresponds to @/O_APPEND/@
    --     (see the documentation of the UNIX @/open()/@ syscall)
    | IOFlagsNonblock
    -- ^ turns on nonblocking mode, corresponds to
    --     @/O_NONBLOCK/@\/@/O_NDELAY/@ (see the documentation of the UNIX @/open()/@
    --     syscall)
    | IOFlagsIsReadable
    -- ^ indicates that the io channel is readable.
    --     This flag cannot be changed.
    | IOFlagsIsWritable
    -- ^ indicates that the io channel is writable.
    --     This flag cannot be changed.
    | IOFlagsIsWriteable
    -- ^ a misspelled version of /@gIOFLAGISWRITABLE@/
    --     that existed before the spelling was fixed in GLib 2.30. It is kept
    --     here for compatibility reasons. Deprecated since 2.30
    | IOFlagsIsSeekable
    -- ^ indicates that the io channel is seekable,
    --     i.e. that 'GI.GLib.Structs.IOChannel.iOChannelSeekPosition' can be used on it.
    --     This flag cannot be changed.
    | IOFlagsMask
    -- ^ the mask that specifies all the valid flags.
    | IOFlagsGetMask
    -- ^ the mask of the flags that are returned from
    --     'GI.GLib.Structs.IOChannel.iOChannelGetFlags'
    | IOFlagsSetMask
    -- ^ the mask of the flags that the user can modify
    --     with 'GI.GLib.Structs.IOChannel.iOChannelSetFlags'
    | AnotherIOFlags Int
    -- ^ Catch-all for unknown values
    deriving (Int -> IOFlags -> ShowS
[IOFlags] -> ShowS
IOFlags -> String
(Int -> IOFlags -> ShowS)
-> (IOFlags -> String) -> ([IOFlags] -> ShowS) -> Show IOFlags
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [IOFlags] -> ShowS
$cshowList :: [IOFlags] -> ShowS
show :: IOFlags -> String
$cshow :: IOFlags -> String
showsPrec :: Int -> IOFlags -> ShowS
$cshowsPrec :: Int -> IOFlags -> ShowS
Show, IOFlags -> IOFlags -> Bool
(IOFlags -> IOFlags -> Bool)
-> (IOFlags -> IOFlags -> Bool) -> Eq IOFlags
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IOFlags -> IOFlags -> Bool
$c/= :: IOFlags -> IOFlags -> Bool
== :: IOFlags -> IOFlags -> Bool
$c== :: IOFlags -> IOFlags -> Bool
Eq)

instance P.Enum IOFlags where
    fromEnum :: IOFlags -> Int
fromEnum IOFlags
IOFlagsAppend = Int
1
    fromEnum IOFlags
IOFlagsNonblock = Int
2
    fromEnum IOFlags
IOFlagsIsReadable = Int
4
    fromEnum IOFlags
IOFlagsIsWritable = Int
8
    fromEnum IOFlags
IOFlagsIsWriteable = Int
8
    fromEnum IOFlags
IOFlagsIsSeekable = Int
16
    fromEnum IOFlags
IOFlagsMask = Int
31
    fromEnum IOFlags
IOFlagsGetMask = Int
31
    fromEnum IOFlags
IOFlagsSetMask = Int
3
    fromEnum (AnotherIOFlags Int
k) = Int
k

    toEnum :: Int -> IOFlags
toEnum Int
1 = IOFlags
IOFlagsAppend
    toEnum Int
2 = IOFlags
IOFlagsNonblock
    toEnum Int
4 = IOFlags
IOFlagsIsReadable
    toEnum Int
8 = IOFlags
IOFlagsIsWritable
    toEnum Int
16 = IOFlags
IOFlagsIsSeekable
    toEnum Int
31 = IOFlags
IOFlagsMask
    toEnum Int
3 = IOFlags
IOFlagsSetMask
    toEnum Int
k = Int -> IOFlags
AnotherIOFlags Int
k

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

instance IsGFlag IOFlags

-- Flags IOCondition
-- | A bitwise combination representing a condition to watch for on an
-- event source.
data IOCondition = 
      IOConditionIn
    -- ^ There is data to read.
    | IOConditionOut
    -- ^ Data can be written (without blocking).
    | IOConditionPri
    -- ^ There is urgent data to read.
    | IOConditionErr
    -- ^ Error condition.
    | IOConditionHup
    -- ^ Hung up (the connection has been broken, usually for
    --            pipes and sockets).
    | IOConditionNval
    -- ^ Invalid request. The file descriptor is not open.
    | AnotherIOCondition Int
    -- ^ Catch-all for unknown values
    deriving (Int -> IOCondition -> ShowS
[IOCondition] -> ShowS
IOCondition -> String
(Int -> IOCondition -> ShowS)
-> (IOCondition -> String)
-> ([IOCondition] -> ShowS)
-> Show IOCondition
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [IOCondition] -> ShowS
$cshowList :: [IOCondition] -> ShowS
show :: IOCondition -> String
$cshow :: IOCondition -> String
showsPrec :: Int -> IOCondition -> ShowS
$cshowsPrec :: Int -> IOCondition -> ShowS
Show, IOCondition -> IOCondition -> Bool
(IOCondition -> IOCondition -> Bool)
-> (IOCondition -> IOCondition -> Bool) -> Eq IOCondition
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IOCondition -> IOCondition -> Bool
$c/= :: IOCondition -> IOCondition -> Bool
== :: IOCondition -> IOCondition -> Bool
$c== :: IOCondition -> IOCondition -> Bool
Eq)

instance P.Enum IOCondition where
    fromEnum :: IOCondition -> Int
fromEnum IOCondition
IOConditionIn = Int
1
    fromEnum IOCondition
IOConditionOut = Int
4
    fromEnum IOCondition
IOConditionPri = Int
2
    fromEnum IOCondition
IOConditionErr = Int
8
    fromEnum IOCondition
IOConditionHup = Int
16
    fromEnum IOCondition
IOConditionNval = Int
32
    fromEnum (AnotherIOCondition Int
k) = Int
k

    toEnum :: Int -> IOCondition
toEnum Int
1 = IOCondition
IOConditionIn
    toEnum Int
4 = IOCondition
IOConditionOut
    toEnum Int
2 = IOCondition
IOConditionPri
    toEnum Int
8 = IOCondition
IOConditionErr
    toEnum Int
16 = IOCondition
IOConditionHup
    toEnum Int
32 = IOCondition
IOConditionNval
    toEnum Int
k = Int -> IOCondition
AnotherIOCondition Int
k

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

type instance O.ParentTypes IOCondition = '[]
instance O.HasParentTypes IOCondition

foreign import ccall "g_io_condition_get_type" c_g_io_condition_get_type :: 
    IO GType

instance B.Types.TypedObject IOCondition where
    glibType :: IO GType
glibType = IO GType
c_g_io_condition_get_type

instance B.Types.BoxedFlags IOCondition

instance IsGFlag IOCondition

-- Flags HookFlagMask
-- | Flags used internally in the t'GI.GLib.Structs.Hook.Hook' implementation.
data HookFlagMask = 
      HookFlagMaskActive
    -- ^ set if the hook has not been destroyed
    | HookFlagMaskInCall
    -- ^ set if the hook is currently being run
    | HookFlagMaskMask
    -- ^ A mask covering all bits reserved for
    --   hook flags; see 'GI.GLib.Constants.HOOK_FLAG_USER_SHIFT'
    | AnotherHookFlagMask Int
    -- ^ Catch-all for unknown values
    deriving (Int -> HookFlagMask -> ShowS
[HookFlagMask] -> ShowS
HookFlagMask -> String
(Int -> HookFlagMask -> ShowS)
-> (HookFlagMask -> String)
-> ([HookFlagMask] -> ShowS)
-> Show HookFlagMask
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [HookFlagMask] -> ShowS
$cshowList :: [HookFlagMask] -> ShowS
show :: HookFlagMask -> String
$cshow :: HookFlagMask -> String
showsPrec :: Int -> HookFlagMask -> ShowS
$cshowsPrec :: Int -> HookFlagMask -> ShowS
Show, HookFlagMask -> HookFlagMask -> Bool
(HookFlagMask -> HookFlagMask -> Bool)
-> (HookFlagMask -> HookFlagMask -> Bool) -> Eq HookFlagMask
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: HookFlagMask -> HookFlagMask -> Bool
$c/= :: HookFlagMask -> HookFlagMask -> Bool
== :: HookFlagMask -> HookFlagMask -> Bool
$c== :: HookFlagMask -> HookFlagMask -> Bool
Eq)

instance P.Enum HookFlagMask where
    fromEnum :: HookFlagMask -> Int
fromEnum HookFlagMask
HookFlagMaskActive = Int
1
    fromEnum HookFlagMask
HookFlagMaskInCall = Int
2
    fromEnum HookFlagMask
HookFlagMaskMask = Int
15
    fromEnum (AnotherHookFlagMask Int
k) = Int
k

    toEnum :: Int -> HookFlagMask
toEnum Int
1 = HookFlagMask
HookFlagMaskActive
    toEnum Int
2 = HookFlagMask
HookFlagMaskInCall
    toEnum Int
15 = HookFlagMask
HookFlagMaskMask
    toEnum Int
k = Int -> HookFlagMask
AnotherHookFlagMask Int
k

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

instance IsGFlag HookFlagMask

-- Flags FormatSizeFlags
-- | Flags to modify the format of the string returned by 'GI.GLib.Functions.formatSizeFull'.
data FormatSizeFlags = 
      FormatSizeFlagsDefault
    -- ^ behave the same as 'GI.GLib.Functions.formatSize'
    | FormatSizeFlagsLongFormat
    -- ^ include the exact number of bytes as part
    --     of the returned string.  For example, \"45.6 kB (45,612 bytes)\".
    | FormatSizeFlagsIecUnits
    -- ^ use IEC (base 1024) units with \"KiB\"-style
    --     suffixes. IEC units should only be used for reporting things with
    --     a strong \"power of 2\" basis, like RAM sizes or RAID stripe sizes.
    --     Network and storage sizes should be reported in the normal SI units.
    | FormatSizeFlagsBits
    -- ^ set the size as a quantity in bits, rather than
    --     bytes, and return units in bits. For example, ‘Mb’ rather than ‘MB’.
    | AnotherFormatSizeFlags Int
    -- ^ Catch-all for unknown values
    deriving (Int -> FormatSizeFlags -> ShowS
[FormatSizeFlags] -> ShowS
FormatSizeFlags -> String
(Int -> FormatSizeFlags -> ShowS)
-> (FormatSizeFlags -> String)
-> ([FormatSizeFlags] -> ShowS)
-> Show FormatSizeFlags
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FormatSizeFlags] -> ShowS
$cshowList :: [FormatSizeFlags] -> ShowS
show :: FormatSizeFlags -> String
$cshow :: FormatSizeFlags -> String
showsPrec :: Int -> FormatSizeFlags -> ShowS
$cshowsPrec :: Int -> FormatSizeFlags -> ShowS
Show, FormatSizeFlags -> FormatSizeFlags -> Bool
(FormatSizeFlags -> FormatSizeFlags -> Bool)
-> (FormatSizeFlags -> FormatSizeFlags -> Bool)
-> Eq FormatSizeFlags
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FormatSizeFlags -> FormatSizeFlags -> Bool
$c/= :: FormatSizeFlags -> FormatSizeFlags -> Bool
== :: FormatSizeFlags -> FormatSizeFlags -> Bool
$c== :: FormatSizeFlags -> FormatSizeFlags -> Bool
Eq)

instance P.Enum FormatSizeFlags where
    fromEnum :: FormatSizeFlags -> Int
fromEnum FormatSizeFlags
FormatSizeFlagsDefault = Int
0
    fromEnum FormatSizeFlags
FormatSizeFlagsLongFormat = Int
1
    fromEnum FormatSizeFlags
FormatSizeFlagsIecUnits = Int
2
    fromEnum FormatSizeFlags
FormatSizeFlagsBits = Int
4
    fromEnum (AnotherFormatSizeFlags Int
k) = Int
k

    toEnum :: Int -> FormatSizeFlags
toEnum Int
0 = FormatSizeFlags
FormatSizeFlagsDefault
    toEnum Int
1 = FormatSizeFlags
FormatSizeFlagsLongFormat
    toEnum Int
2 = FormatSizeFlags
FormatSizeFlagsIecUnits
    toEnum Int
4 = FormatSizeFlags
FormatSizeFlagsBits
    toEnum Int
k = Int -> FormatSizeFlags
AnotherFormatSizeFlags Int
k

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

instance IsGFlag FormatSizeFlags

-- Flags FileTest
-- | A test to perform on a file using 'GI.GLib.Functions.fileTest'.
data FileTest = 
      FileTestIsRegular
    -- ^ 'P.True' if the file is a regular file
    --     (not a directory). Note that this test will also return 'P.True'
    --     if the tested file is a symlink to a regular file.
    | FileTestIsSymlink
    -- ^ 'P.True' if the file is a symlink.
    | FileTestIsDir
    -- ^ 'P.True' if the file is a directory.
    | FileTestIsExecutable
    -- ^ 'P.True' if the file is executable.
    | FileTestExists
    -- ^ 'P.True' if the file exists. It may or may not
    --     be a regular file.
    | AnotherFileTest Int
    -- ^ Catch-all for unknown values
    deriving (Int -> FileTest -> ShowS
[FileTest] -> ShowS
FileTest -> String
(Int -> FileTest -> ShowS)
-> (FileTest -> String) -> ([FileTest] -> ShowS) -> Show FileTest
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FileTest] -> ShowS
$cshowList :: [FileTest] -> ShowS
show :: FileTest -> String
$cshow :: FileTest -> String
showsPrec :: Int -> FileTest -> ShowS
$cshowsPrec :: Int -> FileTest -> ShowS
Show, FileTest -> FileTest -> Bool
(FileTest -> FileTest -> Bool)
-> (FileTest -> FileTest -> Bool) -> Eq FileTest
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FileTest -> FileTest -> Bool
$c/= :: FileTest -> FileTest -> Bool
== :: FileTest -> FileTest -> Bool
$c== :: FileTest -> FileTest -> Bool
Eq)

instance P.Enum FileTest where
    fromEnum :: FileTest -> Int
fromEnum FileTest
FileTestIsRegular = Int
1
    fromEnum FileTest
FileTestIsSymlink = Int
2
    fromEnum FileTest
FileTestIsDir = Int
4
    fromEnum FileTest
FileTestIsExecutable = Int
8
    fromEnum FileTest
FileTestExists = Int
16
    fromEnum (AnotherFileTest Int
k) = Int
k

    toEnum :: Int -> FileTest
toEnum Int
1 = FileTest
FileTestIsRegular
    toEnum Int
2 = FileTest
FileTestIsSymlink
    toEnum Int
4 = FileTest
FileTestIsDir
    toEnum Int
8 = FileTest
FileTestIsExecutable
    toEnum Int
16 = FileTest
FileTestExists
    toEnum Int
k = Int -> FileTest
AnotherFileTest Int
k

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

instance IsGFlag FileTest

-- Flags AsciiType
-- | /No description available in the introspection data./
data AsciiType = 
      AsciiTypeAlnum
    -- ^ /No description available in the introspection data./
    | AsciiTypeAlpha
    -- ^ /No description available in the introspection data./
    | AsciiTypeCntrl
    -- ^ /No description available in the introspection data./
    | AsciiTypeDigit
    -- ^ /No description available in the introspection data./
    | AsciiTypeGraph
    -- ^ /No description available in the introspection data./
    | AsciiTypeLower
    -- ^ /No description available in the introspection data./
    | AsciiTypePrint
    -- ^ /No description available in the introspection data./
    | AsciiTypePunct
    -- ^ /No description available in the introspection data./
    | AsciiTypeSpace
    -- ^ /No description available in the introspection data./
    | AsciiTypeUpper
    -- ^ /No description available in the introspection data./
    | AsciiTypeXdigit
    -- ^ /No description available in the introspection data./
    | AnotherAsciiType Int
    -- ^ Catch-all for unknown values
    deriving (Int -> AsciiType -> ShowS
[AsciiType] -> ShowS
AsciiType -> String
(Int -> AsciiType -> ShowS)
-> (AsciiType -> String)
-> ([AsciiType] -> ShowS)
-> Show AsciiType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AsciiType] -> ShowS
$cshowList :: [AsciiType] -> ShowS
show :: AsciiType -> String
$cshow :: AsciiType -> String
showsPrec :: Int -> AsciiType -> ShowS
$cshowsPrec :: Int -> AsciiType -> ShowS
Show, AsciiType -> AsciiType -> Bool
(AsciiType -> AsciiType -> Bool)
-> (AsciiType -> AsciiType -> Bool) -> Eq AsciiType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AsciiType -> AsciiType -> Bool
$c/= :: AsciiType -> AsciiType -> Bool
== :: AsciiType -> AsciiType -> Bool
$c== :: AsciiType -> AsciiType -> Bool
Eq)

instance P.Enum AsciiType where
    fromEnum :: AsciiType -> Int
fromEnum AsciiType
AsciiTypeAlnum = Int
1
    fromEnum AsciiType
AsciiTypeAlpha = Int
2
    fromEnum AsciiType
AsciiTypeCntrl = Int
4
    fromEnum AsciiType
AsciiTypeDigit = Int
8
    fromEnum AsciiType
AsciiTypeGraph = Int
16
    fromEnum AsciiType
AsciiTypeLower = Int
32
    fromEnum AsciiType
AsciiTypePrint = Int
64
    fromEnum AsciiType
AsciiTypePunct = Int
128
    fromEnum AsciiType
AsciiTypeSpace = Int
256
    fromEnum AsciiType
AsciiTypeUpper = Int
512
    fromEnum AsciiType
AsciiTypeXdigit = Int
1024
    fromEnum (AnotherAsciiType Int
k) = Int
k

    toEnum :: Int -> AsciiType
toEnum Int
1 = AsciiType
AsciiTypeAlnum
    toEnum Int
2 = AsciiType
AsciiTypeAlpha
    toEnum Int
4 = AsciiType
AsciiTypeCntrl
    toEnum Int
8 = AsciiType
AsciiTypeDigit
    toEnum Int
16 = AsciiType
AsciiTypeGraph
    toEnum Int
32 = AsciiType
AsciiTypeLower
    toEnum Int
64 = AsciiType
AsciiTypePrint
    toEnum Int
128 = AsciiType
AsciiTypePunct
    toEnum Int
256 = AsciiType
AsciiTypeSpace
    toEnum Int
512 = AsciiType
AsciiTypeUpper
    toEnum Int
1024 = AsciiType
AsciiTypeXdigit
    toEnum Int
k = Int -> AsciiType
AnotherAsciiType Int
k

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

instance IsGFlag AsciiType