{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A structure which contains a single flags value, its name, and its
-- nickname.

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

module GI.GObject.Structs.FlagsValue
    ( 

-- * Exported types
    FlagsValue(..)                          ,
    newZeroFlagsValue                       ,


 -- * Methods

#if defined(ENABLE_OVERLOADING)
    ResolveFlagsValueMethod                 ,
#endif



 -- * Properties


-- ** value #attr:value#
-- | the flags value

#if defined(ENABLE_OVERLOADING)
    flagsValue_value                        ,
#endif
    getFlagsValueValue                      ,
    setFlagsValueValue                      ,


-- ** valueName #attr:valueName#
-- | the name of the value

    clearFlagsValueValueName                ,
#if defined(ENABLE_OVERLOADING)
    flagsValue_valueName                    ,
#endif
    getFlagsValueValueName                  ,
    setFlagsValueValueName                  ,


-- ** valueNick #attr:valueNick#
-- | the nickname of the value

    clearFlagsValueValueNick                ,
#if defined(ENABLE_OVERLOADING)
    flagsValue_valueNick                    ,
#endif
    getFlagsValueValueNick                  ,
    setFlagsValueValueNick                  ,




    ) 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


-- | Memory-managed wrapper type.
newtype FlagsValue = FlagsValue (SP.ManagedPtr FlagsValue)
    deriving (FlagsValue -> FlagsValue -> Bool
(FlagsValue -> FlagsValue -> Bool)
-> (FlagsValue -> FlagsValue -> Bool) -> Eq FlagsValue
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FlagsValue -> FlagsValue -> Bool
$c/= :: FlagsValue -> FlagsValue -> Bool
== :: FlagsValue -> FlagsValue -> Bool
$c== :: FlagsValue -> FlagsValue -> Bool
Eq)

instance SP.ManagedPtrNewtype FlagsValue where
    toManagedPtr :: FlagsValue -> ManagedPtr FlagsValue
toManagedPtr (FlagsValue ManagedPtr FlagsValue
p) = ManagedPtr FlagsValue
p

instance BoxedPtr FlagsValue where
    boxedPtrCopy :: FlagsValue -> IO FlagsValue
boxedPtrCopy = \FlagsValue
p -> FlagsValue -> (Ptr FlagsValue -> IO FlagsValue) -> IO FlagsValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr FlagsValue
p (Int -> Ptr FlagsValue -> IO (Ptr FlagsValue)
forall a. (HasCallStack, CallocPtr a) => Int -> Ptr a -> IO (Ptr a)
copyBytes Int
24 (Ptr FlagsValue -> IO (Ptr FlagsValue))
-> (Ptr FlagsValue -> IO FlagsValue)
-> Ptr FlagsValue
-> IO FlagsValue
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (ManagedPtr FlagsValue -> FlagsValue)
-> Ptr FlagsValue -> IO FlagsValue
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.wrapPtr ManagedPtr FlagsValue -> FlagsValue
FlagsValue)
    boxedPtrFree :: FlagsValue -> IO ()
boxedPtrFree = \FlagsValue
x -> FlagsValue -> (Ptr FlagsValue -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
SP.withManagedPtr FlagsValue
x Ptr FlagsValue -> IO ()
forall a. Ptr a -> IO ()
SP.freeMem
instance CallocPtr FlagsValue where
    boxedPtrCalloc :: IO (Ptr FlagsValue)
boxedPtrCalloc = Int -> IO (Ptr FlagsValue)
forall a. Int -> IO (Ptr a)
callocBytes Int
24


-- | Construct a `FlagsValue` struct initialized to zero.
newZeroFlagsValue :: MonadIO m => m FlagsValue
newZeroFlagsValue :: forall (m :: * -> *). MonadIO m => m FlagsValue
newZeroFlagsValue = IO FlagsValue -> m FlagsValue
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO FlagsValue -> m FlagsValue) -> IO FlagsValue -> m FlagsValue
forall a b. (a -> b) -> a -> b
$ IO (Ptr FlagsValue)
forall a. CallocPtr a => IO (Ptr a)
boxedPtrCalloc IO (Ptr FlagsValue)
-> (Ptr FlagsValue -> IO FlagsValue) -> IO FlagsValue
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr FlagsValue -> FlagsValue)
-> Ptr FlagsValue -> IO FlagsValue
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr FlagsValue -> FlagsValue
FlagsValue

instance tag ~ 'AttrSet => Constructible FlagsValue tag where
    new :: forall (m :: * -> *).
MonadIO m =>
(ManagedPtr FlagsValue -> FlagsValue)
-> [AttrOp FlagsValue tag] -> m FlagsValue
new ManagedPtr FlagsValue -> FlagsValue
_ [AttrOp FlagsValue tag]
attrs = do
        FlagsValue
o <- m FlagsValue
forall (m :: * -> *). MonadIO m => m FlagsValue
newZeroFlagsValue
        FlagsValue -> [AttrOp FlagsValue 'AttrSet] -> m ()
forall o (m :: * -> *).
MonadIO m =>
o -> [AttrOp o 'AttrSet] -> m ()
GI.Attributes.set FlagsValue
o [AttrOp FlagsValue tag]
[AttrOp FlagsValue 'AttrSet]
attrs
        FlagsValue -> m FlagsValue
forall (m :: * -> *) a. Monad m => a -> m a
return FlagsValue
o


-- | Get the value of the “@value@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' flagsValue #value
-- @
getFlagsValueValue :: MonadIO m => FlagsValue -> m Word32
getFlagsValueValue :: forall (m :: * -> *). MonadIO m => FlagsValue -> m Word32
getFlagsValueValue FlagsValue
s = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ FlagsValue -> (Ptr FlagsValue -> IO Word32) -> IO Word32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr FlagsValue
s ((Ptr FlagsValue -> IO Word32) -> IO Word32)
-> (Ptr FlagsValue -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$ \Ptr FlagsValue
ptr -> do
    Word32
val <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek (Ptr FlagsValue
ptr Ptr FlagsValue -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) :: IO Word32
    Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
val

-- | Set the value of the “@value@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' flagsValue [ #value 'Data.GI.Base.Attributes.:=' value ]
-- @
setFlagsValueValue :: MonadIO m => FlagsValue -> Word32 -> m ()
setFlagsValueValue :: forall (m :: * -> *). MonadIO m => FlagsValue -> Word32 -> m ()
setFlagsValueValue FlagsValue
s Word32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ FlagsValue -> (Ptr FlagsValue -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr FlagsValue
s ((Ptr FlagsValue -> IO ()) -> IO ())
-> (Ptr FlagsValue -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr FlagsValue
ptr -> do
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr FlagsValue
ptr Ptr FlagsValue -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) (Word32
val :: Word32)

#if defined(ENABLE_OVERLOADING)
data FlagsValueValueFieldInfo
instance AttrInfo FlagsValueValueFieldInfo where
    type AttrBaseTypeConstraint FlagsValueValueFieldInfo = (~) FlagsValue
    type AttrAllowedOps FlagsValueValueFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint FlagsValueValueFieldInfo = (~) Word32
    type AttrTransferTypeConstraint FlagsValueValueFieldInfo = (~)Word32
    type AttrTransferType FlagsValueValueFieldInfo = Word32
    type AttrGetType FlagsValueValueFieldInfo = Word32
    type AttrLabel FlagsValueValueFieldInfo = "value"
    type AttrOrigin FlagsValueValueFieldInfo = FlagsValue
    attrGet = getFlagsValueValue
    attrSet = setFlagsValueValue
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

flagsValue_value :: AttrLabelProxy "value"
flagsValue_value = AttrLabelProxy

#endif


-- | Get the value of the “@value_name@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' flagsValue #valueName
-- @
getFlagsValueValueName :: MonadIO m => FlagsValue -> m (Maybe T.Text)
getFlagsValueValueName :: forall (m :: * -> *). MonadIO m => FlagsValue -> m (Maybe Text)
getFlagsValueValueName FlagsValue
s = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ FlagsValue
-> (Ptr FlagsValue -> IO (Maybe Text)) -> IO (Maybe Text)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr FlagsValue
s ((Ptr FlagsValue -> IO (Maybe Text)) -> IO (Maybe Text))
-> (Ptr FlagsValue -> IO (Maybe Text)) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \Ptr FlagsValue
ptr -> do
    CString
val <- Ptr CString -> IO CString
forall a. Storable a => Ptr a -> IO a
peek (Ptr FlagsValue
ptr Ptr FlagsValue -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) :: IO CString
    Maybe Text
result <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
SP.convertIfNonNull CString
val ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
val' -> do
        Text
val'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
val'
        Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
val''
    Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
result

-- | Set the value of the “@value_name@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' flagsValue [ #valueName 'Data.GI.Base.Attributes.:=' value ]
-- @
setFlagsValueValueName :: MonadIO m => FlagsValue -> CString -> m ()
setFlagsValueValueName :: forall (m :: * -> *). MonadIO m => FlagsValue -> CString -> m ()
setFlagsValueValueName FlagsValue
s CString
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ FlagsValue -> (Ptr FlagsValue -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr FlagsValue
s ((Ptr FlagsValue -> IO ()) -> IO ())
-> (Ptr FlagsValue -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr FlagsValue
ptr -> do
    Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr FlagsValue
ptr Ptr FlagsValue -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) (CString
val :: CString)

-- | Set the value of the “@value_name@” field to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #valueName
-- @
clearFlagsValueValueName :: MonadIO m => FlagsValue -> m ()
clearFlagsValueValueName :: forall (m :: * -> *). MonadIO m => FlagsValue -> m ()
clearFlagsValueValueName FlagsValue
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ FlagsValue -> (Ptr FlagsValue -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr FlagsValue
s ((Ptr FlagsValue -> IO ()) -> IO ())
-> (Ptr FlagsValue -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr FlagsValue
ptr -> do
    Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr FlagsValue
ptr Ptr FlagsValue -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) (CString
forall a. Ptr a
FP.nullPtr :: CString)

#if defined(ENABLE_OVERLOADING)
data FlagsValueValueNameFieldInfo
instance AttrInfo FlagsValueValueNameFieldInfo where
    type AttrBaseTypeConstraint FlagsValueValueNameFieldInfo = (~) FlagsValue
    type AttrAllowedOps FlagsValueValueNameFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint FlagsValueValueNameFieldInfo = (~) CString
    type AttrTransferTypeConstraint FlagsValueValueNameFieldInfo = (~)CString
    type AttrTransferType FlagsValueValueNameFieldInfo = CString
    type AttrGetType FlagsValueValueNameFieldInfo = Maybe T.Text
    type AttrLabel FlagsValueValueNameFieldInfo = "value_name"
    type AttrOrigin FlagsValueValueNameFieldInfo = FlagsValue
    attrGet = getFlagsValueValueName
    attrSet = setFlagsValueValueName
    attrConstruct = undefined
    attrClear = clearFlagsValueValueName
    attrTransfer _ v = do
        return v

flagsValue_valueName :: AttrLabelProxy "valueName"
flagsValue_valueName = AttrLabelProxy

#endif


-- | Get the value of the “@value_nick@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' flagsValue #valueNick
-- @
getFlagsValueValueNick :: MonadIO m => FlagsValue -> m (Maybe T.Text)
getFlagsValueValueNick :: forall (m :: * -> *). MonadIO m => FlagsValue -> m (Maybe Text)
getFlagsValueValueNick FlagsValue
s = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ FlagsValue
-> (Ptr FlagsValue -> IO (Maybe Text)) -> IO (Maybe Text)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr FlagsValue
s ((Ptr FlagsValue -> IO (Maybe Text)) -> IO (Maybe Text))
-> (Ptr FlagsValue -> IO (Maybe Text)) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \Ptr FlagsValue
ptr -> do
    CString
val <- Ptr CString -> IO CString
forall a. Storable a => Ptr a -> IO a
peek (Ptr FlagsValue
ptr Ptr FlagsValue -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16) :: IO CString
    Maybe Text
result <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
SP.convertIfNonNull CString
val ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
val' -> do
        Text
val'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
val'
        Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
val''
    Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
result

-- | Set the value of the “@value_nick@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' flagsValue [ #valueNick 'Data.GI.Base.Attributes.:=' value ]
-- @
setFlagsValueValueNick :: MonadIO m => FlagsValue -> CString -> m ()
setFlagsValueValueNick :: forall (m :: * -> *). MonadIO m => FlagsValue -> CString -> m ()
setFlagsValueValueNick FlagsValue
s CString
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ FlagsValue -> (Ptr FlagsValue -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr FlagsValue
s ((Ptr FlagsValue -> IO ()) -> IO ())
-> (Ptr FlagsValue -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr FlagsValue
ptr -> do
    Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr FlagsValue
ptr Ptr FlagsValue -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16) (CString
val :: CString)

-- | Set the value of the “@value_nick@” field to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #valueNick
-- @
clearFlagsValueValueNick :: MonadIO m => FlagsValue -> m ()
clearFlagsValueValueNick :: forall (m :: * -> *). MonadIO m => FlagsValue -> m ()
clearFlagsValueValueNick FlagsValue
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ FlagsValue -> (Ptr FlagsValue -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr FlagsValue
s ((Ptr FlagsValue -> IO ()) -> IO ())
-> (Ptr FlagsValue -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr FlagsValue
ptr -> do
    Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr FlagsValue
ptr Ptr FlagsValue -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16) (CString
forall a. Ptr a
FP.nullPtr :: CString)

#if defined(ENABLE_OVERLOADING)
data FlagsValueValueNickFieldInfo
instance AttrInfo FlagsValueValueNickFieldInfo where
    type AttrBaseTypeConstraint FlagsValueValueNickFieldInfo = (~) FlagsValue
    type AttrAllowedOps FlagsValueValueNickFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint FlagsValueValueNickFieldInfo = (~) CString
    type AttrTransferTypeConstraint FlagsValueValueNickFieldInfo = (~)CString
    type AttrTransferType FlagsValueValueNickFieldInfo = CString
    type AttrGetType FlagsValueValueNickFieldInfo = Maybe T.Text
    type AttrLabel FlagsValueValueNickFieldInfo = "value_nick"
    type AttrOrigin FlagsValueValueNickFieldInfo = FlagsValue
    attrGet = getFlagsValueValueNick
    attrSet = setFlagsValueValueNick
    attrConstruct = undefined
    attrClear = clearFlagsValueValueNick
    attrTransfer _ v = do
        return v

flagsValue_valueNick :: AttrLabelProxy "valueNick"
flagsValue_valueNick = AttrLabelProxy

#endif



#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList FlagsValue
type instance O.AttributeList FlagsValue = FlagsValueAttributeList
type FlagsValueAttributeList = ('[ '("value", FlagsValueValueFieldInfo), '("valueName", FlagsValueValueNameFieldInfo), '("valueNick", FlagsValueValueNickFieldInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveFlagsValueMethod (t :: Symbol) (o :: *) :: * where
    ResolveFlagsValueMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveFlagsValueMethod t FlagsValue, O.OverloadedMethod info FlagsValue p) => OL.IsLabel t (FlagsValue -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif

#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveFlagsValueMethod t FlagsValue, O.OverloadedMethod info FlagsValue p, R.HasField t FlagsValue p) => R.HasField t FlagsValue p where
    getField = O.overloadedMethod @info

#endif

instance (info ~ ResolveFlagsValueMethod t FlagsValue, O.OverloadedMethodInfo info FlagsValue) => OL.IsLabel t (O.MethodProxy info FlagsValue) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif

#endif