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

-- * Exported types
    ActionAny(..)                           ,
    newZeroActionAny                        ,
    noActionAny                             ,


 -- * Properties
-- ** title #attr:title#
{- | /No description available in the introspection data./
-}
#if ENABLE_OVERLOADING
    actionAny_title                         ,
#endif
    clearActionAnyTitle                     ,
    getActionAnyTitle                       ,
    setActionAnyTitle                       ,


-- ** type #attr:type#
{- | /No description available in the introspection data./
-}
#if ENABLE_OVERLOADING
    actionAny_type                          ,
#endif
    getActionAnyType                        ,
    setActionAnyType                        ,




    ) 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 ActionAny = ActionAny (ManagedPtr ActionAny)
instance WrappedPtr ActionAny where
    wrappedPtrCalloc = callocBytes 16
    wrappedPtrCopy = \p -> withManagedPtr p (copyBytes 16 >=> wrapPtr ActionAny)
    wrappedPtrFree = Just ptr_to_g_free

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

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


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

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

actionAny_type :: AttrLabelProxy "type"
actionAny_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' actionAny #title
@
-}
getActionAnyTitle :: MonadIO m => ActionAny -> m (Maybe T.Text)
getActionAnyTitle 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' actionAny [ #title 'Data.GI.Base.Attributes.:=' value ]
@
-}
setActionAnyTitle :: MonadIO m => ActionAny -> CString -> m ()
setActionAnyTitle 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
@
-}
clearActionAnyTitle :: MonadIO m => ActionAny -> m ()
clearActionAnyTitle s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 8) (FP.nullPtr :: CString)

#if ENABLE_OVERLOADING
data ActionAnyTitleFieldInfo
instance AttrInfo ActionAnyTitleFieldInfo where
    type AttrAllowedOps ActionAnyTitleFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint ActionAnyTitleFieldInfo = (~) CString
    type AttrBaseTypeConstraint ActionAnyTitleFieldInfo = (~) ActionAny
    type AttrGetType ActionAnyTitleFieldInfo = Maybe T.Text
    type AttrLabel ActionAnyTitleFieldInfo = "title"
    type AttrOrigin ActionAnyTitleFieldInfo = ActionAny
    attrGet _ = getActionAnyTitle
    attrSet _ = setActionAnyTitle
    attrConstruct = undefined
    attrClear _ = clearActionAnyTitle

actionAny_title :: AttrLabelProxy "title"
actionAny_title = AttrLabelProxy

#endif



#if ENABLE_OVERLOADING
instance O.HasAttributeList ActionAny
type instance O.AttributeList ActionAny = ActionAnyAttributeList
type ActionAnyAttributeList = ('[ '("type", ActionAnyTypeFieldInfo), '("title", ActionAnyTitleFieldInfo)] :: [(Symbol, *)])
#endif

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

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