{-# 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.Vte.Constants
    ( 
    pattern TEST_FLAGS_NONE                 ,
    pattern TEST_FLAGS_ALL                  ,
    pattern TERMPROP_XTERM_TITLE            ,
    pattern TERMPROP_SHELL_PREEXEC          ,
    pattern TERMPROP_SHELL_PRECMD           ,
    pattern TERMPROP_SHELL_POSTEXEC         ,
    pattern TERMPROP_PROGRESS_VALUE         ,
    pattern TERMPROP_PROGRESS_HINT          ,
    pattern TERMPROP_NAME_PREFIX            ,
    pattern TERMPROP_ICON_IMAGE             ,
    pattern TERMPROP_ICON_COLOR             ,
    pattern TERMPROP_CURRENT_FILE_URI       ,
    pattern TERMPROP_CURRENT_DIRECTORY_URI  ,
    pattern TERMPROP_CONTAINER_UID          ,
    pattern TERMPROP_CONTAINER_RUNTIME      ,
    pattern TERMPROP_CONTAINER_NAME         ,
    pattern SPAWN_REQUIRE_SYSTEMD_SCOPE     ,
    pattern SPAWN_NO_SYSTEMD_SCOPE          ,
    pattern SPAWN_NO_PARENT_ENVV            ,
    pattern REGEX_FLAGS_DEFAULT             ,
    pattern MINOR_VERSION                   ,
    pattern MICRO_VERSION                   ,
    pattern MAJOR_VERSION                   ,

    ) 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 $mTEST_FLAGS_NONE :: forall {r}. Word64 -> ((# #) -> r) -> ((# #) -> r) -> r
$bTEST_FLAGS_NONE :: Word64
TEST_FLAGS_NONE = 0 :: Word64

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

-- | A 'GI.Vte.Enums.PropertyTypeString' termprop that stores the xterm window title
-- as set by OSC 0 and OSC 2.
-- Use this with 'GI.Vte.Objects.Terminal.terminalGetTermpropString' instead of using
-- 'GI.Vte.Objects.Terminal.terminalGetWindowTitle'.
-- 
-- Note that this termprop is not settable via the termprop OSC.
-- 
-- /Since: 0.78/
pattern $mTERMPROP_XTERM_TITLE :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bTERMPROP_XTERM_TITLE :: Text
TERMPROP_XTERM_TITLE = "xterm.title" :: T.Text

-- | A 'GI.Vte.Enums.PropertyTypeValueless' termprop that signals that the shell
-- is preparing to execute the command entered at the prompt.
-- 
-- /Since: 0.78/
pattern $mTERMPROP_SHELL_PREEXEC :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bTERMPROP_SHELL_PREEXEC :: Text
TERMPROP_SHELL_PREEXEC = "vte.shell.preexec" :: T.Text

-- | A 'GI.Vte.Enums.PropertyTypeValueless' termprop that signals that the shell
-- is going to prompt.
-- 
-- /Since: 0.78/
pattern $mTERMPROP_SHELL_PRECMD :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bTERMPROP_SHELL_PRECMD :: Text
TERMPROP_SHELL_PRECMD = "vte.shell.precmd" :: T.Text

-- | An ephemeral 'GI.Vte.Enums.PropertyTypeUint' termprop that signals that the shell
-- has executed the commands entered at the prompt and these commands
-- have returned. The termprop value is the exit code.
-- 
-- /Since: 0.78/
pattern $mTERMPROP_SHELL_POSTEXEC :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bTERMPROP_SHELL_POSTEXEC :: Text
TERMPROP_SHELL_POSTEXEC = "vte.shell.postexec" :: T.Text

-- | A 'GI.Vte.Enums.PropertyTypeUint' termprop that stores the progress of the running
-- command as a value between 0 and 100.
-- 
-- Note that this termprop cannot be set by the termprop OSC, but instead
-- only by OSC 9 ; 4 (ConEmu progress).
-- 
-- /Since: 0.80/
pattern $mTERMPROP_PROGRESS_VALUE :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bTERMPROP_PROGRESS_VALUE :: Text
TERMPROP_PROGRESS_VALUE = "vte.progress.value" :: T.Text

-- | A 'GI.Vte.Enums.PropertyTypeInt' termprop that stores a hint how to interpret
-- the 'GI.Vte.Constants.TERMPROP_PROGRESS_VALUE' termprop value. If set, this
-- termprop\'s value will be from the t'GI.Vte.Enums.ProgressHint' enumeration.
-- An unset termprop should be treated as if it had value
-- 'GI.Vte.Enums.ProgressHintActive' if the 'GI.Vte.Constants.TERMPROP_PROGRESS_VALUE'
-- termprop has a value
-- 
-- Note that this termprop never will have the value
-- 'GI.Vte.Enums.ProgressHintInactive'.
-- 
-- The value of this termprop should be ignored unless the
-- 'GI.Vte.Constants.TERMPROP_PROGRESS_VALUE' termprop has a value.
-- 
-- Note that this termprop cannot be set by the termprop OSC, but instead
-- only by OSC 9 ; 4 (ConEmu progress).
-- 
-- /Since: 0.80/
pattern $mTERMPROP_PROGRESS_HINT :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bTERMPROP_PROGRESS_HINT :: Text
TERMPROP_PROGRESS_HINT = "vte.progress.hint" :: T.Text

-- | The string prefix that any termprop\'s name must start with to be installed
-- by 'GI.Vte.Functions.installTermprop'.
-- 
-- /Since: 0.78/
pattern $mTERMPROP_NAME_PREFIX :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bTERMPROP_NAME_PREFIX :: Text
TERMPROP_NAME_PREFIX = "vte.ext." :: T.Text

-- | A 'GI.Vte.Enums.PropertyTypeImage' termprop to specify an image for use
-- as a favicon.
-- 
-- Applications should prefer to use this termprop, if set, over
-- the 'GI.Vte.Constants.TERMPROP_ICON_COLOR' color.
-- 
-- Note that in this vte version, this termprop is always unset.
-- 
-- /Since: 0.80/
pattern $mTERMPROP_ICON_IMAGE :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bTERMPROP_ICON_IMAGE :: Text
TERMPROP_ICON_IMAGE = "vte.icon.image" :: T.Text

-- | /No description available in the introspection data./
pattern $mTERMPROP_ICON_COLOR :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bTERMPROP_ICON_COLOR :: Text
TERMPROP_ICON_COLOR = "vte.icon.color" :: T.Text

-- | A 'GI.Vte.Enums.PropertyTypeUri' termprop that stores the current file URI
-- as set by OSC 6.
-- Use this with 'GI.Vte.Objects.Terminal.terminalRefTermpropUri' instead of using
-- 'GI.Vte.Objects.Terminal.terminalGetCurrentFileUri'.
-- 
-- Note that this termprop is not settable via the termprop OSC.
-- 
-- /Since: 0.78/
pattern $mTERMPROP_CURRENT_FILE_URI :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bTERMPROP_CURRENT_FILE_URI :: Text
TERMPROP_CURRENT_FILE_URI = "vte.cwf" :: T.Text

-- | A 'GI.Vte.Enums.PropertyTypeUri' termprop that stores the current directory
-- URI as set by OSC 7.
-- Use this with 'GI.Vte.Objects.Terminal.terminalRefTermpropUri' instead of using
-- 'GI.Vte.Objects.Terminal.terminalGetCurrentDirectoryUri'.
-- 
-- Note that this termprop is not settable via the termprop OSC.
-- 
-- /Since: 0.78/
pattern $mTERMPROP_CURRENT_DIRECTORY_URI :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bTERMPROP_CURRENT_DIRECTORY_URI :: Text
TERMPROP_CURRENT_DIRECTORY_URI = "vte.cwd" :: T.Text

-- | A 'GI.Vte.Enums.PropertyTypeUint' termprop that stores the user ID of the
-- container.
-- 
-- /Since: 0.78/
pattern $mTERMPROP_CONTAINER_UID :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bTERMPROP_CONTAINER_UID :: Text
TERMPROP_CONTAINER_UID = "vte.container.uid" :: T.Text

-- | A 'GI.Vte.Enums.PropertyTypeString' termprop that stores the runtime of the
-- container.
-- 
-- /Since: 0.78/
pattern $mTERMPROP_CONTAINER_RUNTIME :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bTERMPROP_CONTAINER_RUNTIME :: Text
TERMPROP_CONTAINER_RUNTIME = "vte.container.runtime" :: T.Text

-- | A 'GI.Vte.Enums.PropertyTypeString' termprop that stores the name of the
-- container.
-- 
-- /Since: 0.78/
pattern $mTERMPROP_CONTAINER_NAME :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bTERMPROP_CONTAINER_NAME :: Text
TERMPROP_CONTAINER_NAME = "vte.container.name" :: T.Text

-- | Use this as a spawn flag (together with flags from t'GI.GLib.Flags.SpawnFlags') in
-- 'GI.Vte.Objects.Pty.ptySpawnAsync'.
-- 
-- Requires 'GI.Vte.Objects.Pty.ptySpawnAsync' etc. to move the newly created child
-- process to a systemd user scope; if that fails, the whole spawn fails.
-- 
-- This is supported on Linux only.
-- 
-- /Since: 0.60/
pattern $mSPAWN_REQUIRE_SYSTEMD_SCOPE :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bSPAWN_REQUIRE_SYSTEMD_SCOPE :: Int32
SPAWN_REQUIRE_SYSTEMD_SCOPE = 134217728 :: Int32

-- | Use this as a spawn flag (together with flags from t'GI.GLib.Flags.SpawnFlags') in
-- 'GI.Vte.Objects.Pty.ptySpawnAsync'.
-- 
-- Prevents 'GI.Vte.Objects.Pty.ptySpawnAsync' etc. from moving the newly created child
-- process to a systemd user scope.
-- 
-- /Since: 0.60/
pattern $mSPAWN_NO_SYSTEMD_SCOPE :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bSPAWN_NO_SYSTEMD_SCOPE :: Int32
SPAWN_NO_SYSTEMD_SCOPE = 67108864 :: Int32

-- | Use this as a spawn flag (together with flags from t'GI.GLib.Flags.SpawnFlags') in
-- 'GI.Vte.Objects.Pty.ptySpawnAsync'.
-- 
-- Normally, the spawned process inherits the environment from the parent
-- process; when this flag is used, only the environment variables passed
-- to 'GI.Vte.Objects.Pty.ptySpawnAsync' etc. are passed to the child process.
pattern $mSPAWN_NO_PARENT_ENVV :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bSPAWN_NO_PARENT_ENVV :: Int32
SPAWN_NO_PARENT_ENVV = 33554432 :: Int32

-- | /No description available in the introspection data./
pattern $mREGEX_FLAGS_DEFAULT :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bREGEX_FLAGS_DEFAULT :: Int32
REGEX_FLAGS_DEFAULT = 1075314688 :: Int32

-- | The minor version number of the VTE library
-- (e.g. in version 3.1.4 this is 1).
pattern $mMINOR_VERSION :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bMINOR_VERSION :: Int32
MINOR_VERSION = 80 :: Int32

-- | The micro version number of the VTE library
-- (e.g. in version 3.1.4 this is 4).
pattern $mMICRO_VERSION :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bMICRO_VERSION :: Int32
MICRO_VERSION = 1 :: Int32

-- | The major version number of the VTE library
-- (e.g. in version 3.1.4 this is 3).
pattern $mMAJOR_VERSION :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bMAJOR_VERSION :: Int32
MAJOR_VERSION = 0 :: Int32