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

module GI.Poppler.Structs.ActionOCGState
    ( 

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


 -- * Properties
-- ** stateList #attr:stateList#
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    actionOCGState_stateList                ,
#endif
    clearActionOCGStateStateList            ,
    getActionOCGStateStateList              ,
    setActionOCGStateStateList              ,


-- ** title #attr:title#
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    actionOCGState_title                    ,
#endif
    clearActionOCGStateTitle                ,
    getActionOCGStateTitle                  ,
    setActionOCGStateTitle                  ,


-- ** type #attr:type#
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    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.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
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 {-# SOURCE #-} qualified GI.Poppler.Enums as Poppler.Enums

newtype ActionOCGState = ActionOCGState (ManagedPtr ActionOCGState)
instance WrappedPtr ActionOCGState where
    wrappedPtrCalloc = callocBytes 24
    wrappedPtrCopy = \p -> withManagedPtr p (copyBytes 24 >=> wrapPtr ActionOCGState)
    wrappedPtrFree = Just ptr_to_g_free

-- | Construct a `ActionOCGState` struct initialized to zero.
newZeroActionOCGState :: MonadIO m => m ActionOCGState
newZeroActionOCGState = liftIO $ wrappedPtrCalloc >>= wrapPtr ActionOCGState

instance tag ~ 'AttrSet => Constructible ActionOCGState tag where
    new _ attrs = do
        o <- newZeroActionOCGState
        GI.Attributes.set o attrs
        return o


noActionOCGState :: Maybe ActionOCGState
noActionOCGState = Nothing

getActionOCGStateType :: MonadIO m => ActionOCGState -> m Poppler.Enums.ActionType
getActionOCGStateType s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 0) :: IO CUInt
    let val' = (toEnum . fromIntegral) val
    return val'

setActionOCGStateType :: MonadIO m => ActionOCGState -> Poppler.Enums.ActionType -> m ()
setActionOCGStateType s val = liftIO $ withManagedPtr s $ \ptr -> do
    let val' = (fromIntegral . fromEnum) val
    poke (ptr `plusPtr` 0) (val' :: CUInt)

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

actionOCGState_type :: AttrLabelProxy "type"
actionOCGState_type = AttrLabelProxy

#endif


getActionOCGStateTitle :: MonadIO m => ActionOCGState -> m (Maybe T.Text)
getActionOCGStateTitle s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 8) :: IO CString
    result <- SP.convertIfNonNull val $ \val' -> do
        val'' <- cstringToText val'
        return val''
    return result

setActionOCGStateTitle :: MonadIO m => ActionOCGState -> CString -> m ()
setActionOCGStateTitle s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 8) (val :: CString)

clearActionOCGStateTitle :: MonadIO m => ActionOCGState -> m ()
clearActionOCGStateTitle s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 8) (FP.nullPtr :: CString)

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data ActionOCGStateTitleFieldInfo
instance AttrInfo ActionOCGStateTitleFieldInfo where
    type AttrAllowedOps ActionOCGStateTitleFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint ActionOCGStateTitleFieldInfo = (~) CString
    type AttrBaseTypeConstraint ActionOCGStateTitleFieldInfo = (~) ActionOCGState
    type AttrGetType ActionOCGStateTitleFieldInfo = Maybe T.Text
    type AttrLabel ActionOCGStateTitleFieldInfo = "title"
    type AttrOrigin ActionOCGStateTitleFieldInfo = ActionOCGState
    attrGet _ = getActionOCGStateTitle
    attrSet _ = setActionOCGStateTitle
    attrConstruct = undefined
    attrClear _ = clearActionOCGStateTitle

actionOCGState_title :: AttrLabelProxy "title"
actionOCGState_title = AttrLabelProxy

#endif


getActionOCGStateStateList :: MonadIO m => ActionOCGState -> m ([Ptr ()])
getActionOCGStateStateList s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 16) :: IO (Ptr (GList (Ptr ())))
    val' <- unpackGList val
    return val'

setActionOCGStateStateList :: MonadIO m => ActionOCGState -> Ptr (GList (Ptr ())) -> m ()
setActionOCGStateStateList s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 16) (val :: Ptr (GList (Ptr ())))

clearActionOCGStateStateList :: MonadIO m => ActionOCGState -> m ()
clearActionOCGStateStateList s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 16) (FP.nullPtr :: Ptr (GList (Ptr ())))

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

actionOCGState_stateList :: AttrLabelProxy "stateList"
actionOCGState_stateList = AttrLabelProxy

#endif



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

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

instance (info ~ ResolveActionOCGStateMethod t ActionOCGState, O.MethodInfo info ActionOCGState p) => O.IsLabelProxy t (ActionOCGState -> p) where
    fromLabelProxy _ = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)

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

#endif