{- |
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.ActionGotoDest
    (

-- * Exported types
    ActionGotoDest(..)                      ,
    newZeroActionGotoDest                   ,
    noActionGotoDest                        ,


 -- * Properties
-- ** dest #attr:dest#
{- | /No description available in the introspection data./
-}
#if ENABLE_OVERLOADING
    actionGotoDest_dest                     ,
#endif
    clearActionGotoDestDest                 ,
    getActionGotoDestDest                   ,
    setActionGotoDestDest                   ,


-- ** title #attr:title#
{- | /No description available in the introspection data./
-}
#if ENABLE_OVERLOADING
    actionGotoDest_title                    ,
#endif
    clearActionGotoDestTitle                ,
    getActionGotoDestTitle                  ,
    setActionGotoDestTitle                  ,


-- ** type #attr:type#
{- | /No description available in the introspection data./
-}
#if ENABLE_OVERLOADING
    actionGotoDest_type                     ,
#endif
    getActionGotoDestType                   ,
    setActionGotoDestType                   ,




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

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

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

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


-- | A convenience alias for `Nothing` :: `Maybe` `ActionGotoDest`.
noActionGotoDest :: Maybe ActionGotoDest
noActionGotoDest = 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' actionGotoDest #type
@
-}
getActionGotoDestType :: MonadIO m => ActionGotoDest -> m Poppler.Enums.ActionType
getActionGotoDestType 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' actionGotoDest [ #type 'Data.GI.Base.Attributes.:=' value ]
@
-}
setActionGotoDestType :: MonadIO m => ActionGotoDest -> Poppler.Enums.ActionType -> m ()
setActionGotoDestType s val = liftIO $ withManagedPtr s $ \ptr -> do
    let val' = (fromIntegral . fromEnum) val
    poke (ptr `plusPtr` 0) (val' :: CUInt)

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

actionGotoDest_type :: AttrLabelProxy "type"
actionGotoDest_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' actionGotoDest #title
@
-}
getActionGotoDestTitle :: MonadIO m => ActionGotoDest -> m (Maybe T.Text)
getActionGotoDestTitle 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' actionGotoDest [ #title 'Data.GI.Base.Attributes.:=' value ]
@
-}
setActionGotoDestTitle :: MonadIO m => ActionGotoDest -> CString -> m ()
setActionGotoDestTitle 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
@
-}
clearActionGotoDestTitle :: MonadIO m => ActionGotoDest -> m ()
clearActionGotoDestTitle s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 8) (FP.nullPtr :: CString)

#if ENABLE_OVERLOADING
data ActionGotoDestTitleFieldInfo
instance AttrInfo ActionGotoDestTitleFieldInfo where
    type AttrAllowedOps ActionGotoDestTitleFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint ActionGotoDestTitleFieldInfo = (~) CString
    type AttrBaseTypeConstraint ActionGotoDestTitleFieldInfo = (~) ActionGotoDest
    type AttrGetType ActionGotoDestTitleFieldInfo = Maybe T.Text
    type AttrLabel ActionGotoDestTitleFieldInfo = "title"
    type AttrOrigin ActionGotoDestTitleFieldInfo = ActionGotoDest
    attrGet _ = getActionGotoDestTitle
    attrSet _ = setActionGotoDestTitle
    attrConstruct = undefined
    attrClear _ = clearActionGotoDestTitle

actionGotoDest_title :: AttrLabelProxy "title"
actionGotoDest_title = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' actionGotoDest #dest
@
-}
getActionGotoDestDest :: MonadIO m => ActionGotoDest -> m (Maybe Poppler.Dest.Dest)
getActionGotoDestDest s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 16) :: IO (Ptr Poppler.Dest.Dest)
    result <- SP.convertIfNonNull val $ \val' -> do
        val'' <- (newBoxed Poppler.Dest.Dest) val'
        return val''
    return result

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

@
'Data.GI.Base.Attributes.set' actionGotoDest [ #dest 'Data.GI.Base.Attributes.:=' value ]
@
-}
setActionGotoDestDest :: MonadIO m => ActionGotoDest -> Ptr Poppler.Dest.Dest -> m ()
setActionGotoDestDest s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 16) (val :: Ptr Poppler.Dest.Dest)

{- |
Set the value of the “@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' #dest
@
-}
clearActionGotoDestDest :: MonadIO m => ActionGotoDest -> m ()
clearActionGotoDestDest s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 16) (FP.nullPtr :: Ptr Poppler.Dest.Dest)

#if ENABLE_OVERLOADING
data ActionGotoDestDestFieldInfo
instance AttrInfo ActionGotoDestDestFieldInfo where
    type AttrAllowedOps ActionGotoDestDestFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint ActionGotoDestDestFieldInfo = (~) (Ptr Poppler.Dest.Dest)
    type AttrBaseTypeConstraint ActionGotoDestDestFieldInfo = (~) ActionGotoDest
    type AttrGetType ActionGotoDestDestFieldInfo = Maybe Poppler.Dest.Dest
    type AttrLabel ActionGotoDestDestFieldInfo = "dest"
    type AttrOrigin ActionGotoDestDestFieldInfo = ActionGotoDest
    attrGet _ = getActionGotoDestDest
    attrSet _ = setActionGotoDestDest
    attrConstruct = undefined
    attrClear _ = clearActionGotoDestDest

actionGotoDest_dest :: AttrLabelProxy "dest"
actionGotoDest_dest = AttrLabelProxy

#endif



#if ENABLE_OVERLOADING
instance O.HasAttributeList ActionGotoDest
type instance O.AttributeList ActionGotoDest = ActionGotoDestAttributeList
type ActionGotoDestAttributeList = ('[ '("type", ActionGotoDestTypeFieldInfo), '("title", ActionGotoDestTitleFieldInfo), '("dest", ActionGotoDestDestFieldInfo)] :: [(Symbol, *)])
#endif

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

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