{-# 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.HarfBuzz.Constants
    ( 
    pattern VERSION_STRING                  ,
    pattern VERSION_MINOR                   ,
    pattern VERSION_MICRO                   ,
    pattern VERSION_MAJOR                   ,
    pattern UNICODE_MAX_DECOMPOSITION_LEN   ,
    pattern UNICODE_MAX                     ,
    pattern UNICODE_COMBINING_CLASS_CCC133  ,
    pattern OT_VAR_NO_AXIS_INDEX            ,
    pattern OT_MAX_TAGS_PER_SCRIPT          ,
    pattern OT_MAX_TAGS_PER_LANGUAGE        ,
    pattern OT_LAYOUT_NO_VARIATIONS_INDEX   ,
    pattern OT_LAYOUT_NO_SCRIPT_INDEX       ,
    pattern OT_LAYOUT_NO_FEATURE_INDEX      ,
    pattern OT_LAYOUT_DEFAULT_LANGUAGE_INDEX,
    pattern FONT_NO_VAR_NAMED_INSTANCE      ,
    pattern FEATURE_GLOBAL_START            ,
    pattern CODEPOINT_INVALID               ,
    pattern BUFFER_REPLACEMENT_CODEPOINT_DEFAULT,
    pattern AAT_LAYOUT_NO_SELECTOR_INDEX    ,

    ) 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

-- | A string literal containing the library version available at compile-time.
pattern $mVERSION_STRING :: forall {r}. Text -> ((# #) -> r) -> ((# #) -> r) -> r
$bVERSION_STRING :: Text
VERSION_STRING = "8.4.0" :: T.Text

-- | The minor component of the library version available at compile-time.
pattern $mVERSION_MINOR :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bVERSION_MINOR :: Int32
VERSION_MINOR = 4 :: Int32

-- | The micro component of the library version available at compile-time.
pattern $mVERSION_MICRO :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bVERSION_MICRO :: Int32
VERSION_MICRO = 0 :: Int32

-- | The major component of the library version available at compile-time.
pattern $mVERSION_MAJOR :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bVERSION_MAJOR :: Int32
VERSION_MAJOR = 8 :: Int32

{-# DEPRECATED UNICODE_MAX_DECOMPOSITION_LEN ["(Since version 2.0.0)"] #-}
-- | See Unicode 6.1 for details on the maximum decomposition length.
pattern $mUNICODE_MAX_DECOMPOSITION_LEN :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bUNICODE_MAX_DECOMPOSITION_LEN :: Int32
UNICODE_MAX_DECOMPOSITION_LEN = 19 :: Int32

-- | Maximum valid Unicode code point.
-- 
-- /Since: 1.9.0/
pattern $mUNICODE_MAX :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bUNICODE_MAX :: Int32
UNICODE_MAX = 1114111 :: Int32

{-# DEPRECATED UNICODE_COMBINING_CLASS_CCC133 ["(Since version 7.2.0)"] #-}
-- | [Tibetan]
pattern $mUNICODE_COMBINING_CLASS_CCC133 :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bUNICODE_COMBINING_CLASS_CCC133 :: Int32
UNICODE_COMBINING_CLASS_CCC133 = 133 :: Int32

{-# DEPRECATED OT_VAR_NO_AXIS_INDEX ["(Since version 2.2.0)"] #-}
-- | Do not use.
-- 
-- /Since: 1.4.2/
pattern $mOT_VAR_NO_AXIS_INDEX :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bOT_VAR_NO_AXIS_INDEX :: Int32
OT_VAR_NO_AXIS_INDEX = 4294967295 :: Int32

-- | Maximum number of OpenType tags that can correspond to a give t'GI.HarfBuzz.Enums.ScriptT'.
-- 
-- /Since: 2.0.0/
pattern $mOT_MAX_TAGS_PER_SCRIPT :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bOT_MAX_TAGS_PER_SCRIPT :: Int32
OT_MAX_TAGS_PER_SCRIPT = 3 :: Int32

-- | Maximum number of OpenType tags that can correspond to a give t'GI.HarfBuzz.Structs.LanguageT.LanguageT'.
-- 
-- /Since: 2.0.0/
pattern $mOT_MAX_TAGS_PER_LANGUAGE :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bOT_MAX_TAGS_PER_LANGUAGE :: Int32
OT_MAX_TAGS_PER_LANGUAGE = 3 :: Int32

-- | Special value for variations index indicating unsupported variation.
pattern $mOT_LAYOUT_NO_VARIATIONS_INDEX :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bOT_LAYOUT_NO_VARIATIONS_INDEX :: Int32
OT_LAYOUT_NO_VARIATIONS_INDEX = 4294967295 :: Int32

-- | Special value for script index indicating unsupported script.
pattern $mOT_LAYOUT_NO_SCRIPT_INDEX :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bOT_LAYOUT_NO_SCRIPT_INDEX :: Int32
OT_LAYOUT_NO_SCRIPT_INDEX = 65535 :: Int32

-- | Special value for feature index indicating unsupported feature.
pattern $mOT_LAYOUT_NO_FEATURE_INDEX :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bOT_LAYOUT_NO_FEATURE_INDEX :: Int32
OT_LAYOUT_NO_FEATURE_INDEX = 65535 :: Int32

-- | Special value for language index indicating default or unsupported language.
pattern $mOT_LAYOUT_DEFAULT_LANGUAGE_INDEX :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bOT_LAYOUT_DEFAULT_LANGUAGE_INDEX :: Int32
OT_LAYOUT_DEFAULT_LANGUAGE_INDEX = 65535 :: Int32

-- XXX: Could not generate constant
-- Not implemented: Don't know how to treat constants of type TInterface (Name {namespace = "HarfBuzz", name = "language_t"})

-- | Constant signifying that a font does not have any
-- named-instance index set.  This is the default of
-- a font.
-- 
-- /Since: 7.0.0/
pattern $mFONT_NO_VAR_NAMED_INSTANCE :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bFONT_NO_VAR_NAMED_INSTANCE :: Int32
FONT_NO_VAR_NAMED_INSTANCE = 4294967295 :: Int32

-- | Special setting for t'GI.HarfBuzz.Structs.FeatureT.FeatureT'.@/start/@ to apply the feature from the start
-- of the buffer.
-- 
-- /Since: 2.0.0/
pattern $mFEATURE_GLOBAL_START :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bFEATURE_GLOBAL_START :: Int32
FEATURE_GLOBAL_START = 0 :: Int32

-- | Unused @/hb_codepoint_t/@ value.
-- 
-- /Since: 8.0.0/
pattern $mCODEPOINT_INVALID :: forall {r}. Word32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bCODEPOINT_INVALID :: Word32
CODEPOINT_INVALID = 4294967295 :: Word32

-- | The default code point for replacing invalid characters in a given encoding.
-- Set to U+FFFD REPLACEMENT CHARACTER.
-- 
-- /Since: 0.9.31/
pattern $mBUFFER_REPLACEMENT_CODEPOINT_DEFAULT :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bBUFFER_REPLACEMENT_CODEPOINT_DEFAULT :: Int32
BUFFER_REPLACEMENT_CODEPOINT_DEFAULT = 65533 :: Int32

-- | Used when getting or setting AAT feature selectors. Indicates that
-- there is no selector index corresponding to the selector of interest.
pattern $mAAT_LAYOUT_NO_SELECTOR_INDEX :: forall {r}. Int32 -> ((# #) -> r) -> ((# #) -> r) -> r
$bAAT_LAYOUT_NO_SELECTOR_INDEX :: Int32
AAT_LAYOUT_NO_SELECTOR_INDEX = 65535 :: Int32