{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- /No description available in the introspection data./

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

module GI.Poppler.Structs.ActionOCGState
    ( 

-- * Exported types
    ActionOCGState(..)                      ,
    newZeroActionOCGState                   ,


 -- * Methods
-- ** Overloaded methods #method:Overloaded methods#

#if defined(ENABLE_OVERLOADING)
    ResolveActionOCGStateMethod             ,
#endif




 -- * Properties
-- ** stateList #attr:stateList#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    actionOCGState_stateList                ,
#endif
    clearActionOCGStateStateList            ,
    getActionOCGStateStateList              ,
    setActionOCGStateStateList              ,


-- ** title #attr:title#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    actionOCGState_title                    ,
#endif
    clearActionOCGStateTitle                ,
    getActionOCGStateTitle                  ,
    setActionOCGStateTitle                  ,


-- ** type #attr:type#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    actionOCGState_type                     ,
#endif
    getActionOCGStateType                   ,
    setActionOCGStateType                   ,




    ) 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.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 {-# SOURCE #-} qualified GI.Poppler.Enums as Poppler.Enums

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

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

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


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

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


-- | Get the value of the “@type@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' actionOCGState #type
-- @
getActionOCGStateType :: MonadIO m => ActionOCGState -> m Poppler.Enums.ActionType
getActionOCGStateType :: ActionOCGState -> m ActionType
getActionOCGStateType ActionOCGState
s = IO ActionType -> m ActionType
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ActionType -> m ActionType) -> IO ActionType -> m ActionType
forall a b. (a -> b) -> a -> b
$ ActionOCGState
-> (Ptr ActionOCGState -> IO ActionType) -> IO ActionType
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr ActionOCGState
s ((Ptr ActionOCGState -> IO ActionType) -> IO ActionType)
-> (Ptr ActionOCGState -> IO ActionType) -> IO ActionType
forall a b. (a -> b) -> a -> b
$ \Ptr ActionOCGState
ptr -> do
    CUInt
val <- Ptr CUInt -> IO CUInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr ActionOCGState
ptr Ptr ActionOCGState -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) :: IO CUInt
    let val' :: ActionType
val' = (Int -> ActionType
forall a. Enum a => Int -> a
toEnum (Int -> ActionType) -> (CUInt -> Int) -> CUInt -> ActionType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
val
    ActionType -> IO ActionType
forall (m :: * -> *) a. Monad m => a -> m a
return ActionType
val'

-- | Set the value of the “@type@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' actionOCGState [ #type 'Data.GI.Base.Attributes.:=' value ]
-- @
setActionOCGStateType :: MonadIO m => ActionOCGState -> Poppler.Enums.ActionType -> m ()
setActionOCGStateType :: ActionOCGState -> ActionType -> m ()
setActionOCGStateType ActionOCGState
s ActionType
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ ActionOCGState -> (Ptr ActionOCGState -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr ActionOCGState
s ((Ptr ActionOCGState -> IO ()) -> IO ())
-> (Ptr ActionOCGState -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr ActionOCGState
ptr -> do
    let val' :: CUInt
val' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (ActionType -> Int) -> ActionType -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ActionType -> Int
forall a. Enum a => a -> Int
fromEnum) ActionType
val
    Ptr CUInt -> CUInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ActionOCGState
ptr Ptr ActionOCGState -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) (CUInt
val' :: CUInt)

#if defined(ENABLE_OVERLOADING)
data ActionOCGStateTypeFieldInfo
instance AttrInfo ActionOCGStateTypeFieldInfo where
    type AttrBaseTypeConstraint ActionOCGStateTypeFieldInfo = (~) ActionOCGState
    type AttrAllowedOps ActionOCGStateTypeFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint ActionOCGStateTypeFieldInfo = (~) Poppler.Enums.ActionType
    type AttrTransferTypeConstraint ActionOCGStateTypeFieldInfo = (~)Poppler.Enums.ActionType
    type AttrTransferType ActionOCGStateTypeFieldInfo = Poppler.Enums.ActionType
    type AttrGetType ActionOCGStateTypeFieldInfo = Poppler.Enums.ActionType
    type AttrLabel ActionOCGStateTypeFieldInfo = "type"
    type AttrOrigin ActionOCGStateTypeFieldInfo = ActionOCGState
    attrGet = getActionOCGStateType
    attrSet = setActionOCGStateType
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

actionOCGState_type :: AttrLabelProxy "type"
actionOCGState_type = AttrLabelProxy

#endif


-- | Get the value of the “@title@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' actionOCGState #title
-- @
getActionOCGStateTitle :: MonadIO m => ActionOCGState -> m (Maybe T.Text)
getActionOCGStateTitle :: ActionOCGState -> m (Maybe Text)
getActionOCGStateTitle ActionOCGState
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
$ ActionOCGState
-> (Ptr ActionOCGState -> IO (Maybe Text)) -> IO (Maybe Text)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr ActionOCGState
s ((Ptr ActionOCGState -> IO (Maybe Text)) -> IO (Maybe Text))
-> (Ptr ActionOCGState -> IO (Maybe Text)) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \Ptr ActionOCGState
ptr -> do
    CString
val <- Ptr CString -> IO CString
forall a. Storable a => Ptr a -> IO a
peek (Ptr ActionOCGState
ptr Ptr ActionOCGState -> 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 “@title@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' actionOCGState [ #title 'Data.GI.Base.Attributes.:=' value ]
-- @
setActionOCGStateTitle :: MonadIO m => ActionOCGState -> CString -> m ()
setActionOCGStateTitle :: ActionOCGState -> CString -> m ()
setActionOCGStateTitle ActionOCGState
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
$ ActionOCGState -> (Ptr ActionOCGState -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr ActionOCGState
s ((Ptr ActionOCGState -> IO ()) -> IO ())
-> (Ptr ActionOCGState -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr ActionOCGState
ptr -> do
    Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ActionOCGState
ptr Ptr ActionOCGState -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) (CString
val :: CString)

-- | Set the value of the “@title@” 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' #title
-- @
clearActionOCGStateTitle :: MonadIO m => ActionOCGState -> m ()
clearActionOCGStateTitle :: ActionOCGState -> m ()
clearActionOCGStateTitle ActionOCGState
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ ActionOCGState -> (Ptr ActionOCGState -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr ActionOCGState
s ((Ptr ActionOCGState -> IO ()) -> IO ())
-> (Ptr ActionOCGState -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr ActionOCGState
ptr -> do
    Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ActionOCGState
ptr Ptr ActionOCGState -> 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 ActionOCGStateTitleFieldInfo
instance AttrInfo ActionOCGStateTitleFieldInfo where
    type AttrBaseTypeConstraint ActionOCGStateTitleFieldInfo = (~) ActionOCGState
    type AttrAllowedOps ActionOCGStateTitleFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint ActionOCGStateTitleFieldInfo = (~) CString
    type AttrTransferTypeConstraint ActionOCGStateTitleFieldInfo = (~)CString
    type AttrTransferType ActionOCGStateTitleFieldInfo = CString
    type AttrGetType ActionOCGStateTitleFieldInfo = Maybe T.Text
    type AttrLabel ActionOCGStateTitleFieldInfo = "title"
    type AttrOrigin ActionOCGStateTitleFieldInfo = ActionOCGState
    attrGet = getActionOCGStateTitle
    attrSet = setActionOCGStateTitle
    attrConstruct = undefined
    attrClear = clearActionOCGStateTitle
    attrTransfer _ v = do
        return v

actionOCGState_title :: AttrLabelProxy "title"
actionOCGState_title = AttrLabelProxy

#endif


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

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

-- | Set the value of the “@state_list@” 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' #stateList
-- @
clearActionOCGStateStateList :: MonadIO m => ActionOCGState -> m ()
clearActionOCGStateStateList :: ActionOCGState -> m ()
clearActionOCGStateStateList ActionOCGState
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ ActionOCGState -> (Ptr ActionOCGState -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr ActionOCGState
s ((Ptr ActionOCGState -> IO ()) -> IO ())
-> (Ptr ActionOCGState -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr ActionOCGState
ptr -> do
    Ptr (Ptr (GList (Ptr ()))) -> Ptr (GList (Ptr ())) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ActionOCGState
ptr Ptr ActionOCGState -> Int -> Ptr (Ptr (GList (Ptr ())))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16) (Ptr (GList (Ptr ()))
forall a. Ptr a
FP.nullPtr :: Ptr (GList (Ptr ())))

#if defined(ENABLE_OVERLOADING)
data ActionOCGStateStateListFieldInfo
instance AttrInfo ActionOCGStateStateListFieldInfo where
    type AttrBaseTypeConstraint ActionOCGStateStateListFieldInfo = (~) ActionOCGState
    type AttrAllowedOps ActionOCGStateStateListFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint ActionOCGStateStateListFieldInfo = (~) (Ptr (GList (Ptr ())))
    type AttrTransferTypeConstraint ActionOCGStateStateListFieldInfo = (~)(Ptr (GList (Ptr ())))
    type AttrTransferType ActionOCGStateStateListFieldInfo = (Ptr (GList (Ptr ())))
    type AttrGetType ActionOCGStateStateListFieldInfo = [Ptr ()]
    type AttrLabel ActionOCGStateStateListFieldInfo = "state_list"
    type AttrOrigin ActionOCGStateStateListFieldInfo = ActionOCGState
    attrGet = getActionOCGStateStateList
    attrSet = setActionOCGStateStateList
    attrConstruct = undefined
    attrClear = clearActionOCGStateStateList
    attrTransfer _ v = do
        return v

actionOCGState_stateList :: AttrLabelProxy "stateList"
actionOCGState_stateList = AttrLabelProxy

#endif



#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList ActionOCGState
type instance O.AttributeList ActionOCGState = ActionOCGStateAttributeList
type ActionOCGStateAttributeList = ('[ '("type", ActionOCGStateTypeFieldInfo), '("title", ActionOCGStateTitleFieldInfo), '("stateList", ActionOCGStateStateListFieldInfo)] :: [(Symbol, *)])
#endif

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

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

#endif