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

/No description available in the introspection data./
-}

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

module GI.Poppler.Structs.ActionNamed
    (

-- * Exported types
    ActionNamed(..)                         ,
    newZeroActionNamed                      ,
    noActionNamed                           ,


 -- * Properties
-- ** namedDest #attr:namedDest#
{- | /No description available in the introspection data./
-}
#if ENABLE_OVERLOADING
    actionNamed_namedDest                   ,
#endif
    clearActionNamedNamedDest               ,
    getActionNamedNamedDest                 ,
    setActionNamedNamedDest                 ,


-- ** title #attr:title#
{- | /No description available in the introspection data./
-}
#if ENABLE_OVERLOADING
    actionNamed_title                       ,
#endif
    clearActionNamedTitle                   ,
    getActionNamedTitle                     ,
    setActionNamedTitle                     ,


-- ** type #attr:type#
{- | /No description available in the introspection data./
-}
#if ENABLE_OVERLOADING
    actionNamed_type                        ,
#endif
    getActionNamedType                      ,
    setActionNamedType                      ,




    ) 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

import {-# SOURCE #-} qualified GI.Poppler.Enums as Poppler.Enums

-- | Memory-managed wrapper type.
newtype ActionNamed = ActionNamed (ManagedPtr ActionNamed)
instance WrappedPtr ActionNamed where
    wrappedPtrCalloc = callocBytes 24
    wrappedPtrCopy = \p -> withManagedPtr p (copyBytes 24 >=> wrapPtr ActionNamed)
    wrappedPtrFree = Just ptr_to_g_free

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

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


-- | A convenience alias for `Nothing` :: `Maybe` `ActionNamed`.
noActionNamed :: Maybe ActionNamed
noActionNamed = Nothing

{- |
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' actionNamed #type
@
-}
getActionNamedType :: MonadIO m => ActionNamed -> m Poppler.Enums.ActionType
getActionNamedType s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 0) :: IO CUInt
    let val' = (toEnum . fromIntegral) val
    return 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' actionNamed [ #type 'Data.GI.Base.Attributes.:=' value ]
@
-}
setActionNamedType :: MonadIO m => ActionNamed -> Poppler.Enums.ActionType -> m ()
setActionNamedType s val = liftIO $ withManagedPtr s $ \ptr -> do
    let val' = (fromIntegral . fromEnum) val
    poke (ptr `plusPtr` 0) (val' :: CUInt)

#if ENABLE_OVERLOADING
data ActionNamedTypeFieldInfo
instance AttrInfo ActionNamedTypeFieldInfo where
    type AttrAllowedOps ActionNamedTypeFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint ActionNamedTypeFieldInfo = (~) Poppler.Enums.ActionType
    type AttrBaseTypeConstraint ActionNamedTypeFieldInfo = (~) ActionNamed
    type AttrGetType ActionNamedTypeFieldInfo = Poppler.Enums.ActionType
    type AttrLabel ActionNamedTypeFieldInfo = "type"
    type AttrOrigin ActionNamedTypeFieldInfo = ActionNamed
    attrGet _ = getActionNamedType
    attrSet _ = setActionNamedType
    attrConstruct = undefined
    attrClear _ = undefined

actionNamed_type :: AttrLabelProxy "type"
actionNamed_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' actionNamed #title
@
-}
getActionNamedTitle :: MonadIO m => ActionNamed -> m (Maybe T.Text)
getActionNamedTitle 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

{- |
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' actionNamed [ #title 'Data.GI.Base.Attributes.:=' value ]
@
-}
setActionNamedTitle :: MonadIO m => ActionNamed -> CString -> m ()
setActionNamedTitle s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 8) (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
@
-}
clearActionNamedTitle :: MonadIO m => ActionNamed -> m ()
clearActionNamedTitle s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 8) (FP.nullPtr :: CString)

#if ENABLE_OVERLOADING
data ActionNamedTitleFieldInfo
instance AttrInfo ActionNamedTitleFieldInfo where
    type AttrAllowedOps ActionNamedTitleFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint ActionNamedTitleFieldInfo = (~) CString
    type AttrBaseTypeConstraint ActionNamedTitleFieldInfo = (~) ActionNamed
    type AttrGetType ActionNamedTitleFieldInfo = Maybe T.Text
    type AttrLabel ActionNamedTitleFieldInfo = "title"
    type AttrOrigin ActionNamedTitleFieldInfo = ActionNamed
    attrGet _ = getActionNamedTitle
    attrSet _ = setActionNamedTitle
    attrConstruct = undefined
    attrClear _ = clearActionNamedTitle

actionNamed_title :: AttrLabelProxy "title"
actionNamed_title = AttrLabelProxy

#endif


{- |
Get the value of the “@named_dest@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.get' actionNamed #namedDest
@
-}
getActionNamedNamedDest :: MonadIO m => ActionNamed -> m (Maybe T.Text)
getActionNamedNamedDest s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 16) :: IO CString
    result <- SP.convertIfNonNull val $ \val' -> do
        val'' <- cstringToText val'
        return val''
    return result

{- |
Set the value of the “@named_dest@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.set' actionNamed [ #namedDest 'Data.GI.Base.Attributes.:=' value ]
@
-}
setActionNamedNamedDest :: MonadIO m => ActionNamed -> CString -> m ()
setActionNamedNamedDest s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 16) (val :: CString)

{- |
Set the value of the “@named_dest@” 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' #namedDest
@
-}
clearActionNamedNamedDest :: MonadIO m => ActionNamed -> m ()
clearActionNamedNamedDest s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 16) (FP.nullPtr :: CString)

#if ENABLE_OVERLOADING
data ActionNamedNamedDestFieldInfo
instance AttrInfo ActionNamedNamedDestFieldInfo where
    type AttrAllowedOps ActionNamedNamedDestFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint ActionNamedNamedDestFieldInfo = (~) CString
    type AttrBaseTypeConstraint ActionNamedNamedDestFieldInfo = (~) ActionNamed
    type AttrGetType ActionNamedNamedDestFieldInfo = Maybe T.Text
    type AttrLabel ActionNamedNamedDestFieldInfo = "named_dest"
    type AttrOrigin ActionNamedNamedDestFieldInfo = ActionNamed
    attrGet _ = getActionNamedNamedDest
    attrSet _ = setActionNamedNamedDest
    attrConstruct = undefined
    attrClear _ = clearActionNamedNamedDest

actionNamed_namedDest :: AttrLabelProxy "namedDest"
actionNamed_namedDest = AttrLabelProxy

#endif



#if ENABLE_OVERLOADING
instance O.HasAttributeList ActionNamed
type instance O.AttributeList ActionNamed = ActionNamedAttributeList
type ActionNamedAttributeList = ('[ '("type", ActionNamedTypeFieldInfo), '("title", ActionNamedTitleFieldInfo), '("namedDest", ActionNamedNamedDestFieldInfo)] :: [(Symbol, *)])
#endif

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

instance (info ~ ResolveActionNamedMethod t ActionNamed, O.MethodInfo info ActionNamed p) => OL.IsLabel t (ActionNamed -> 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