{- | Copyright : Will Thompson, Iñaki García Etxebarria and Jonas Platte License : LGPL-2.1 Maintainer : Iñaki García Etxebarria (garetxe@gmail.com) -} #define ENABLE_OVERLOADING (MIN_VERSION_haskell_gi_overloading(1,0,0) \ && !defined(__HADDOCK_VERSION__)) 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.ManagedPtr as B.ManagedPtr 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.Text as T import qualified Data.ByteString.Char8 as B import qualified Data.Map as Map import qualified Foreign.Ptr as FP -- 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 (Show, Eq) instance P.Enum TraverseFlags where fromEnum TraverseFlagsLeaves = 1 fromEnum TraverseFlagsNonLeaves = 2 fromEnum TraverseFlagsAll = 3 fromEnum TraverseFlagsMask = 3 fromEnum TraverseFlagsLeafs = 1 fromEnum TraverseFlagsNonLeafs = 2 fromEnum (AnotherTraverseFlags k) = k toEnum 1 = TraverseFlagsLeaves toEnum 2 = TraverseFlagsNonLeaves toEnum 3 = TraverseFlagsAll toEnum 3 = TraverseFlagsMask toEnum 1 = TraverseFlagsLeafs toEnum 2 = TraverseFlagsNonLeafs toEnum k = AnotherTraverseFlags k instance P.Ord TraverseFlags where compare a b = P.compare (P.fromEnum a) (P.fromEnum b) instance IsGFlag TraverseFlags -- Flags TestTrapFlags {-# DEPRECATED TestTrapFlags ["'GI.GLib.Flags.TestTrapFlags' is used only with 'GI.GLib.Functions.testTrapFork',","which is deprecated. 'GI.GLib.Functions.testTrapSubprocess' uses","'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 (Show, Eq) instance P.Enum TestTrapFlags where fromEnum TestTrapFlagsSilenceStdout = 128 fromEnum TestTrapFlagsSilenceStderr = 256 fromEnum TestTrapFlagsInheritStdin = 512 fromEnum (AnotherTestTrapFlags k) = k toEnum 128 = TestTrapFlagsSilenceStdout toEnum 256 = TestTrapFlagsSilenceStderr toEnum 512 = TestTrapFlagsInheritStdin toEnum k = AnotherTestTrapFlags k instance P.Ord TestTrapFlags where compare a b = P.compare (P.fromEnum a) (P.fromEnum 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 (Show, Eq) instance P.Enum TestSubprocessFlags where fromEnum TestSubprocessFlagsStdin = 1 fromEnum TestSubprocessFlagsStdout = 2 fromEnum TestSubprocessFlagsStderr = 4 fromEnum (AnotherTestSubprocessFlags k) = k toEnum 1 = TestSubprocessFlagsStdin toEnum 2 = TestSubprocessFlagsStdout toEnum 4 = TestSubprocessFlagsStderr toEnum k = AnotherTestSubprocessFlags k instance P.Ord TestSubprocessFlags where compare a b = P.compare (P.fromEnum a) (P.fromEnum 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 (Show, Eq) instance P.Enum SpawnFlags where fromEnum SpawnFlagsDefault = 0 fromEnum SpawnFlagsLeaveDescriptorsOpen = 1 fromEnum SpawnFlagsDoNotReapChild = 2 fromEnum SpawnFlagsSearchPath = 4 fromEnum SpawnFlagsStdoutToDevNull = 8 fromEnum SpawnFlagsStderrToDevNull = 16 fromEnum SpawnFlagsChildInheritsStdin = 32 fromEnum SpawnFlagsFileAndArgvZero = 64 fromEnum SpawnFlagsSearchPathFromEnvp = 128 fromEnum SpawnFlagsCloexecPipes = 256 fromEnum (AnotherSpawnFlags k) = k toEnum 0 = SpawnFlagsDefault toEnum 1 = SpawnFlagsLeaveDescriptorsOpen toEnum 2 = SpawnFlagsDoNotReapChild toEnum 4 = SpawnFlagsSearchPath toEnum 8 = SpawnFlagsStdoutToDevNull toEnum 16 = SpawnFlagsStderrToDevNull toEnum 32 = SpawnFlagsChildInheritsStdin toEnum 64 = SpawnFlagsFileAndArgvZero toEnum 128 = SpawnFlagsSearchPathFromEnvp toEnum 256 = SpawnFlagsCloexecPipes toEnum k = AnotherSpawnFlags k instance P.Ord SpawnFlags where compare a b = P.compare (P.fromEnum a) (P.fromEnum 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 'GI.GLib.Structs.Regex.Regex', setting the \'\\r\' character as line terminator. -} | RegexMatchFlagsNewlineLf {- ^ Overrides the newline definition set when creating a new 'GI.GLib.Structs.Regex.Regex', setting the \'\\n\' character as line terminator. -} | RegexMatchFlagsNewlineCrlf {- ^ Overrides the newline definition set when creating a new 'GI.GLib.Structs.Regex.Regex', setting the \'\\r\\n\' characters sequence as line terminator. -} | RegexMatchFlagsNewlineAny {- ^ Overrides the newline definition set when creating a new '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 '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 '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 '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 (Show, Eq) instance P.Enum RegexMatchFlags where fromEnum RegexMatchFlagsAnchored = 16 fromEnum RegexMatchFlagsNotbol = 128 fromEnum RegexMatchFlagsNoteol = 256 fromEnum RegexMatchFlagsNotempty = 1024 fromEnum RegexMatchFlagsPartial = 32768 fromEnum RegexMatchFlagsNewlineCr = 1048576 fromEnum RegexMatchFlagsNewlineLf = 2097152 fromEnum RegexMatchFlagsNewlineCrlf = 3145728 fromEnum RegexMatchFlagsNewlineAny = 4194304 fromEnum RegexMatchFlagsNewlineAnycrlf = 5242880 fromEnum RegexMatchFlagsBsrAnycrlf = 8388608 fromEnum RegexMatchFlagsBsrAny = 16777216 fromEnum RegexMatchFlagsPartialSoft = 32768 fromEnum RegexMatchFlagsPartialHard = 134217728 fromEnum RegexMatchFlagsNotemptyAtstart = 268435456 fromEnum (AnotherRegexMatchFlags k) = k toEnum 16 = RegexMatchFlagsAnchored toEnum 128 = RegexMatchFlagsNotbol toEnum 256 = RegexMatchFlagsNoteol toEnum 1024 = RegexMatchFlagsNotempty toEnum 32768 = RegexMatchFlagsPartial toEnum 1048576 = RegexMatchFlagsNewlineCr toEnum 2097152 = RegexMatchFlagsNewlineLf toEnum 3145728 = RegexMatchFlagsNewlineCrlf toEnum 4194304 = RegexMatchFlagsNewlineAny toEnum 5242880 = RegexMatchFlagsNewlineAnycrlf toEnum 8388608 = RegexMatchFlagsBsrAnycrlf toEnum 16777216 = RegexMatchFlagsBsrAny toEnum 32768 = RegexMatchFlagsPartialSoft toEnum 134217728 = RegexMatchFlagsPartialHard toEnum 268435456 = RegexMatchFlagsNotemptyAtstart toEnum k = AnotherRegexMatchFlags k instance P.Ord RegexMatchFlags where compare a b = P.compare (P.fromEnum a) (P.fromEnum 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 (Show, Eq) instance P.Enum RegexCompileFlags where fromEnum RegexCompileFlagsCaseless = 1 fromEnum RegexCompileFlagsMultiline = 2 fromEnum RegexCompileFlagsDotall = 4 fromEnum RegexCompileFlagsExtended = 8 fromEnum RegexCompileFlagsAnchored = 16 fromEnum RegexCompileFlagsDollarEndonly = 32 fromEnum RegexCompileFlagsUngreedy = 512 fromEnum RegexCompileFlagsRaw = 2048 fromEnum RegexCompileFlagsNoAutoCapture = 4096 fromEnum RegexCompileFlagsOptimize = 8192 fromEnum RegexCompileFlagsFirstline = 262144 fromEnum RegexCompileFlagsDupnames = 524288 fromEnum RegexCompileFlagsNewlineCr = 1048576 fromEnum RegexCompileFlagsNewlineLf = 2097152 fromEnum RegexCompileFlagsNewlineCrlf = 3145728 fromEnum RegexCompileFlagsNewlineAnycrlf = 5242880 fromEnum RegexCompileFlagsBsrAnycrlf = 8388608 fromEnum RegexCompileFlagsJavascriptCompat = 33554432 fromEnum (AnotherRegexCompileFlags k) = k toEnum 1 = RegexCompileFlagsCaseless toEnum 2 = RegexCompileFlagsMultiline toEnum 4 = RegexCompileFlagsDotall toEnum 8 = RegexCompileFlagsExtended toEnum 16 = RegexCompileFlagsAnchored toEnum 32 = RegexCompileFlagsDollarEndonly toEnum 512 = RegexCompileFlagsUngreedy toEnum 2048 = RegexCompileFlagsRaw toEnum 4096 = RegexCompileFlagsNoAutoCapture toEnum 8192 = RegexCompileFlagsOptimize toEnum 262144 = RegexCompileFlagsFirstline toEnum 524288 = RegexCompileFlagsDupnames toEnum 1048576 = RegexCompileFlagsNewlineCr toEnum 2097152 = RegexCompileFlagsNewlineLf toEnum 3145728 = RegexCompileFlagsNewlineCrlf toEnum 5242880 = RegexCompileFlagsNewlineAnycrlf toEnum 8388608 = RegexCompileFlagsBsrAnycrlf toEnum 33554432 = RegexCompileFlagsJavascriptCompat toEnum k = AnotherRegexCompileFlags k instance P.Ord RegexCompileFlags where compare a b = P.compare (P.fromEnum a) (P.fromEnum 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 (Show, Eq) instance P.Enum OptionFlags where fromEnum OptionFlagsNone = 0 fromEnum OptionFlagsHidden = 1 fromEnum OptionFlagsInMain = 2 fromEnum OptionFlagsReverse = 4 fromEnum OptionFlagsNoArg = 8 fromEnum OptionFlagsFilename = 16 fromEnum OptionFlagsOptionalArg = 32 fromEnum OptionFlagsNoalias = 64 fromEnum (AnotherOptionFlags k) = k toEnum 0 = OptionFlagsNone toEnum 1 = OptionFlagsHidden toEnum 2 = OptionFlagsInMain toEnum 4 = OptionFlagsReverse toEnum 8 = OptionFlagsNoArg toEnum 16 = OptionFlagsFilename toEnum 32 = OptionFlagsOptionalArg toEnum 64 = OptionFlagsNoalias toEnum k = AnotherOptionFlags k instance P.Ord OptionFlags where compare a b = P.compare (P.fromEnum a) (P.fromEnum 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 '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 (Show, Eq) instance P.Enum MarkupParseFlags where fromEnum MarkupParseFlagsDoNotUseThisUnsupportedFlag = 1 fromEnum MarkupParseFlagsTreatCdataAsText = 2 fromEnum MarkupParseFlagsPrefixErrorPosition = 4 fromEnum MarkupParseFlagsIgnoreQualified = 8 fromEnum (AnotherMarkupParseFlags k) = k toEnum 1 = MarkupParseFlagsDoNotUseThisUnsupportedFlag toEnum 2 = MarkupParseFlagsTreatCdataAsText toEnum 4 = MarkupParseFlagsPrefixErrorPosition toEnum 8 = MarkupParseFlagsIgnoreQualified toEnum k = AnotherMarkupParseFlags k instance P.Ord MarkupParseFlags where compare a b = P.compare (P.fromEnum a) (P.fromEnum 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 '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 '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 'False' nor '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 (Show, Eq) instance P.Enum MarkupCollectType where fromEnum MarkupCollectTypeInvalid = 0 fromEnum MarkupCollectTypeString = 1 fromEnum MarkupCollectTypeStrdup = 2 fromEnum MarkupCollectTypeBoolean = 3 fromEnum MarkupCollectTypeTristate = 4 fromEnum MarkupCollectTypeOptional = 65536 fromEnum (AnotherMarkupCollectType k) = k toEnum 0 = MarkupCollectTypeInvalid toEnum 1 = MarkupCollectTypeString toEnum 2 = MarkupCollectTypeStrdup toEnum 3 = MarkupCollectTypeBoolean toEnum 4 = MarkupCollectTypeTristate toEnum 65536 = MarkupCollectTypeOptional toEnum k = AnotherMarkupCollectType k instance P.Ord MarkupCollectType where compare a b = P.compare (P.fromEnum a) (P.fromEnum 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 (Show, Eq) instance P.Enum LogLevelFlags where fromEnum LogLevelFlagsFlagRecursion = 1 fromEnum LogLevelFlagsFlagFatal = 2 fromEnum LogLevelFlagsLevelError = 4 fromEnum LogLevelFlagsLevelCritical = 8 fromEnum LogLevelFlagsLevelWarning = 16 fromEnum LogLevelFlagsLevelMessage = 32 fromEnum LogLevelFlagsLevelInfo = 64 fromEnum LogLevelFlagsLevelDebug = 128 fromEnum LogLevelFlagsLevelMask = -4 fromEnum (AnotherLogLevelFlags k) = k toEnum 1 = LogLevelFlagsFlagRecursion toEnum 2 = LogLevelFlagsFlagFatal toEnum 4 = LogLevelFlagsLevelError toEnum 8 = LogLevelFlagsLevelCritical toEnum 16 = LogLevelFlagsLevelWarning toEnum 32 = LogLevelFlagsLevelMessage toEnum 64 = LogLevelFlagsLevelInfo toEnum 128 = LogLevelFlagsLevelDebug toEnum -4 = LogLevelFlagsLevelMask toEnum k = AnotherLogLevelFlags k instance P.Ord LogLevelFlags where compare a b = P.compare (P.fromEnum a) (P.fromEnum 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 (Show, Eq) instance P.Enum KeyFileFlags where fromEnum KeyFileFlagsNone = 0 fromEnum KeyFileFlagsKeepComments = 1 fromEnum KeyFileFlagsKeepTranslations = 2 fromEnum (AnotherKeyFileFlags k) = k toEnum 0 = KeyFileFlagsNone toEnum 1 = KeyFileFlagsKeepComments toEnum 2 = KeyFileFlagsKeepTranslations toEnum k = AnotherKeyFileFlags k instance P.Ord KeyFileFlags where compare a b = P.compare (P.fromEnum a) (P.fromEnum b) instance IsGFlag KeyFileFlags -- Flags IOFlags {- | Specifies properties of a '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 (Show, Eq) instance P.Enum IOFlags where fromEnum IOFlagsAppend = 1 fromEnum IOFlagsNonblock = 2 fromEnum IOFlagsIsReadable = 4 fromEnum IOFlagsIsWritable = 8 fromEnum IOFlagsIsWriteable = 8 fromEnum IOFlagsIsSeekable = 16 fromEnum IOFlagsMask = 31 fromEnum IOFlagsGetMask = 31 fromEnum IOFlagsSetMask = 3 fromEnum (AnotherIOFlags k) = k toEnum 1 = IOFlagsAppend toEnum 2 = IOFlagsNonblock toEnum 4 = IOFlagsIsReadable toEnum 8 = IOFlagsIsWritable toEnum 8 = IOFlagsIsWriteable toEnum 16 = IOFlagsIsSeekable toEnum 31 = IOFlagsMask toEnum 31 = IOFlagsGetMask toEnum 3 = IOFlagsSetMask toEnum k = AnotherIOFlags k instance P.Ord IOFlags where compare a b = P.compare (P.fromEnum a) (P.fromEnum 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 (Show, Eq) instance P.Enum IOCondition where fromEnum IOConditionIn = 1 fromEnum IOConditionOut = 4 fromEnum IOConditionPri = 2 fromEnum IOConditionErr = 8 fromEnum IOConditionHup = 16 fromEnum IOConditionNval = 32 fromEnum (AnotherIOCondition k) = k toEnum 1 = IOConditionIn toEnum 4 = IOConditionOut toEnum 2 = IOConditionPri toEnum 8 = IOConditionErr toEnum 16 = IOConditionHup toEnum 32 = IOConditionNval toEnum k = AnotherIOCondition k instance P.Ord IOCondition where compare a b = P.compare (P.fromEnum a) (P.fromEnum b) foreign import ccall "g_io_condition_get_type" c_g_io_condition_get_type :: IO GType instance BoxedFlags IOCondition where boxedFlagsType _ = c_g_io_condition_get_type instance IsGFlag IOCondition -- Flags HookFlagMask {- | Flags used internally in the '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 (Show, Eq) instance P.Enum HookFlagMask where fromEnum HookFlagMaskActive = 1 fromEnum HookFlagMaskInCall = 2 fromEnum HookFlagMaskMask = 15 fromEnum (AnotherHookFlagMask k) = k toEnum 1 = HookFlagMaskActive toEnum 2 = HookFlagMaskInCall toEnum 15 = HookFlagMaskMask toEnum k = AnotherHookFlagMask k instance P.Ord HookFlagMask where compare a b = P.compare (P.fromEnum a) (P.fromEnum 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 (Show, Eq) instance P.Enum FormatSizeFlags where fromEnum FormatSizeFlagsDefault = 0 fromEnum FormatSizeFlagsLongFormat = 1 fromEnum FormatSizeFlagsIecUnits = 2 fromEnum FormatSizeFlagsBits = 4 fromEnum (AnotherFormatSizeFlags k) = k toEnum 0 = FormatSizeFlagsDefault toEnum 1 = FormatSizeFlagsLongFormat toEnum 2 = FormatSizeFlagsIecUnits toEnum 4 = FormatSizeFlagsBits toEnum k = AnotherFormatSizeFlags k instance P.Ord FormatSizeFlags where compare a b = P.compare (P.fromEnum a) (P.fromEnum b) instance IsGFlag FormatSizeFlags -- Flags FileTest {- | A test to perform on a file using 'GI.GLib.Functions.fileTest'. -} data FileTest = FileTestIsRegular {- ^ 'True' if the file is a regular file (not a directory). Note that this test will also return 'True' if the tested file is a symlink to a regular file. -} | FileTestIsSymlink {- ^ 'True' if the file is a symlink. -} | FileTestIsDir {- ^ 'True' if the file is a directory. -} | FileTestIsExecutable {- ^ 'True' if the file is executable. -} | FileTestExists {- ^ 'True' if the file exists. It may or may not be a regular file. -} | AnotherFileTest Int -- ^ Catch-all for unknown values deriving (Show, Eq) instance P.Enum FileTest where fromEnum FileTestIsRegular = 1 fromEnum FileTestIsSymlink = 2 fromEnum FileTestIsDir = 4 fromEnum FileTestIsExecutable = 8 fromEnum FileTestExists = 16 fromEnum (AnotherFileTest k) = k toEnum 1 = FileTestIsRegular toEnum 2 = FileTestIsSymlink toEnum 4 = FileTestIsDir toEnum 8 = FileTestIsExecutable toEnum 16 = FileTestExists toEnum k = AnotherFileTest k instance P.Ord FileTest where compare a b = P.compare (P.fromEnum a) (P.fromEnum 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 (Show, Eq) instance P.Enum AsciiType where fromEnum AsciiTypeAlnum = 1 fromEnum AsciiTypeAlpha = 2 fromEnum AsciiTypeCntrl = 4 fromEnum AsciiTypeDigit = 8 fromEnum AsciiTypeGraph = 16 fromEnum AsciiTypeLower = 32 fromEnum AsciiTypePrint = 64 fromEnum AsciiTypePunct = 128 fromEnum AsciiTypeSpace = 256 fromEnum AsciiTypeUpper = 512 fromEnum AsciiTypeXdigit = 1024 fromEnum (AnotherAsciiType k) = k toEnum 1 = AsciiTypeAlnum toEnum 2 = AsciiTypeAlpha toEnum 4 = AsciiTypeCntrl toEnum 8 = AsciiTypeDigit toEnum 16 = AsciiTypeGraph toEnum 32 = AsciiTypeLower toEnum 64 = AsciiTypePrint toEnum 128 = AsciiTypePunct toEnum 256 = AsciiTypeSpace toEnum 512 = AsciiTypeUpper toEnum 1024 = AsciiTypeXdigit toEnum k = AnotherAsciiType k instance P.Ord AsciiType where compare a b = P.compare (P.fromEnum a) (P.fromEnum b) instance IsGFlag AsciiType