{-# LANGUAGE PatternSynonyms, ScopedTypeVariables, ViewPatterns #-}


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

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

module GI.GLib.Constants
    ( 
    pattern WIN32_MSG_HANDLE                ,
    pattern VERSION_MIN_REQUIRED            ,
    pattern VA_COPY_AS_ARRAY                ,
    pattern USEC_PER_SEC                    ,
    pattern URI_RESERVED_CHARS_SUBCOMPONENT_DELIMITERS,
    pattern URI_RESERVED_CHARS_GENERIC_DELIMITERS,
    pattern UNICHAR_MAX_DECOMPOSITION_LENGTH,
    pattern TIME_SPAN_SECOND                ,
    pattern TIME_SPAN_MINUTE                ,
    pattern TIME_SPAN_MILLISECOND           ,
    pattern TIME_SPAN_HOUR                  ,
    pattern TIME_SPAN_DAY                   ,
    pattern TEST_OPTION_ISOLATE_DIRS        ,
    pattern SYSDEF_MSG_PEEK                 ,
    pattern SYSDEF_MSG_OOB                  ,
    pattern SYSDEF_MSG_DONTROUTE            ,
    pattern SYSDEF_AF_UNIX                  ,
    pattern SYSDEF_AF_INET6                 ,
    pattern SYSDEF_AF_INET                  ,
    pattern STR_DELIMITERS                  ,
    pattern SQRT2                           ,
    pattern SOURCE_REMOVE                   ,
    pattern SOURCE_CONTINUE                 ,
    pattern SIZEOF_VOID_P                   ,
    pattern SIZEOF_SSIZE_T                  ,
    pattern SIZEOF_SIZE_T                   ,
    pattern SIZEOF_LONG                     ,
    pattern SEARCHPATH_SEPARATOR_S          ,
    pattern SEARCHPATH_SEPARATOR            ,
    pattern REF_COUNT_INIT                  ,
    pattern PRIORITY_LOW                    ,
    pattern PRIORITY_HIGH_IDLE              ,
    pattern PRIORITY_HIGH                   ,
    pattern PRIORITY_DEFAULT_IDLE           ,
    pattern PRIORITY_DEFAULT                ,
    pattern POLLFD_FORMAT                   ,
    pattern PI_4                            ,
    pattern PI_2                            ,
    pattern PID_FORMAT                      ,
    pattern PI                              ,
    pattern PDP_ENDIAN                      ,
    pattern OPTION_REMAINING                ,
    pattern MODULE_SUFFIX                   ,
    pattern MINOR_VERSION                   ,
    pattern MININT8                         ,
    pattern MININT64                        ,
    pattern MININT32                        ,
    pattern MININT16                        ,
    pattern MICRO_VERSION                   ,
    pattern MAXUINT8                        ,
    pattern MAXUINT64                       ,
    pattern MAXUINT32                       ,
    pattern MAXUINT16                       ,
    pattern MAXINT8                         ,
    pattern MAXINT64                        ,
    pattern MAXINT32                        ,
    pattern MAXINT16                        ,
    pattern MAJOR_VERSION                   ,
    pattern LOG_LEVEL_USER_SHIFT            ,
    pattern LOG_FATAL_MASK                  ,
    pattern LOG_DOMAIN                      ,
    pattern LOG_2_BASE_10                   ,
    pattern LN2                             ,
    pattern LN10                            ,
    pattern LITTLE_ENDIAN                   ,
    pattern KEY_FILE_DESKTOP_TYPE_LINK      ,
    pattern KEY_FILE_DESKTOP_TYPE_DIRECTORY ,
    pattern KEY_FILE_DESKTOP_TYPE_APPLICATION,
    pattern KEY_FILE_DESKTOP_KEY_VERSION    ,
    pattern KEY_FILE_DESKTOP_KEY_URL        ,
    pattern KEY_FILE_DESKTOP_KEY_TYPE       ,
    pattern KEY_FILE_DESKTOP_KEY_TRY_EXEC   ,
    pattern KEY_FILE_DESKTOP_KEY_TERMINAL   ,
    pattern KEY_FILE_DESKTOP_KEY_STARTUP_WM_CLASS,
    pattern KEY_FILE_DESKTOP_KEY_STARTUP_NOTIFY,
    pattern KEY_FILE_DESKTOP_KEY_PATH       ,
    pattern KEY_FILE_DESKTOP_KEY_ONLY_SHOW_IN,
    pattern KEY_FILE_DESKTOP_KEY_NO_DISPLAY ,
    pattern KEY_FILE_DESKTOP_KEY_NOT_SHOW_IN,
    pattern KEY_FILE_DESKTOP_KEY_NAME       ,
    pattern KEY_FILE_DESKTOP_KEY_MIME_TYPE  ,
    pattern KEY_FILE_DESKTOP_KEY_ICON       ,
    pattern KEY_FILE_DESKTOP_KEY_HIDDEN     ,
    pattern KEY_FILE_DESKTOP_KEY_GENERIC_NAME,
    pattern KEY_FILE_DESKTOP_KEY_EXEC       ,
    pattern KEY_FILE_DESKTOP_KEY_DBUS_ACTIVATABLE,
    pattern KEY_FILE_DESKTOP_KEY_COMMENT    ,
    pattern KEY_FILE_DESKTOP_KEY_CATEGORIES ,
    pattern KEY_FILE_DESKTOP_KEY_ACTIONS    ,
    pattern KEY_FILE_DESKTOP_GROUP          ,
    pattern IEEE754_FLOAT_BIAS              ,
    pattern IEEE754_DOUBLE_BIAS             ,
    pattern HOOK_FLAG_USER_SHIFT            ,
    pattern HAVE_ISO_VARARGS                ,
    pattern HAVE_GROWING_STACK              ,
    pattern HAVE_GNUC_VISIBILITY            ,
    pattern HAVE_GNUC_VARARGS               ,
    pattern HAVE_GINT64                     ,
    pattern GUINTPTR_FORMAT                 ,
    pattern GUINT64_FORMAT                  ,
    pattern GUINT32_FORMAT                  ,
    pattern GUINT16_FORMAT                  ,
    pattern GSSIZE_MODIFIER                 ,
    pattern GSSIZE_FORMAT                   ,
    pattern GSIZE_MODIFIER                  ,
    pattern GSIZE_FORMAT                    ,
    pattern GNUC_PRETTY_FUNCTION            ,
    pattern GNUC_FUNCTION                   ,
    pattern GINTPTR_MODIFIER                ,
    pattern GINTPTR_FORMAT                  ,
    pattern GINT64_MODIFIER                 ,
    pattern GINT64_FORMAT                   ,
    pattern GINT32_MODIFIER                 ,
    pattern GINT32_FORMAT                   ,
    pattern GINT16_MODIFIER                 ,
    pattern GINT16_FORMAT                   ,
    pattern E                               ,
    pattern DIR_SEPARATOR_S                 ,
    pattern DIR_SEPARATOR                   ,
    pattern DATE_BAD_YEAR                   ,
    pattern DATE_BAD_JULIAN                 ,
    pattern DATE_BAD_DAY                    ,
    pattern DATALIST_FLAGS_MASK             ,
    pattern C_STD_VERSION                   ,
    pattern CSET_a_2_z                      ,
    pattern CSET_DIGITS                     ,
    pattern CSET_A_2_Z                      ,
    pattern C'macro__has_attribute___noreturn__,
    pattern BIG_ENDIAN                      ,
    pattern ATOMIC_REF_COUNT_INIT           ,
    pattern ASCII_DTOSTR_BUF_SIZE           ,
    pattern ANALYZER_ANALYZING              ,
    pattern ALLOC_ONLY                      ,
    pattern ALLOC_AND_FREE                  ,
    pattern ALLOCATOR_SLIST                 ,
    pattern ALLOCATOR_NODE                  ,
    pattern ALLOCATOR_LIST                  ,

    ) where

import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.Kind as DK
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R
import qualified Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT

-- Workaround for https://gitlab.haskell.org/ghc/ghc/-/issues/23392
#if MIN_VERSION_base(4,18,0)

#else

#endif

-- | /No description available in the introspection data./
pattern $mWIN32_MSG_HANDLE :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bWIN32_MSG_HANDLE :: Int32
WIN32_MSG_HANDLE = 19981206 :: Int32

-- | A macro that should be defined by the user prior to including
-- the glib.h header.
-- The definition should be one of the predefined GLib version
-- macros: @/GLIB_VERSION_2_26/@, @/GLIB_VERSION_2_28/@,...
-- 
-- This macro defines the earliest version of GLib that the package is
-- required to be able to compile against.
-- 
-- If the compiler is configured to warn about the use of deprecated
-- functions, then using functions that were deprecated in version
-- 'GI.GLib.Constants.VERSION_MIN_REQUIRED' or earlier will cause warnings (but
-- using functions deprecated in later releases will not).
-- 
-- /Since: 2.32/
pattern $mVERSION_MIN_REQUIRED :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bVERSION_MIN_REQUIRED :: Int32
VERSION_MIN_REQUIRED = 2 :: Int32

-- | /No description available in the introspection data./
pattern $mVA_COPY_AS_ARRAY :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bVA_COPY_AS_ARRAY :: Int32
VA_COPY_AS_ARRAY = 1 :: Int32

-- | Number of microseconds in one second (1 million).
-- This macro is provided for code readability.
pattern $mUSEC_PER_SEC :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bUSEC_PER_SEC :: Int32
USEC_PER_SEC = 1000000 :: Int32

-- | Subcomponent delimiter characters as defined in
-- <https://tools.ietf.org/html/rfc3986 RFC 3986>. Includes @!$&\'()*+,;=@.
-- 
-- /Since: 2.16/
pattern $mURI_RESERVED_CHARS_SUBCOMPONENT_DELIMITERS :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bURI_RESERVED_CHARS_SUBCOMPONENT_DELIMITERS :: Text
URI_RESERVED_CHARS_SUBCOMPONENT_DELIMITERS = "!$&'()*+,;=" :: T.Text

-- | Generic delimiters characters as defined in
-- <https://tools.ietf.org/html/rfc3986 RFC 3986>. Includes @:\/?#[]\@@.
-- 
-- /Since: 2.16/
pattern $mURI_RESERVED_CHARS_GENERIC_DELIMITERS :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bURI_RESERVED_CHARS_GENERIC_DELIMITERS :: Text
URI_RESERVED_CHARS_GENERIC_DELIMITERS = ":/?#[]@" :: T.Text

-- | The maximum length (in codepoints) of a compatibility or canonical
-- decomposition of a single Unicode character.
-- 
-- This is as defined by Unicode 6.1.
-- 
-- /Since: 2.32/
pattern $mUNICHAR_MAX_DECOMPOSITION_LENGTH :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bUNICHAR_MAX_DECOMPOSITION_LENGTH :: Int32
UNICHAR_MAX_DECOMPOSITION_LENGTH = 18 :: Int32

-- | Evaluates to a time span of one second.
-- 
-- /Since: 2.26/
pattern $mTIME_SPAN_SECOND :: forall {r}. Int64 -> ((# #) -> r) -> ((# #) -> r) -> r
$bTIME_SPAN_SECOND :: Int64
TIME_SPAN_SECOND = 1000000 :: Int64

-- | Evaluates to a time span of one minute.
-- 
-- /Since: 2.26/
pattern $mTIME_SPAN_MINUTE :: forall {r}. Int64 -> ((# #) -> r) -> ((# #) -> r) -> r
$bTIME_SPAN_MINUTE :: Int64
TIME_SPAN_MINUTE = 60000000 :: Int64

-- | Evaluates to a time span of one millisecond.
-- 
-- /Since: 2.26/
pattern $mTIME_SPAN_MILLISECOND :: forall {r}. Int64 -> ((# #) -> r) -> ((# #) -> r) -> r
$bTIME_SPAN_MILLISECOND :: Int64
TIME_SPAN_MILLISECOND = 1000 :: Int64

-- | Evaluates to a time span of one hour.
-- 
-- /Since: 2.26/
pattern $mTIME_SPAN_HOUR :: forall {r}. Int64 -> ((# #) -> r) -> ((# #) -> r) -> r
$bTIME_SPAN_HOUR :: Int64
TIME_SPAN_HOUR = 3600000000 :: Int64

-- | Evaluates to a time span of one day.
-- 
-- /Since: 2.26/
pattern $mTIME_SPAN_DAY :: forall {r}. Int64 -> ((# #) -> r) -> ((# #) -> r) -> r
$bTIME_SPAN_DAY :: Int64
TIME_SPAN_DAY = 86400000000 :: Int64

-- | Creates a unique temporary directory for each unit test and uses
-- @/g_set_user_dirs()/@ to set XDG directories to point into subdirectories of it
-- for the duration of the unit test. The directory tree is cleaned up after the
-- test finishes successfully. Note that this doesn’t take effect until
-- 'GI.GLib.Functions.testRun' is called, so calls to (for example) @/g_get_user_home_dir()/@ will
-- return the system-wide value when made in a test program’s @/main()/@ function.
-- 
-- The following functions will return subdirectories of the temporary directory
-- when this option is used. The specific subdirectory paths in use are not
-- guaranteed to be stable API — always use a getter function to retrieve them.
-- 
--  - 'GI.GLib.Functions.getHomeDir'
--  - 'GI.GLib.Functions.getUserCacheDir'
--  - 'GI.GLib.Functions.getSystemConfigDirs'
--  - 'GI.GLib.Functions.getUserConfigDir'
--  - 'GI.GLib.Functions.getSystemDataDirs'
--  - 'GI.GLib.Functions.getUserDataDir'
--  - 'GI.GLib.Functions.getUserStateDir'
--  - 'GI.GLib.Functions.getUserRuntimeDir'
-- 
-- The subdirectories may not be created by the test harness; as with normal
-- calls to functions like 'GI.GLib.Functions.getUserCacheDir', the caller must be prepared
-- to create the directory if it doesn’t exist.
-- 
-- /Since: 2.60/
pattern $mTEST_OPTION_ISOLATE_DIRS :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bTEST_OPTION_ISOLATE_DIRS :: Text
TEST_OPTION_ISOLATE_DIRS = "isolate_dirs" :: T.Text

-- | /No description available in the introspection data./
pattern $mSYSDEF_MSG_PEEK :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bSYSDEF_MSG_PEEK :: Int32
SYSDEF_MSG_PEEK = 2 :: Int32

-- | /No description available in the introspection data./
pattern $mSYSDEF_MSG_OOB :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bSYSDEF_MSG_OOB :: Int32
SYSDEF_MSG_OOB = 1 :: Int32

-- | /No description available in the introspection data./
pattern $mSYSDEF_MSG_DONTROUTE :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bSYSDEF_MSG_DONTROUTE :: Int32
SYSDEF_MSG_DONTROUTE = 4 :: Int32

-- | /No description available in the introspection data./
pattern $mSYSDEF_AF_UNIX :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bSYSDEF_AF_UNIX :: Int32
SYSDEF_AF_UNIX = 1 :: Int32

-- | /No description available in the introspection data./
pattern $mSYSDEF_AF_INET6 :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bSYSDEF_AF_INET6 :: Int32
SYSDEF_AF_INET6 = 10 :: Int32

-- | /No description available in the introspection data./
pattern $mSYSDEF_AF_INET :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bSYSDEF_AF_INET :: Int32
SYSDEF_AF_INET = 2 :: Int32

-- | The standard delimiters, used in 'GI.GLib.Functions.strdelimit'.
pattern $mSTR_DELIMITERS :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bSTR_DELIMITERS :: Text
STR_DELIMITERS = "_-|> <." :: T.Text

-- | /No description available in the introspection data./
pattern $mSQRT2 :: forall {r}. Double -> ((# #) -> r) -> ((# #) -> r) -> r
$bSQRT2 :: Double
SQRT2 = 1.414214 :: Double

-- | Use this macro as the return value of a t'GI.GLib.Callbacks.SourceFunc' to remove
-- the t'GI.GLib.Structs.Source.Source' from the main loop.
-- 
-- /Since: 2.32/
pattern $mSOURCE_REMOVE :: forall {r}. Bool -> ((# #) -> r) -> ((# #) -> r) -> r
$bSOURCE_REMOVE :: Bool
SOURCE_REMOVE = P.False :: Bool

-- | Use this macro as the return value of a t'GI.GLib.Callbacks.SourceFunc' to leave
-- the t'GI.GLib.Structs.Source.Source' in the main loop.
-- 
-- /Since: 2.32/
pattern $mSOURCE_CONTINUE :: forall {r}. Bool -> ((# #) -> r) -> ((# #) -> r) -> r
$bSOURCE_CONTINUE :: Bool
SOURCE_CONTINUE = P.True :: Bool

-- | /No description available in the introspection data./
pattern $mSIZEOF_VOID_P :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bSIZEOF_VOID_P :: Int32
SIZEOF_VOID_P = 8 :: Int32

-- | /No description available in the introspection data./
pattern $mSIZEOF_SSIZE_T :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bSIZEOF_SSIZE_T :: Int32
SIZEOF_SSIZE_T = 8 :: Int32

-- | /No description available in the introspection data./
pattern $mSIZEOF_SIZE_T :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bSIZEOF_SIZE_T :: Int32
SIZEOF_SIZE_T = 8 :: Int32

-- | /No description available in the introspection data./
pattern $mSIZEOF_LONG :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bSIZEOF_LONG :: Int32
SIZEOF_LONG = 8 :: Int32

-- | /No description available in the introspection data./
pattern $mSEARCHPATH_SEPARATOR_S :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bSEARCHPATH_SEPARATOR_S :: Text
SEARCHPATH_SEPARATOR_S = ":" :: T.Text

-- | /No description available in the introspection data./
pattern $mSEARCHPATH_SEPARATOR :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bSEARCHPATH_SEPARATOR :: Int32
SEARCHPATH_SEPARATOR = 58 :: Int32

-- | Evaluates to the initial reference count for @grefcount@.
-- 
-- This macro is useful for initializing @grefcount@ fields inside
-- structures, for instance:
-- 
-- 
-- === /C code/
-- >
-- >typedef struct {
-- >  grefcount ref_count;
-- >  char *name;
-- >  char *address;
-- >} Person;
-- >
-- >static const Person default_person = {
-- >  .ref_count = G_REF_COUNT_INIT,
-- >  .name = "Default name",
-- >  .address = "Default address",
-- >};
-- 
-- 
-- /Since: 2.78/
pattern $mREF_COUNT_INIT :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bREF_COUNT_INIT :: Int32
REF_COUNT_INIT = -1 :: Int32

-- | Use this for very low priority background tasks.
-- 
-- It is not used within GLib or GTK.
pattern $mPRIORITY_LOW :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bPRIORITY_LOW :: Int32
PRIORITY_LOW = 300 :: Int32

-- | Use this for high priority idle functions.
-- 
-- GTK uses 'GI.GLib.Constants.PRIORITY_HIGH_IDLE' + 10 for resizing operations,
-- and 'GI.GLib.Constants.PRIORITY_HIGH_IDLE' + 20 for redrawing operations. (This is
-- done to ensure that any pending resizes are processed before any
-- pending redraws, so that widgets are not redrawn twice unnecessarily.)
pattern $mPRIORITY_HIGH_IDLE :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bPRIORITY_HIGH_IDLE :: Int32
PRIORITY_HIGH_IDLE = 100 :: Int32

-- | Use this for high priority event sources.
-- 
-- It is not used within GLib or GTK.
pattern $mPRIORITY_HIGH :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bPRIORITY_HIGH :: Int32
PRIORITY_HIGH = -100 :: Int32

-- | Use this for default priority idle functions.
-- 
-- In GLib this priority is used when adding idle functions with
-- @/g_idle_add()/@.
pattern $mPRIORITY_DEFAULT_IDLE :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bPRIORITY_DEFAULT_IDLE :: Int32
PRIORITY_DEFAULT_IDLE = 200 :: Int32

-- | Use this for default priority event sources.
-- 
-- In GLib this priority is used when adding timeout functions
-- with @/g_timeout_add()/@. In GDK this priority is used for events
-- from the X server.
pattern $mPRIORITY_DEFAULT :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bPRIORITY_DEFAULT :: Int32
PRIORITY_DEFAULT = 0 :: Int32

-- | A format specifier that can be used in @/printf()/@-style format strings
-- when printing the /@fd@/ member of a t'GI.GLib.Structs.PollFD.PollFD'.
pattern $mPOLLFD_FORMAT :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bPOLLFD_FORMAT :: Text
POLLFD_FORMAT = "%d" :: T.Text

-- | /No description available in the introspection data./
pattern $mPI_4 :: forall {r}. Double -> ((# #) -> r) -> ((# #) -> r) -> r
$bPI_4 :: Double
PI_4 = 0.785398 :: Double

-- | /No description available in the introspection data./
pattern $mPI_2 :: forall {r}. Double -> ((# #) -> r) -> ((# #) -> r) -> r
$bPI_2 :: Double
PI_2 = 1.570796 :: Double

-- | A format specifier that can be used in @/printf()/@-style format strings
-- when printing a @/GPid/@.
-- 
-- /Since: 2.50/
pattern $mPID_FORMAT :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bPID_FORMAT :: Text
PID_FORMAT = "i" :: T.Text

-- | /No description available in the introspection data./
pattern $mPI :: forall {r}. Double -> ((# #) -> r) -> ((# #) -> r) -> r
$bPI :: Double
PI = 3.141593 :: Double

-- | /No description available in the introspection data./
pattern $mPDP_ENDIAN :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bPDP_ENDIAN :: Int32
PDP_ENDIAN = 3412 :: Int32

-- | If a long option in the main group has this name, it is not treated as a
-- regular option. Instead it collects all non-option arguments which would
-- otherwise be left in @argv@. The option must be of type
-- 'GI.GLib.Enums.OptionArgCallback', 'GI.GLib.Enums.OptionArgStringArray'
-- or 'GI.GLib.Enums.OptionArgFilenameArray'.
-- 
-- 
-- Using 'GI.GLib.Constants.OPTION_REMAINING' instead of simply scanning @argv@
-- for leftover arguments has the advantage that GOption takes care of
-- necessary encoding conversions for strings or filenames.
-- 
-- /Since: 2.6/
pattern $mOPTION_REMAINING :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bOPTION_REMAINING :: Text
OPTION_REMAINING = "" :: T.Text

-- | /No description available in the introspection data./
pattern $mMODULE_SUFFIX :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bMODULE_SUFFIX :: Text
MODULE_SUFFIX = "so" :: T.Text

-- | The minor version number of the GLib library.
-- 
-- Like @/gtk_minor_version/@, but from the headers used at
-- application compile time, rather than from the library
-- linked against at application run time.
pattern $mMINOR_VERSION :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bMINOR_VERSION :: Int32
MINOR_VERSION = 80 :: Int32

-- | The minimum value which can be held in a @/gint8/@.
-- 
-- /Since: 2.4/
pattern $mMININT8 :: forall {r}. Int8 -> ((# #) -> r) -> ((# #) -> r) -> r
$bMININT8 :: Int8
MININT8 = -128 :: Int8

-- | The minimum value which can be held in a @/gint64/@.
pattern $mMININT64 :: forall {r}. Int64 -> ((# #) -> r) -> ((# #) -> r) -> r
$bMININT64 :: Int64
MININT64 = -9223372036854775808 :: Int64

-- | The minimum value which can be held in a @/gint32/@.
-- 
-- /Since: 2.4/
pattern $mMININT32 :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bMININT32 :: Int32
MININT32 = -2147483648 :: Int32

-- | The minimum value which can be held in a @/gint16/@.
-- 
-- /Since: 2.4/
pattern $mMININT16 :: forall {r}. Int16 -> ((# #) -> r) -> ((# #) -> r) -> r
$bMININT16 :: Int16
MININT16 = -32768 :: Int16

-- | The micro version number of the GLib library.
-- 
-- Like @/gtk_micro_version/@, but from the headers used at
-- application compile time, rather than from the library
-- linked against at application run time.
pattern $mMICRO_VERSION :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bMICRO_VERSION :: Int32
MICRO_VERSION = 2 :: Int32

-- | /No description available in the introspection data./
pattern $mMAXUINT8 :: forall {r}. Word8 -> ((# #) -> r) -> ((# #) -> r) -> r
$bMAXUINT8 :: Word8
MAXUINT8 = 255 :: Word8

-- | /No description available in the introspection data./
pattern $mMAXUINT64 :: forall {r}. Word64 -> ((# #) -> r) -> ((# #) -> r) -> r
$bMAXUINT64 :: Word64
MAXUINT64 = 18446744073709551615 :: Word64

-- | /No description available in the introspection data./
pattern $mMAXUINT32 :: forall {r}. Word32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bMAXUINT32 :: Word32
MAXUINT32 = 4294967295 :: Word32

-- | /No description available in the introspection data./
pattern $mMAXUINT16 :: forall {r}. Word16 -> ((# #) -> r) -> ((# #) -> r) -> r
$bMAXUINT16 :: Word16
MAXUINT16 = 65535 :: Word16

-- | /No description available in the introspection data./
pattern $mMAXINT8 :: forall {r}. Int8 -> ((# #) -> r) -> ((# #) -> r) -> r
$bMAXINT8 :: Int8
MAXINT8 = 127 :: Int8

-- | /No description available in the introspection data./
pattern $mMAXINT64 :: forall {r}. Int64 -> ((# #) -> r) -> ((# #) -> r) -> r
$bMAXINT64 :: Int64
MAXINT64 = 9223372036854775807 :: Int64

-- | /No description available in the introspection data./
pattern $mMAXINT32 :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bMAXINT32 :: Int32
MAXINT32 = 2147483647 :: Int32

-- | /No description available in the introspection data./
pattern $mMAXINT16 :: forall {r}. Int16 -> ((# #) -> r) -> ((# #) -> r) -> r
$bMAXINT16 :: Int16
MAXINT16 = 32767 :: Int16

-- | The major version number of the GLib library.
-- 
-- Like @/glib_major_version/@, but from the headers used at
-- application compile time, rather than from the library
-- linked against at application run time.
pattern $mMAJOR_VERSION :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bMAJOR_VERSION :: Int32
MAJOR_VERSION = 2 :: Int32

-- | Log levels below @1\<\<G_LOG_LEVEL_USER_SHIFT@ are used by GLib.
-- Higher bits can be used for user-defined log levels.
pattern $mLOG_LEVEL_USER_SHIFT :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bLOG_LEVEL_USER_SHIFT :: Int32
LOG_LEVEL_USER_SHIFT = 8 :: Int32

-- | GLib log levels that are considered fatal by default.
-- 
-- This is not used if structured logging is enabled; see
-- <http://developer.gnome.org/glib/stable/logging.html#using-structured-logging Using Structured Logging>.
pattern $mLOG_FATAL_MASK :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bLOG_FATAL_MASK :: Int32
LOG_FATAL_MASK = 5 :: Int32

-- | Defines the log domain. See <http://developer.gnome.org/glib/stable/#log-domains Log Domains>.
-- 
-- Libraries should define this so that any messages
-- which they log can be differentiated from messages from other
-- libraries and application code. But be careful not to define
-- it in any public header files.
-- 
-- Log domains must be unique, and it is recommended that they are the
-- application or library name, optionally followed by a hyphen and a sub-domain
-- name. For example, @bloatpad@ or @bloatpad-io@.
-- 
-- If undefined, it defaults to the default 'P.Nothing' (or @\"\"@) log domain; this is
-- not advisable, as it cannot be filtered against using the @G_MESSAGES_DEBUG@
-- environment variable.
-- 
-- For example, GTK uses this in its @Makefile.am@:
-- >
-- >AM_CPPFLAGS = -DG_LOG_DOMAIN=\"Gtk\"
-- 
-- 
-- Applications can choose to leave it as the default 'P.Nothing' (or @\"\"@)
-- domain. However, defining the domain offers the same advantages as
-- above.
pattern $mLOG_DOMAIN :: forall {r}. Int8 -> ((# #) -> r) -> ((# #) -> r) -> r
$bLOG_DOMAIN :: Int8
LOG_DOMAIN = 0 :: Int8

-- | /No description available in the introspection data./
pattern $mLOG_2_BASE_10 :: forall {r}. Double -> ((# #) -> r) -> ((# #) -> r) -> r
$bLOG_2_BASE_10 :: Double
LOG_2_BASE_10 = 0.301030 :: Double

-- | /No description available in the introspection data./
pattern $mLN2 :: forall {r}. Double -> ((# #) -> r) -> ((# #) -> r) -> r
$bLN2 :: Double
LN2 = 0.693147 :: Double

-- | /No description available in the introspection data./
pattern $mLN10 :: forall {r}. Double -> ((# #) -> r) -> ((# #) -> r) -> r
$bLN10 :: Double
LN10 = 2.302585 :: Double

-- | /No description available in the introspection data./
pattern $mLITTLE_ENDIAN :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bLITTLE_ENDIAN :: Int32
LITTLE_ENDIAN = 1234 :: Int32

-- | The value of the 'GI.GLib.Constants.KEY_FILE_DESKTOP_KEY_TYPE', key for desktop
-- entries representing links to documents.
-- 
-- /Since: 2.14/
pattern $mKEY_FILE_DESKTOP_TYPE_LINK :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bKEY_FILE_DESKTOP_TYPE_LINK :: Text
KEY_FILE_DESKTOP_TYPE_LINK = "Link" :: T.Text

-- | The value of the 'GI.GLib.Constants.KEY_FILE_DESKTOP_KEY_TYPE', key for desktop
-- entries representing directories.
-- 
-- /Since: 2.14/
pattern $mKEY_FILE_DESKTOP_TYPE_DIRECTORY :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bKEY_FILE_DESKTOP_TYPE_DIRECTORY :: Text
KEY_FILE_DESKTOP_TYPE_DIRECTORY = "Directory" :: T.Text

-- | The value of the 'GI.GLib.Constants.KEY_FILE_DESKTOP_KEY_TYPE', key for desktop
-- entries representing applications.
-- 
-- /Since: 2.14/
pattern $mKEY_FILE_DESKTOP_TYPE_APPLICATION :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bKEY_FILE_DESKTOP_TYPE_APPLICATION :: Text
KEY_FILE_DESKTOP_TYPE_APPLICATION = "Application" :: T.Text

-- | A key under 'GI.GLib.Constants.KEY_FILE_DESKTOP_GROUP', whose value is a string
-- giving the version of the Desktop Entry Specification used for
-- the desktop entry file.
-- 
-- /Since: 2.14/
pattern $mKEY_FILE_DESKTOP_KEY_VERSION :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bKEY_FILE_DESKTOP_KEY_VERSION :: Text
KEY_FILE_DESKTOP_KEY_VERSION = "Version" :: T.Text

-- | A key under 'GI.GLib.Constants.KEY_FILE_DESKTOP_GROUP', whose value is a string
-- giving the URL to access. It is only valid for desktop entries
-- with the @Link@ type.
-- 
-- /Since: 2.14/
pattern $mKEY_FILE_DESKTOP_KEY_URL :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bKEY_FILE_DESKTOP_KEY_URL :: Text
KEY_FILE_DESKTOP_KEY_URL = "URL" :: T.Text

-- | A key under 'GI.GLib.Constants.KEY_FILE_DESKTOP_GROUP', whose value is a string
-- giving the type of the desktop entry.
-- 
-- Usually 'GI.GLib.Constants.KEY_FILE_DESKTOP_TYPE_APPLICATION',
-- 'GI.GLib.Constants.KEY_FILE_DESKTOP_TYPE_LINK', or
-- 'GI.GLib.Constants.KEY_FILE_DESKTOP_TYPE_DIRECTORY'.
-- 
-- /Since: 2.14/
pattern $mKEY_FILE_DESKTOP_KEY_TYPE :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bKEY_FILE_DESKTOP_KEY_TYPE :: Text
KEY_FILE_DESKTOP_KEY_TYPE = "Type" :: T.Text

-- | A key under 'GI.GLib.Constants.KEY_FILE_DESKTOP_GROUP', whose value is a string
-- giving the file name of a binary on disk used to determine if the
-- program is actually installed. It is only valid for desktop entries
-- with the @Application@ type.
-- 
-- /Since: 2.14/
pattern $mKEY_FILE_DESKTOP_KEY_TRY_EXEC :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bKEY_FILE_DESKTOP_KEY_TRY_EXEC :: Text
KEY_FILE_DESKTOP_KEY_TRY_EXEC = "TryExec" :: T.Text

-- | A key under 'GI.GLib.Constants.KEY_FILE_DESKTOP_GROUP', whose value is a boolean
-- stating whether the program should be run in a terminal window.
-- 
-- It is only valid for desktop entries with the @Application@ type.
-- 
-- /Since: 2.14/
pattern $mKEY_FILE_DESKTOP_KEY_TERMINAL :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bKEY_FILE_DESKTOP_KEY_TERMINAL :: Text
KEY_FILE_DESKTOP_KEY_TERMINAL = "Terminal" :: T.Text

-- | A key under 'GI.GLib.Constants.KEY_FILE_DESKTOP_GROUP', whose value is string
-- identifying the WM class or name hint of a window that the application
-- will create, which can be used to emulate Startup Notification with
-- older applications.
-- 
-- /Since: 2.14/
pattern $mKEY_FILE_DESKTOP_KEY_STARTUP_WM_CLASS :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bKEY_FILE_DESKTOP_KEY_STARTUP_WM_CLASS :: Text
KEY_FILE_DESKTOP_KEY_STARTUP_WM_CLASS = "StartupWMClass" :: T.Text

-- | A key under 'GI.GLib.Constants.KEY_FILE_DESKTOP_GROUP', whose value is a boolean
-- stating whether the application supports the
-- <http://www.freedesktop.org/Standards/startup-notification-spec Startup Notification Protocol Specification>.
-- 
-- /Since: 2.14/
pattern $mKEY_FILE_DESKTOP_KEY_STARTUP_NOTIFY :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bKEY_FILE_DESKTOP_KEY_STARTUP_NOTIFY :: Text
KEY_FILE_DESKTOP_KEY_STARTUP_NOTIFY = "StartupNotify" :: T.Text

-- | A key under 'GI.GLib.Constants.KEY_FILE_DESKTOP_GROUP', whose value is a string
-- containing the working directory to run the program in. It is only
-- valid for desktop entries with the @Application@ type.
-- 
-- /Since: 2.14/
pattern $mKEY_FILE_DESKTOP_KEY_PATH :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bKEY_FILE_DESKTOP_KEY_PATH :: Text
KEY_FILE_DESKTOP_KEY_PATH = "Path" :: T.Text

-- | A key under 'GI.GLib.Constants.KEY_FILE_DESKTOP_GROUP', whose value is a list of
-- strings identifying the environments that should display the
-- desktop entry.
-- 
-- /Since: 2.14/
pattern $mKEY_FILE_DESKTOP_KEY_ONLY_SHOW_IN :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bKEY_FILE_DESKTOP_KEY_ONLY_SHOW_IN :: Text
KEY_FILE_DESKTOP_KEY_ONLY_SHOW_IN = "OnlyShowIn" :: T.Text

-- | A key under 'GI.GLib.Constants.KEY_FILE_DESKTOP_GROUP', whose value is a boolean
-- stating whether the desktop entry should be shown in menus.
-- 
-- /Since: 2.14/
pattern $mKEY_FILE_DESKTOP_KEY_NO_DISPLAY :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bKEY_FILE_DESKTOP_KEY_NO_DISPLAY :: Text
KEY_FILE_DESKTOP_KEY_NO_DISPLAY = "NoDisplay" :: T.Text

-- | A key under 'GI.GLib.Constants.KEY_FILE_DESKTOP_GROUP', whose value is a list of
-- strings identifying the environments that should not display the
-- desktop entry.
-- 
-- /Since: 2.14/
pattern $mKEY_FILE_DESKTOP_KEY_NOT_SHOW_IN :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bKEY_FILE_DESKTOP_KEY_NOT_SHOW_IN :: Text
KEY_FILE_DESKTOP_KEY_NOT_SHOW_IN = "NotShowIn" :: T.Text

-- | A key under 'GI.GLib.Constants.KEY_FILE_DESKTOP_GROUP', whose value is a localized
-- string giving the specific name of the desktop entry.
-- 
-- /Since: 2.14/
pattern $mKEY_FILE_DESKTOP_KEY_NAME :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bKEY_FILE_DESKTOP_KEY_NAME :: Text
KEY_FILE_DESKTOP_KEY_NAME = "Name" :: T.Text

-- | A key under 'GI.GLib.Constants.KEY_FILE_DESKTOP_GROUP', whose value is a list
-- of strings giving the MIME types supported by this desktop entry.
-- 
-- /Since: 2.14/
pattern $mKEY_FILE_DESKTOP_KEY_MIME_TYPE :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bKEY_FILE_DESKTOP_KEY_MIME_TYPE :: Text
KEY_FILE_DESKTOP_KEY_MIME_TYPE = "MimeType" :: T.Text

-- | A key under 'GI.GLib.Constants.KEY_FILE_DESKTOP_GROUP', whose value is a localized
-- string giving the name of the icon to be displayed for the desktop
-- entry.
-- 
-- /Since: 2.14/
pattern $mKEY_FILE_DESKTOP_KEY_ICON :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bKEY_FILE_DESKTOP_KEY_ICON :: Text
KEY_FILE_DESKTOP_KEY_ICON = "Icon" :: T.Text

-- | A key under 'GI.GLib.Constants.KEY_FILE_DESKTOP_GROUP', whose value is a boolean
-- stating whether the desktop entry has been deleted by the user.
-- 
-- /Since: 2.14/
pattern $mKEY_FILE_DESKTOP_KEY_HIDDEN :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bKEY_FILE_DESKTOP_KEY_HIDDEN :: Text
KEY_FILE_DESKTOP_KEY_HIDDEN = "Hidden" :: T.Text

-- | A key under 'GI.GLib.Constants.KEY_FILE_DESKTOP_GROUP', whose value is a localized
-- string giving the generic name of the desktop entry.
-- 
-- /Since: 2.14/
pattern $mKEY_FILE_DESKTOP_KEY_GENERIC_NAME :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bKEY_FILE_DESKTOP_KEY_GENERIC_NAME :: Text
KEY_FILE_DESKTOP_KEY_GENERIC_NAME = "GenericName" :: T.Text

-- | A key under 'GI.GLib.Constants.KEY_FILE_DESKTOP_GROUP', whose value is a string
-- giving the command line to execute. It is only valid for desktop
-- entries with the @Application@ type.
-- 
-- /Since: 2.14/
pattern $mKEY_FILE_DESKTOP_KEY_EXEC :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bKEY_FILE_DESKTOP_KEY_EXEC :: Text
KEY_FILE_DESKTOP_KEY_EXEC = "Exec" :: T.Text

-- | A key under 'GI.GLib.Constants.KEY_FILE_DESKTOP_GROUP', whose value is a boolean
-- set to true if the application is D-Bus activatable.
-- 
-- /Since: 2.38/
pattern $mKEY_FILE_DESKTOP_KEY_DBUS_ACTIVATABLE :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bKEY_FILE_DESKTOP_KEY_DBUS_ACTIVATABLE :: Text
KEY_FILE_DESKTOP_KEY_DBUS_ACTIVATABLE = "DBusActivatable" :: T.Text

-- | A key under 'GI.GLib.Constants.KEY_FILE_DESKTOP_GROUP', whose value is a localized
-- string giving the tooltip for the desktop entry.
-- 
-- /Since: 2.14/
pattern $mKEY_FILE_DESKTOP_KEY_COMMENT :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bKEY_FILE_DESKTOP_KEY_COMMENT :: Text
KEY_FILE_DESKTOP_KEY_COMMENT = "Comment" :: T.Text

-- | A key under 'GI.GLib.Constants.KEY_FILE_DESKTOP_GROUP', whose value is a list
-- of strings giving the categories in which the desktop entry
-- should be shown in a menu.
-- 
-- /Since: 2.14/
pattern $mKEY_FILE_DESKTOP_KEY_CATEGORIES :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bKEY_FILE_DESKTOP_KEY_CATEGORIES :: Text
KEY_FILE_DESKTOP_KEY_CATEGORIES = "Categories" :: T.Text

-- | A key under 'GI.GLib.Constants.KEY_FILE_DESKTOP_GROUP', whose value is a string list
-- giving the available application actions.
-- 
-- /Since: 2.38/
pattern $mKEY_FILE_DESKTOP_KEY_ACTIONS :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bKEY_FILE_DESKTOP_KEY_ACTIONS :: Text
KEY_FILE_DESKTOP_KEY_ACTIONS = "Actions" :: T.Text

-- | The name of the main group of a desktop entry file, as defined in the
-- <http://freedesktop.org/Standards/desktop-entry-spec Desktop Entry Specification>.
-- Consult the specification for more
-- details about the meanings of the keys below.
-- 
-- /Since: 2.14/
pattern $mKEY_FILE_DESKTOP_GROUP :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bKEY_FILE_DESKTOP_GROUP :: Text
KEY_FILE_DESKTOP_GROUP = "Desktop Entry" :: T.Text

-- | /No description available in the introspection data./
pattern $mIEEE754_FLOAT_BIAS :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bIEEE754_FLOAT_BIAS :: Int32
IEEE754_FLOAT_BIAS = 127 :: Int32

-- | /No description available in the introspection data./
pattern $mIEEE754_DOUBLE_BIAS :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bIEEE754_DOUBLE_BIAS :: Int32
IEEE754_DOUBLE_BIAS = 1023 :: Int32

-- | The position of the first bit which is not reserved for internal
-- use be the t'GI.GLib.Structs.Hook.Hook' implementation, i.e.
-- @1 \<\< G_HOOK_FLAG_USER_SHIFT@ is the first
-- bit which can be used for application-defined flags.
pattern $mHOOK_FLAG_USER_SHIFT :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bHOOK_FLAG_USER_SHIFT :: Int32
HOOK_FLAG_USER_SHIFT = 4 :: Int32

-- | /No description available in the introspection data./
pattern $mHAVE_ISO_VARARGS :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bHAVE_ISO_VARARGS :: Int32
HAVE_ISO_VARARGS = 1 :: Int32

-- | /No description available in the introspection data./
pattern $mHAVE_GROWING_STACK :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bHAVE_GROWING_STACK :: Int32
HAVE_GROWING_STACK = 0 :: Int32

-- | /No description available in the introspection data./
pattern $mHAVE_GNUC_VISIBILITY :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bHAVE_GNUC_VISIBILITY :: Int32
HAVE_GNUC_VISIBILITY = 1 :: Int32

-- | /No description available in the introspection data./
pattern $mHAVE_GNUC_VARARGS :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bHAVE_GNUC_VARARGS :: Int32
HAVE_GNUC_VARARGS = 1 :: Int32

-- | /No description available in the introspection data./
pattern $mHAVE_GINT64 :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bHAVE_GINT64 :: Int32
HAVE_GINT64 = 1 :: Int32

-- | /No description available in the introspection data./
pattern $mGUINTPTR_FORMAT :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bGUINTPTR_FORMAT :: Text
GUINTPTR_FORMAT = "lu" :: T.Text

-- | /No description available in the introspection data./
pattern $mGUINT64_FORMAT :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bGUINT64_FORMAT :: Text
GUINT64_FORMAT = "lu" :: T.Text

-- | /No description available in the introspection data./
pattern $mGUINT32_FORMAT :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bGUINT32_FORMAT :: Text
GUINT32_FORMAT = "u" :: T.Text

-- | /No description available in the introspection data./
pattern $mGUINT16_FORMAT :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bGUINT16_FORMAT :: Text
GUINT16_FORMAT = "hu" :: T.Text

-- | /No description available in the introspection data./
pattern $mGSSIZE_MODIFIER :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bGSSIZE_MODIFIER :: Text
GSSIZE_MODIFIER = "l" :: T.Text

-- | /No description available in the introspection data./
pattern $mGSSIZE_FORMAT :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bGSSIZE_FORMAT :: Text
GSSIZE_FORMAT = "li" :: T.Text

-- | /No description available in the introspection data./
pattern $mGSIZE_MODIFIER :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bGSIZE_MODIFIER :: Text
GSIZE_MODIFIER = "l" :: T.Text

-- | /No description available in the introspection data./
pattern $mGSIZE_FORMAT :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bGSIZE_FORMAT :: Text
GSIZE_FORMAT = "lu" :: T.Text

{-# DEPRECATED GNUC_PRETTY_FUNCTION ["(Since version 2.16)","Use @/G_STRFUNC()/@ instead"] #-}
-- | Expands to \"\" on all modern compilers, and to __PRETTY_FUNCTION__
-- on gcc version 2.x. Don\'t use it.
pattern $mGNUC_PRETTY_FUNCTION :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bGNUC_PRETTY_FUNCTION :: Text
GNUC_PRETTY_FUNCTION = "" :: T.Text

{-# DEPRECATED GNUC_FUNCTION ["(Since version 2.16)","Use @/G_STRFUNC()/@ instead"] #-}
-- | Expands to \"\" on all modern compilers, and to  __FUNCTION__ on gcc
-- version 2.x. Don\'t use it.
pattern $mGNUC_FUNCTION :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bGNUC_FUNCTION :: Text
GNUC_FUNCTION = "" :: T.Text

-- | /No description available in the introspection data./
pattern $mGINTPTR_MODIFIER :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bGINTPTR_MODIFIER :: Text
GINTPTR_MODIFIER = "l" :: T.Text

-- | /No description available in the introspection data./
pattern $mGINTPTR_FORMAT :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bGINTPTR_FORMAT :: Text
GINTPTR_FORMAT = "li" :: T.Text

-- | /No description available in the introspection data./
pattern $mGINT64_MODIFIER :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bGINT64_MODIFIER :: Text
GINT64_MODIFIER = "l" :: T.Text

-- | /No description available in the introspection data./
pattern $mGINT64_FORMAT :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bGINT64_FORMAT :: Text
GINT64_FORMAT = "li" :: T.Text

-- | /No description available in the introspection data./
pattern $mGINT32_MODIFIER :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bGINT32_MODIFIER :: Text
GINT32_MODIFIER = "" :: T.Text

-- | /No description available in the introspection data./
pattern $mGINT32_FORMAT :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bGINT32_FORMAT :: Text
GINT32_FORMAT = "i" :: T.Text

-- | /No description available in the introspection data./
pattern $mGINT16_MODIFIER :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bGINT16_MODIFIER :: Text
GINT16_MODIFIER = "h" :: T.Text

-- | /No description available in the introspection data./
pattern $mGINT16_FORMAT :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bGINT16_FORMAT :: Text
GINT16_FORMAT = "hi" :: T.Text

-- | /No description available in the introspection data./
pattern $mE :: forall {r}. Double -> ((# #) -> r) -> ((# #) -> r) -> r
$bE :: Double
E = 2.718282 :: Double

-- | /No description available in the introspection data./
pattern $mDIR_SEPARATOR_S :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bDIR_SEPARATOR_S :: Text
DIR_SEPARATOR_S = "/" :: T.Text

-- | /No description available in the introspection data./
pattern $mDIR_SEPARATOR :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bDIR_SEPARATOR :: Int32
DIR_SEPARATOR = 47 :: Int32

-- | Represents an invalid year.
pattern $mDATE_BAD_YEAR :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bDATE_BAD_YEAR :: Int32
DATE_BAD_YEAR = 0 :: Int32

-- | Represents an invalid Julian day number.
pattern $mDATE_BAD_JULIAN :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bDATE_BAD_JULIAN :: Int32
DATE_BAD_JULIAN = 0 :: Int32

-- | Represents an invalid @/GDateDay/@.
pattern $mDATE_BAD_DAY :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bDATE_BAD_DAY :: Int32
DATE_BAD_DAY = 0 :: Int32

-- | A bitmask that restricts the possible flags passed to
-- 'GI.GLib.Functions.datalistSetFlags'. Passing a flags value where
-- flags & ~G_DATALIST_FLAGS_MASK != 0 is an error.
pattern $mDATALIST_FLAGS_MASK :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bDATALIST_FLAGS_MASK :: Int32
DATALIST_FLAGS_MASK = 3 :: Int32

-- | /No description available in the introspection data./
pattern $mC_STD_VERSION :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bC_STD_VERSION :: Int32
C_STD_VERSION = 199000 :: Int32

-- | The set of lowercase ASCII alphabet characters.
-- Used for specifying valid identifier characters
-- in t'GI.GLib.Structs.ScannerConfig.ScannerConfig'.
pattern $mCSET_a_2_z :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bCSET_a_2_z :: Text
CSET_a_2_z = "abcdefghijklmnopqrstuvwxyz" :: T.Text

-- | The set of ASCII digits.
-- Used for specifying valid identifier characters
-- in t'GI.GLib.Structs.ScannerConfig.ScannerConfig'.
pattern $mCSET_DIGITS :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bCSET_DIGITS :: Text
CSET_DIGITS = "0123456789" :: T.Text

-- | The set of uppercase ASCII alphabet characters.
-- Used for specifying valid identifier characters
-- in t'GI.GLib.Structs.ScannerConfig.ScannerConfig'.
pattern $mCSET_A_2_Z :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bCSET_A_2_Z :: Text
CSET_A_2_Z = "ABCDEFGHIJKLMNOPQRSTUVWXYZ" :: T.Text

-- | /No description available in the introspection data./
pattern $mC'macro__has_attribute___noreturn__ :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bC'macro__has_attribute___noreturn__ :: Int32
C'macro__has_attribute___noreturn__ = 0 :: Int32

-- | /No description available in the introspection data./
pattern $mBIG_ENDIAN :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bBIG_ENDIAN :: Int32
BIG_ENDIAN = 4321 :: Int32

-- | Evaluates to the initial reference count for @gatomicrefcount@.
-- 
-- This macro is useful for initializing @gatomicrefcount@ fields inside
-- structures, for instance:
-- 
-- 
-- === /C code/
-- >
-- >typedef struct {
-- >  gatomicrefcount ref_count;
-- >  char *name;
-- >  char *address;
-- >} Person;
-- >
-- >static const Person default_person = {
-- >  .ref_count = G_ATOMIC_REF_COUNT_INIT,
-- >  .name = "Default name",
-- >  .address = "Default address",
-- >};
-- 
-- 
-- /Since: 2.78/
pattern $mATOMIC_REF_COUNT_INIT :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bATOMIC_REF_COUNT_INIT :: Int32
ATOMIC_REF_COUNT_INIT = 1 :: Int32

-- | A good size for a buffer to be passed into 'GI.GLib.Functions.asciiDtostr'.
-- It is guaranteed to be enough for all output of that function
-- on systems with 64bit IEEE-compatible doubles.
-- 
-- The typical usage would be something like:
-- 
-- === /C code/
-- >char buf[G_ASCII_DTOSTR_BUF_SIZE];
-- >
-- >fprintf (out, "value=%s\n", g_ascii_dtostr (buf, sizeof (buf), value));
pattern $mASCII_DTOSTR_BUF_SIZE :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bASCII_DTOSTR_BUF_SIZE :: Int32
ASCII_DTOSTR_BUF_SIZE = 39 :: Int32

-- | /No description available in the introspection data./
pattern $mANALYZER_ANALYZING :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bANALYZER_ANALYZING :: Int32
ANALYZER_ANALYZING = 1 :: Int32

-- | /No description available in the introspection data./
pattern $mALLOC_ONLY :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bALLOC_ONLY :: Int32
ALLOC_ONLY = 1 :: Int32

-- | /No description available in the introspection data./
pattern $mALLOC_AND_FREE :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bALLOC_AND_FREE :: Int32
ALLOC_AND_FREE = 2 :: Int32

-- | /No description available in the introspection data./
pattern $mALLOCATOR_SLIST :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bALLOCATOR_SLIST :: Int32
ALLOCATOR_SLIST = 2 :: Int32

-- | /No description available in the introspection data./
pattern $mALLOCATOR_NODE :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bALLOCATOR_NODE :: Int32
ALLOCATOR_NODE = 3 :: Int32

-- | /No description available in the introspection data./
pattern $mALLOCATOR_LIST :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bALLOCATOR_LIST :: Int32
ALLOCATOR_LIST = 1 :: Int32