{- |
Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
License    : LGPL-2.1
Maintainer : Iñaki García Etxebarria (inaki@blueleaf.cc)
-}

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

module GI.GObject.Flags
    (

 -- * Flags
-- ** BindingFlags #flag:BindingFlags#

    BindingFlags(..)                        ,


-- ** ConnectFlags #flag:ConnectFlags#

    ConnectFlags(..)                        ,


-- ** ParamFlags #flag:ParamFlags#

    ParamFlags(..)                          ,


-- ** SignalFlags #flag:SignalFlags#

    SignalFlags(..)                         ,


-- ** SignalMatchType #flag:SignalMatchType#

    SignalMatchType(..)                     ,


-- ** TypeDebugFlags #flag:TypeDebugFlags#

    TypeDebugFlags(..)                      ,


-- ** TypeFlags #flag:TypeFlags#

    TypeFlags(..)                           ,


-- ** TypeFundamentalFlags #flag:TypeFundamentalFlags#

    TypeFundamentalFlags(..)                ,




    ) 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.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.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


-- Flags TypeFundamentalFlags
{- |
Bit masks used to check or determine specific characteristics of a
fundamental type.
-}
data TypeFundamentalFlags =
      TypeFundamentalFlagsClassed
    {- ^
    Indicates a classed type
    -}
    | TypeFundamentalFlagsInstantiatable
    {- ^
    Indicates an instantiable type (implies classed)
    -}
    | TypeFundamentalFlagsDerivable
    {- ^
    Indicates a flat derivable type
    -}
    | TypeFundamentalFlagsDeepDerivable
    {- ^
    Indicates a deep derivable type (implies derivable)
    -}
    | AnotherTypeFundamentalFlags Int
    -- ^ Catch-all for unknown values
    deriving (Show, Eq)

instance P.Enum TypeFundamentalFlags where
    fromEnum TypeFundamentalFlagsClassed = 1
    fromEnum TypeFundamentalFlagsInstantiatable = 2
    fromEnum TypeFundamentalFlagsDerivable = 4
    fromEnum TypeFundamentalFlagsDeepDerivable = 8
    fromEnum (AnotherTypeFundamentalFlags k) = k

    toEnum 1 = TypeFundamentalFlagsClassed
    toEnum 2 = TypeFundamentalFlagsInstantiatable
    toEnum 4 = TypeFundamentalFlagsDerivable
    toEnum 8 = TypeFundamentalFlagsDeepDerivable
    toEnum k = AnotherTypeFundamentalFlags k

instance P.Ord TypeFundamentalFlags where
    compare a b = P.compare (P.fromEnum a) (P.fromEnum b)

instance IsGFlag TypeFundamentalFlags

-- Flags TypeFlags
{- |
Bit masks used to check or determine characteristics of a type.
-}
data TypeFlags =
      TypeFlagsAbstract
    {- ^
    Indicates an abstract type. No instances can be
     created for an abstract type
    -}
    | TypeFlagsValueAbstract
    {- ^
    Indicates an abstract value type, i.e. a type
     that introduces a value table, but can\'t be used for
     'GI.GObject.Structs.Value.valueInit'
    -}
    | AnotherTypeFlags Int
    -- ^ Catch-all for unknown values
    deriving (Show, Eq)

instance P.Enum TypeFlags where
    fromEnum TypeFlagsAbstract = 16
    fromEnum TypeFlagsValueAbstract = 32
    fromEnum (AnotherTypeFlags k) = k

    toEnum 16 = TypeFlagsAbstract
    toEnum 32 = TypeFlagsValueAbstract
    toEnum k = AnotherTypeFlags k

instance P.Ord TypeFlags where
    compare a b = P.compare (P.fromEnum a) (P.fromEnum b)

instance IsGFlag TypeFlags

-- Flags TypeDebugFlags
{-# DEPRECATED TypeDebugFlags ["(Since version 2.36)","'GI.GObject.Functions.typeInit' is now done automatically"] #-}
{- |
These flags used to be passed to 'GI.GObject.Functions.typeInitWithDebugFlags' which
is now deprecated.

If you need to enable debugging features, use the GOBJECT_DEBUG
environment variable.
-}
data TypeDebugFlags =
      TypeDebugFlagsNone
    {- ^
    Print no messages
    -}
    | TypeDebugFlagsObjects
    {- ^
    Print messages about object bookkeeping
    -}
    | TypeDebugFlagsSignals
    {- ^
    Print messages about signal emissions
    -}
    | TypeDebugFlagsInstanceCount
    {- ^
    Keep a count of instances of each type
    -}
    | TypeDebugFlagsMask
    {- ^
    Mask covering all debug flags
    -}
    | AnotherTypeDebugFlags Int
    -- ^ Catch-all for unknown values
    deriving (Show, Eq)

instance P.Enum TypeDebugFlags where
    fromEnum TypeDebugFlagsNone = 0
    fromEnum TypeDebugFlagsObjects = 1
    fromEnum TypeDebugFlagsSignals = 2
    fromEnum TypeDebugFlagsInstanceCount = 4
    fromEnum TypeDebugFlagsMask = 7
    fromEnum (AnotherTypeDebugFlags k) = k

    toEnum 0 = TypeDebugFlagsNone
    toEnum 1 = TypeDebugFlagsObjects
    toEnum 2 = TypeDebugFlagsSignals
    toEnum 4 = TypeDebugFlagsInstanceCount
    toEnum 7 = TypeDebugFlagsMask
    toEnum k = AnotherTypeDebugFlags k

instance P.Ord TypeDebugFlags where
    compare a b = P.compare (P.fromEnum a) (P.fromEnum b)

instance IsGFlag TypeDebugFlags

-- Flags SignalMatchType
{- |
The match types specify what 'GI.GObject.Functions.signalHandlersBlockMatched',
'GI.GObject.Functions.signalHandlersUnblockMatched' and 'GI.GObject.Functions.signalHandlersDisconnectMatched'
match signals by.
-}
data SignalMatchType =
      SignalMatchTypeId
    {- ^
    The signal id must be equal.
    -}
    | SignalMatchTypeDetail
    {- ^
    The signal detail be equal.
    -}
    | SignalMatchTypeClosure
    {- ^
    The closure must be the same.
    -}
    | SignalMatchTypeFunc
    {- ^
    The C closure callback must be the same.
    -}
    | SignalMatchTypeData
    {- ^
    The closure data must be the same.
    -}
    | SignalMatchTypeUnblocked
    {- ^
    Only unblocked signals may matched.
    -}
    | AnotherSignalMatchType Int
    -- ^ Catch-all for unknown values
    deriving (Show, Eq)

instance P.Enum SignalMatchType where
    fromEnum SignalMatchTypeId = 1
    fromEnum SignalMatchTypeDetail = 2
    fromEnum SignalMatchTypeClosure = 4
    fromEnum SignalMatchTypeFunc = 8
    fromEnum SignalMatchTypeData = 16
    fromEnum SignalMatchTypeUnblocked = 32
    fromEnum (AnotherSignalMatchType k) = k

    toEnum 1 = SignalMatchTypeId
    toEnum 2 = SignalMatchTypeDetail
    toEnum 4 = SignalMatchTypeClosure
    toEnum 8 = SignalMatchTypeFunc
    toEnum 16 = SignalMatchTypeData
    toEnum 32 = SignalMatchTypeUnblocked
    toEnum k = AnotherSignalMatchType k

instance P.Ord SignalMatchType where
    compare a b = P.compare (P.fromEnum a) (P.fromEnum b)

instance IsGFlag SignalMatchType

-- Flags SignalFlags
{- |
The signal flags are used to specify a signal\'s behaviour, the overall
signal description outlines how especially the RUN flags control the
stages of a signal emission.
-}
data SignalFlags =
      SignalFlagsRunFirst
    {- ^
    Invoke the object method handler in the first emission stage.
    -}
    | SignalFlagsRunLast
    {- ^
    Invoke the object method handler in the third emission stage.
    -}
    | SignalFlagsRunCleanup
    {- ^
    Invoke the object method handler in the last emission stage.
    -}
    | SignalFlagsNoRecurse
    {- ^
    Signals being emitted for an object while currently being in
     emission for this very object will not be emitted recursively,
     but instead cause the first emission to be restarted.
    -}
    | SignalFlagsDetailed
    {- ^
    This signal supports \"::detail\" appendices to the signal name
     upon handler connections and emissions.
    -}
    | SignalFlagsAction
    {- ^
    Action signals are signals that may freely be emitted on alive
     objects from user code via @/g_signal_emit()/@ and friends, without
     the need of being embedded into extra code that performs pre or
     post emission adjustments on the object. They can also be thought
     of as object methods which can be called generically by
     third-party code.
    -}
    | SignalFlagsNoHooks
    {- ^
    No emissions hooks are supported for this signal.
    -}
    | SignalFlagsMustCollect
    {- ^
    Varargs signal emission will always collect the
      arguments, even if there are no signal handlers connected.  Since 2.30.
    -}
    | SignalFlagsDeprecated
    {- ^
    The signal is deprecated and will be removed
      in a future version. A warning will be generated if it is connected while
      running with G_ENABLE_DIAGNOSTIC=1.  Since 2.32.
    -}
    | AnotherSignalFlags Int
    -- ^ Catch-all for unknown values
    deriving (Show, Eq)

instance P.Enum SignalFlags where
    fromEnum SignalFlagsRunFirst = 1
    fromEnum SignalFlagsRunLast = 2
    fromEnum SignalFlagsRunCleanup = 4
    fromEnum SignalFlagsNoRecurse = 8
    fromEnum SignalFlagsDetailed = 16
    fromEnum SignalFlagsAction = 32
    fromEnum SignalFlagsNoHooks = 64
    fromEnum SignalFlagsMustCollect = 128
    fromEnum SignalFlagsDeprecated = 256
    fromEnum (AnotherSignalFlags k) = k

    toEnum 1 = SignalFlagsRunFirst
    toEnum 2 = SignalFlagsRunLast
    toEnum 4 = SignalFlagsRunCleanup
    toEnum 8 = SignalFlagsNoRecurse
    toEnum 16 = SignalFlagsDetailed
    toEnum 32 = SignalFlagsAction
    toEnum 64 = SignalFlagsNoHooks
    toEnum 128 = SignalFlagsMustCollect
    toEnum 256 = SignalFlagsDeprecated
    toEnum k = AnotherSignalFlags k

instance P.Ord SignalFlags where
    compare a b = P.compare (P.fromEnum a) (P.fromEnum b)

instance IsGFlag SignalFlags

-- Flags ParamFlags
{- |
Through the 'GI.GObject.Flags.ParamFlags' flag values, certain aspects of parameters
can be configured. See also 'GI.GObject.Constants.PARAM_STATIC_STRINGS'.
-}
data ParamFlags =
      ParamFlagsReadable
    {- ^
    the parameter is readable
    -}
    | ParamFlagsWritable
    {- ^
    the parameter is writable
    -}
    | ParamFlagsReadwrite
    {- ^
    alias for 'GI.GObject.Flags.ParamFlagsReadable' | 'GI.GObject.Flags.ParamFlagsWritable'
    -}
    | ParamFlagsConstruct
    {- ^
    the parameter will be set upon object construction
    -}
    | ParamFlagsConstructOnly
    {- ^
    the parameter can only be set upon object construction
    -}
    | ParamFlagsLaxValidation
    {- ^
    upon parameter conversion (see 'GI.GObject.Functions.paramValueConvert')
     strict validation is not required
    -}
    | ParamFlagsStaticName
    {- ^
    the string used as name when constructing the
     parameter is guaranteed to remain valid and
     unmodified for the lifetime of the parameter.
     Since 2.8
    -}
    | ParamFlagsPrivate
    {- ^
    internal
    -}
    | ParamFlagsStaticNick
    {- ^
    the string used as nick when constructing the
     parameter is guaranteed to remain valid and
     unmmodified for the lifetime of the parameter.
     Since 2.8
    -}
    | ParamFlagsStaticBlurb
    {- ^
    the string used as blurb when constructing the
     parameter is guaranteed to remain valid and
     unmodified for the lifetime of the parameter.
     Since 2.8
    -}
    | ParamFlagsExplicitNotify
    {- ^
    calls to 'GI.GObject.Objects.Object.objectSetProperty' for this
      property will not automatically result in a \"notify\" signal being
      emitted: the implementation must call 'GI.GObject.Objects.Object.objectNotify' themselves
      in case the property actually changes.  Since: 2.42.
    -}
    | ParamFlagsDeprecated
    {- ^
    the parameter is deprecated and will be removed
     in a future version. A warning will be generated if it is used
     while running with G_ENABLE_DIAGNOSTIC=1.
     Since 2.26
    -}
    | AnotherParamFlags Int
    -- ^ Catch-all for unknown values
    deriving (Show, Eq)

instance P.Enum ParamFlags where
    fromEnum ParamFlagsReadable = 1
    fromEnum ParamFlagsWritable = 2
    fromEnum ParamFlagsReadwrite = 3
    fromEnum ParamFlagsConstruct = 4
    fromEnum ParamFlagsConstructOnly = 8
    fromEnum ParamFlagsLaxValidation = 16
    fromEnum ParamFlagsStaticName = 32
    fromEnum ParamFlagsPrivate = 32
    fromEnum ParamFlagsStaticNick = 64
    fromEnum ParamFlagsStaticBlurb = 128
    fromEnum ParamFlagsExplicitNotify = 1073741824
    fromEnum ParamFlagsDeprecated = 2147483648
    fromEnum (AnotherParamFlags k) = k

    toEnum 1 = ParamFlagsReadable
    toEnum 2 = ParamFlagsWritable
    toEnum 3 = ParamFlagsReadwrite
    toEnum 4 = ParamFlagsConstruct
    toEnum 8 = ParamFlagsConstructOnly
    toEnum 16 = ParamFlagsLaxValidation
    toEnum 32 = ParamFlagsStaticName
    toEnum 64 = ParamFlagsStaticNick
    toEnum 128 = ParamFlagsStaticBlurb
    toEnum 1073741824 = ParamFlagsExplicitNotify
    toEnum 2147483648 = ParamFlagsDeprecated
    toEnum k = AnotherParamFlags k

instance P.Ord ParamFlags where
    compare a b = P.compare (P.fromEnum a) (P.fromEnum b)

instance IsGFlag ParamFlags

-- Flags ConnectFlags
{- |
The connection flags are used to specify the behaviour of a signal\'s
connection.
-}
data ConnectFlags =
      ConnectFlagsAfter
    {- ^
    whether the handler should be called before or after the
     default handler of the signal.
    -}
    | ConnectFlagsSwapped
    {- ^
    whether the instance and data should be swapped when
     calling the handler; see @/g_signal_connect_swapped()/@ for an example.
    -}
    | AnotherConnectFlags Int
    -- ^ Catch-all for unknown values
    deriving (Show, Eq)

instance P.Enum ConnectFlags where
    fromEnum ConnectFlagsAfter = 1
    fromEnum ConnectFlagsSwapped = 2
    fromEnum (AnotherConnectFlags k) = k

    toEnum 1 = ConnectFlagsAfter
    toEnum 2 = ConnectFlagsSwapped
    toEnum k = AnotherConnectFlags k

instance P.Ord ConnectFlags where
    compare a b = P.compare (P.fromEnum a) (P.fromEnum b)

instance IsGFlag ConnectFlags

-- Flags BindingFlags
{- |
Flags to be passed to 'GI.GObject.Objects.Object.objectBindProperty' or
@/g_object_bind_property_full()/@.

This enumeration can be extended at later date.

/Since: 2.26/
-}
data BindingFlags =
      BindingFlagsDefault
    {- ^
    The default binding; if the source property
      changes, the target property is updated with its value.
    -}
    | BindingFlagsBidirectional
    {- ^
    Bidirectional binding; if either the
      property of the source or the property of the target changes,
      the other is updated.
    -}
    | BindingFlagsSyncCreate
    {- ^
    Synchronize the values of the source and
      target properties when creating the binding; the direction of
      the synchronization is always from the source to the target.
    -}
    | BindingFlagsInvertBoolean
    {- ^
    If the two properties being bound are
      booleans, setting one to 'True' will result in the other being
      set to 'False' and vice versa. This flag will only work for
      boolean properties, and cannot be used when passing custom
      transformation functions to @/g_object_bind_property_full()/@.
    -}
    | AnotherBindingFlags Int
    -- ^ Catch-all for unknown values
    deriving (Show, Eq)

instance P.Enum BindingFlags where
    fromEnum BindingFlagsDefault = 0
    fromEnum BindingFlagsBidirectional = 1
    fromEnum BindingFlagsSyncCreate = 2
    fromEnum BindingFlagsInvertBoolean = 4
    fromEnum (AnotherBindingFlags k) = k

    toEnum 0 = BindingFlagsDefault
    toEnum 1 = BindingFlagsBidirectional
    toEnum 2 = BindingFlagsSyncCreate
    toEnum 4 = BindingFlagsInvertBoolean
    toEnum k = AnotherBindingFlags k

instance P.Ord BindingFlags where
    compare a b = P.compare (P.fromEnum a) (P.fromEnum b)

foreign import ccall "g_binding_flags_get_type" c_g_binding_flags_get_type ::
    IO GType

instance BoxedFlags BindingFlags where
    boxedFlagsType _ = c_g_binding_flags_get_type

instance IsGFlag BindingFlags