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


-- 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 (Int -> TypeFundamentalFlags -> ShowS
[TypeFundamentalFlags] -> ShowS
TypeFundamentalFlags -> String
(Int -> TypeFundamentalFlags -> ShowS)
-> (TypeFundamentalFlags -> String)
-> ([TypeFundamentalFlags] -> ShowS)
-> Show TypeFundamentalFlags
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TypeFundamentalFlags] -> ShowS
$cshowList :: [TypeFundamentalFlags] -> ShowS
show :: TypeFundamentalFlags -> String
$cshow :: TypeFundamentalFlags -> String
showsPrec :: Int -> TypeFundamentalFlags -> ShowS
$cshowsPrec :: Int -> TypeFundamentalFlags -> ShowS
Show, TypeFundamentalFlags -> TypeFundamentalFlags -> Bool
(TypeFundamentalFlags -> TypeFundamentalFlags -> Bool)
-> (TypeFundamentalFlags -> TypeFundamentalFlags -> Bool)
-> Eq TypeFundamentalFlags
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TypeFundamentalFlags -> TypeFundamentalFlags -> Bool
$c/= :: TypeFundamentalFlags -> TypeFundamentalFlags -> Bool
== :: TypeFundamentalFlags -> TypeFundamentalFlags -> Bool
$c== :: TypeFundamentalFlags -> TypeFundamentalFlags -> Bool
Eq)

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

    toEnum :: Int -> TypeFundamentalFlags
toEnum Int
1 = TypeFundamentalFlags
TypeFundamentalFlagsClassed
    toEnum Int
2 = TypeFundamentalFlags
TypeFundamentalFlagsInstantiatable
    toEnum Int
4 = TypeFundamentalFlags
TypeFundamentalFlagsDerivable
    toEnum Int
8 = TypeFundamentalFlags
TypeFundamentalFlagsDeepDerivable
    toEnum Int
k = Int -> TypeFundamentalFlags
AnotherTypeFundamentalFlags Int
k

instance P.Ord TypeFundamentalFlags where
    compare :: TypeFundamentalFlags -> TypeFundamentalFlags -> Ordering
compare TypeFundamentalFlags
a TypeFundamentalFlags
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (TypeFundamentalFlags -> Int
forall a. Enum a => a -> Int
P.fromEnum TypeFundamentalFlags
a) (TypeFundamentalFlags -> Int
forall a. Enum a => a -> Int
P.fromEnum TypeFundamentalFlags
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 (Int -> TypeFlags -> ShowS
[TypeFlags] -> ShowS
TypeFlags -> String
(Int -> TypeFlags -> ShowS)
-> (TypeFlags -> String)
-> ([TypeFlags] -> ShowS)
-> Show TypeFlags
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TypeFlags] -> ShowS
$cshowList :: [TypeFlags] -> ShowS
show :: TypeFlags -> String
$cshow :: TypeFlags -> String
showsPrec :: Int -> TypeFlags -> ShowS
$cshowsPrec :: Int -> TypeFlags -> ShowS
Show, TypeFlags -> TypeFlags -> Bool
(TypeFlags -> TypeFlags -> Bool)
-> (TypeFlags -> TypeFlags -> Bool) -> Eq TypeFlags
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TypeFlags -> TypeFlags -> Bool
$c/= :: TypeFlags -> TypeFlags -> Bool
== :: TypeFlags -> TypeFlags -> Bool
$c== :: TypeFlags -> TypeFlags -> Bool
Eq)

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

    toEnum :: Int -> TypeFlags
toEnum Int
16 = TypeFlags
TypeFlagsAbstract
    toEnum Int
32 = TypeFlags
TypeFlagsValueAbstract
    toEnum Int
k = Int -> TypeFlags
AnotherTypeFlags Int
k

instance P.Ord TypeFlags where
    compare :: TypeFlags -> TypeFlags -> Ordering
compare TypeFlags
a TypeFlags
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (TypeFlags -> Int
forall a. Enum a => a -> Int
P.fromEnum TypeFlags
a) (TypeFlags -> Int
forall a. Enum a => a -> Int
P.fromEnum TypeFlags
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 (Int -> TypeDebugFlags -> ShowS
[TypeDebugFlags] -> ShowS
TypeDebugFlags -> String
(Int -> TypeDebugFlags -> ShowS)
-> (TypeDebugFlags -> String)
-> ([TypeDebugFlags] -> ShowS)
-> Show TypeDebugFlags
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TypeDebugFlags] -> ShowS
$cshowList :: [TypeDebugFlags] -> ShowS
show :: TypeDebugFlags -> String
$cshow :: TypeDebugFlags -> String
showsPrec :: Int -> TypeDebugFlags -> ShowS
$cshowsPrec :: Int -> TypeDebugFlags -> ShowS
Show, TypeDebugFlags -> TypeDebugFlags -> Bool
(TypeDebugFlags -> TypeDebugFlags -> Bool)
-> (TypeDebugFlags -> TypeDebugFlags -> Bool) -> Eq TypeDebugFlags
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TypeDebugFlags -> TypeDebugFlags -> Bool
$c/= :: TypeDebugFlags -> TypeDebugFlags -> Bool
== :: TypeDebugFlags -> TypeDebugFlags -> Bool
$c== :: TypeDebugFlags -> TypeDebugFlags -> Bool
Eq)

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

    toEnum :: Int -> TypeDebugFlags
toEnum Int
0 = TypeDebugFlags
TypeDebugFlagsNone
    toEnum Int
1 = TypeDebugFlags
TypeDebugFlagsObjects
    toEnum Int
2 = TypeDebugFlags
TypeDebugFlagsSignals
    toEnum Int
4 = TypeDebugFlags
TypeDebugFlagsInstanceCount
    toEnum Int
7 = TypeDebugFlags
TypeDebugFlagsMask
    toEnum Int
k = Int -> TypeDebugFlags
AnotherTypeDebugFlags Int
k

instance P.Ord TypeDebugFlags where
    compare :: TypeDebugFlags -> TypeDebugFlags -> Ordering
compare TypeDebugFlags
a TypeDebugFlags
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (TypeDebugFlags -> Int
forall a. Enum a => a -> Int
P.fromEnum TypeDebugFlags
a) (TypeDebugFlags -> Int
forall a. Enum a => a -> Int
P.fromEnum TypeDebugFlags
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 must 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 be matched.
    | AnotherSignalMatchType Int
    -- ^ Catch-all for unknown values
    deriving (Int -> SignalMatchType -> ShowS
[SignalMatchType] -> ShowS
SignalMatchType -> String
(Int -> SignalMatchType -> ShowS)
-> (SignalMatchType -> String)
-> ([SignalMatchType] -> ShowS)
-> Show SignalMatchType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SignalMatchType] -> ShowS
$cshowList :: [SignalMatchType] -> ShowS
show :: SignalMatchType -> String
$cshow :: SignalMatchType -> String
showsPrec :: Int -> SignalMatchType -> ShowS
$cshowsPrec :: Int -> SignalMatchType -> ShowS
Show, SignalMatchType -> SignalMatchType -> Bool
(SignalMatchType -> SignalMatchType -> Bool)
-> (SignalMatchType -> SignalMatchType -> Bool)
-> Eq SignalMatchType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SignalMatchType -> SignalMatchType -> Bool
$c/= :: SignalMatchType -> SignalMatchType -> Bool
== :: SignalMatchType -> SignalMatchType -> Bool
$c== :: SignalMatchType -> SignalMatchType -> Bool
Eq)

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

    toEnum :: Int -> SignalMatchType
toEnum Int
1 = SignalMatchType
SignalMatchTypeId
    toEnum Int
2 = SignalMatchType
SignalMatchTypeDetail
    toEnum Int
4 = SignalMatchType
SignalMatchTypeClosure
    toEnum Int
8 = SignalMatchType
SignalMatchTypeFunc
    toEnum Int
16 = SignalMatchType
SignalMatchTypeData
    toEnum Int
32 = SignalMatchType
SignalMatchTypeUnblocked
    toEnum Int
k = Int -> SignalMatchType
AnotherSignalMatchType Int
k

instance P.Ord SignalMatchType where
    compare :: SignalMatchType -> SignalMatchType -> Ordering
compare SignalMatchType
a SignalMatchType
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (SignalMatchType -> Int
forall a. Enum a => a -> Int
P.fromEnum SignalMatchType
a) (SignalMatchType -> Int
forall a. Enum a => a -> Int
P.fromEnum SignalMatchType
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](#g:signal: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 (Int -> SignalFlags -> ShowS
[SignalFlags] -> ShowS
SignalFlags -> String
(Int -> SignalFlags -> ShowS)
-> (SignalFlags -> String)
-> ([SignalFlags] -> ShowS)
-> Show SignalFlags
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SignalFlags] -> ShowS
$cshowList :: [SignalFlags] -> ShowS
show :: SignalFlags -> String
$cshow :: SignalFlags -> String
showsPrec :: Int -> SignalFlags -> ShowS
$cshowsPrec :: Int -> SignalFlags -> ShowS
Show, SignalFlags -> SignalFlags -> Bool
(SignalFlags -> SignalFlags -> Bool)
-> (SignalFlags -> SignalFlags -> Bool) -> Eq SignalFlags
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SignalFlags -> SignalFlags -> Bool
$c/= :: SignalFlags -> SignalFlags -> Bool
== :: SignalFlags -> SignalFlags -> Bool
$c== :: SignalFlags -> SignalFlags -> Bool
Eq)

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

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

instance P.Ord SignalFlags where
    compare :: SignalFlags -> SignalFlags -> Ordering
compare SignalFlags
a SignalFlags
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (SignalFlags -> Int
forall a. Enum a => a -> Int
P.fromEnum SignalFlags
a) (SignalFlags -> Int
forall a. Enum a => a -> Int
P.fromEnum SignalFlags
b)

instance IsGFlag SignalFlags

-- Flags ParamFlags
-- | Through the t'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 (Int -> ParamFlags -> ShowS
[ParamFlags] -> ShowS
ParamFlags -> String
(Int -> ParamFlags -> ShowS)
-> (ParamFlags -> String)
-> ([ParamFlags] -> ShowS)
-> Show ParamFlags
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ParamFlags] -> ShowS
$cshowList :: [ParamFlags] -> ShowS
show :: ParamFlags -> String
$cshow :: ParamFlags -> String
showsPrec :: Int -> ParamFlags -> ShowS
$cshowsPrec :: Int -> ParamFlags -> ShowS
Show, ParamFlags -> ParamFlags -> Bool
(ParamFlags -> ParamFlags -> Bool)
-> (ParamFlags -> ParamFlags -> Bool) -> Eq ParamFlags
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ParamFlags -> ParamFlags -> Bool
$c/= :: ParamFlags -> ParamFlags -> Bool
== :: ParamFlags -> ParamFlags -> Bool
$c== :: ParamFlags -> ParamFlags -> Bool
Eq)

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

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

instance P.Ord ParamFlags where
    compare :: ParamFlags -> ParamFlags -> Ordering
compare ParamFlags
a ParamFlags
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (ParamFlags -> Int
forall a. Enum a => a -> Int
P.fromEnum ParamFlags
a) (ParamFlags -> Int
forall a. Enum a => a -> Int
P.fromEnum ParamFlags
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 (Int -> ConnectFlags -> ShowS
[ConnectFlags] -> ShowS
ConnectFlags -> String
(Int -> ConnectFlags -> ShowS)
-> (ConnectFlags -> String)
-> ([ConnectFlags] -> ShowS)
-> Show ConnectFlags
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ConnectFlags] -> ShowS
$cshowList :: [ConnectFlags] -> ShowS
show :: ConnectFlags -> String
$cshow :: ConnectFlags -> String
showsPrec :: Int -> ConnectFlags -> ShowS
$cshowsPrec :: Int -> ConnectFlags -> ShowS
Show, ConnectFlags -> ConnectFlags -> Bool
(ConnectFlags -> ConnectFlags -> Bool)
-> (ConnectFlags -> ConnectFlags -> Bool) -> Eq ConnectFlags
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ConnectFlags -> ConnectFlags -> Bool
$c/= :: ConnectFlags -> ConnectFlags -> Bool
== :: ConnectFlags -> ConnectFlags -> Bool
$c== :: ConnectFlags -> ConnectFlags -> Bool
Eq)

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

    toEnum :: Int -> ConnectFlags
toEnum Int
1 = ConnectFlags
ConnectFlagsAfter
    toEnum Int
2 = ConnectFlags
ConnectFlagsSwapped
    toEnum Int
k = Int -> ConnectFlags
AnotherConnectFlags Int
k

instance P.Ord ConnectFlags where
    compare :: ConnectFlags -> ConnectFlags -> Ordering
compare ConnectFlags
a ConnectFlags
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (ConnectFlags -> Int
forall a. Enum a => a -> Int
P.fromEnum ConnectFlags
a) (ConnectFlags -> Int
forall a. Enum a => a -> Int
P.fromEnum ConnectFlags
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 'P.True' will result in the other being
    --   set to 'P.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 (Int -> BindingFlags -> ShowS
[BindingFlags] -> ShowS
BindingFlags -> String
(Int -> BindingFlags -> ShowS)
-> (BindingFlags -> String)
-> ([BindingFlags] -> ShowS)
-> Show BindingFlags
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BindingFlags] -> ShowS
$cshowList :: [BindingFlags] -> ShowS
show :: BindingFlags -> String
$cshow :: BindingFlags -> String
showsPrec :: Int -> BindingFlags -> ShowS
$cshowsPrec :: Int -> BindingFlags -> ShowS
Show, BindingFlags -> BindingFlags -> Bool
(BindingFlags -> BindingFlags -> Bool)
-> (BindingFlags -> BindingFlags -> Bool) -> Eq BindingFlags
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BindingFlags -> BindingFlags -> Bool
$c/= :: BindingFlags -> BindingFlags -> Bool
== :: BindingFlags -> BindingFlags -> Bool
$c== :: BindingFlags -> BindingFlags -> Bool
Eq)

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

    toEnum :: Int -> BindingFlags
toEnum Int
0 = BindingFlags
BindingFlagsDefault
    toEnum Int
1 = BindingFlags
BindingFlagsBidirectional
    toEnum Int
2 = BindingFlags
BindingFlagsSyncCreate
    toEnum Int
4 = BindingFlags
BindingFlagsInvertBoolean
    toEnum Int
k = Int -> BindingFlags
AnotherBindingFlags Int
k

instance P.Ord BindingFlags where
    compare :: BindingFlags -> BindingFlags -> Ordering
compare BindingFlags
a BindingFlags
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare (BindingFlags -> Int
forall a. Enum a => a -> Int
P.fromEnum BindingFlags
a) (BindingFlags -> Int
forall a. Enum a => a -> Int
P.fromEnum BindingFlags
b)

type instance O.ParentTypes BindingFlags = '[]
instance O.HasParentTypes BindingFlags

foreign import ccall "g_binding_flags_get_type" c_g_binding_flags_get_type :: 
    IO GType

instance B.Types.TypedObject BindingFlags where
    glibType :: IO GType
glibType = IO GType
c_g_binding_flags_get_type

instance B.Types.BoxedFlags BindingFlags

instance IsGFlag BindingFlags