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


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

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

module GI.Vte.Constants
    ( 
    pattern TEST_FLAGS_NONE                 ,
    pattern TEST_FLAGS_ALL                  ,
    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.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R


-- | /No description available in the introspection data./
pattern $bTEST_FLAGS_NONE :: Word64
$mTEST_FLAGS_NONE :: forall {r}. Word64 -> (Void# -> r) -> (Void# -> r) -> r
TEST_FLAGS_NONE = 0 :: Word64

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

-- | 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 $bSPAWN_REQUIRE_SYSTEMD_SCOPE :: Int32
$mSPAWN_REQUIRE_SYSTEMD_SCOPE :: forall {r}. Int32 -> (Void# -> r) -> (Void# -> r) -> r
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 $bSPAWN_NO_SYSTEMD_SCOPE :: Int32
$mSPAWN_NO_SYSTEMD_SCOPE :: forall {r}. Int32 -> (Void# -> r) -> (Void# -> r) -> r
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 $bSPAWN_NO_PARENT_ENVV :: Int32
$mSPAWN_NO_PARENT_ENVV :: forall {r}. Int32 -> (Void# -> r) -> (Void# -> r) -> r
SPAWN_NO_PARENT_ENVV = 33554432 :: Int32

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

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

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

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