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

-- * Exported types
    ActionMovie(..)                         ,
    newZeroActionMovie                      ,
    noActionMovie                           ,


 -- * Properties
-- ** movie #attr:movie#
{- | /No description available in the introspection data./
-}
#if ENABLE_OVERLOADING
    actionMovie_movie                       ,
#endif
    clearActionMovieMovie                   ,
    getActionMovieMovie                     ,
    setActionMovieMovie                     ,


-- ** operation #attr:operation#
{- | /No description available in the introspection data./
-}
#if ENABLE_OVERLOADING
    actionMovie_operation                   ,
#endif
    getActionMovieOperation                 ,
    setActionMovieOperation                 ,


-- ** title #attr:title#
{- | /No description available in the introspection data./
-}
#if ENABLE_OVERLOADING
    actionMovie_title                       ,
#endif
    clearActionMovieTitle                   ,
    getActionMovieTitle                     ,
    setActionMovieTitle                     ,


-- ** type #attr:type#
{- | /No description available in the introspection data./
-}
#if ENABLE_OVERLOADING
    actionMovie_type                        ,
#endif
    getActionMovieType                      ,
    setActionMovieType                      ,




    ) 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.Objects.Movie as Poppler.Movie

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

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

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


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

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

actionMovie_type :: AttrLabelProxy "type"
actionMovie_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' actionMovie #title
@
-}
getActionMovieTitle :: MonadIO m => ActionMovie -> m (Maybe T.Text)
getActionMovieTitle 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' actionMovie [ #title 'Data.GI.Base.Attributes.:=' value ]
@
-}
setActionMovieTitle :: MonadIO m => ActionMovie -> CString -> m ()
setActionMovieTitle 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
@
-}
clearActionMovieTitle :: MonadIO m => ActionMovie -> m ()
clearActionMovieTitle s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 8) (FP.nullPtr :: CString)

#if ENABLE_OVERLOADING
data ActionMovieTitleFieldInfo
instance AttrInfo ActionMovieTitleFieldInfo where
    type AttrAllowedOps ActionMovieTitleFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint ActionMovieTitleFieldInfo = (~) CString
    type AttrBaseTypeConstraint ActionMovieTitleFieldInfo = (~) ActionMovie
    type AttrGetType ActionMovieTitleFieldInfo = Maybe T.Text
    type AttrLabel ActionMovieTitleFieldInfo = "title"
    type AttrOrigin ActionMovieTitleFieldInfo = ActionMovie
    attrGet _ = getActionMovieTitle
    attrSet _ = setActionMovieTitle
    attrConstruct = undefined
    attrClear _ = clearActionMovieTitle

actionMovie_title :: AttrLabelProxy "title"
actionMovie_title = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' actionMovie #operation
@
-}
getActionMovieOperation :: MonadIO m => ActionMovie -> m Poppler.Enums.ActionMovieOperation
getActionMovieOperation s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 16) :: IO CUInt
    let val' = (toEnum . fromIntegral) val
    return val'

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

@
'Data.GI.Base.Attributes.set' actionMovie [ #operation 'Data.GI.Base.Attributes.:=' value ]
@
-}
setActionMovieOperation :: MonadIO m => ActionMovie -> Poppler.Enums.ActionMovieOperation -> m ()
setActionMovieOperation s val = liftIO $ withManagedPtr s $ \ptr -> do
    let val' = (fromIntegral . fromEnum) val
    poke (ptr `plusPtr` 16) (val' :: CUInt)

#if ENABLE_OVERLOADING
data ActionMovieOperationFieldInfo
instance AttrInfo ActionMovieOperationFieldInfo where
    type AttrAllowedOps ActionMovieOperationFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint ActionMovieOperationFieldInfo = (~) Poppler.Enums.ActionMovieOperation
    type AttrBaseTypeConstraint ActionMovieOperationFieldInfo = (~) ActionMovie
    type AttrGetType ActionMovieOperationFieldInfo = Poppler.Enums.ActionMovieOperation
    type AttrLabel ActionMovieOperationFieldInfo = "operation"
    type AttrOrigin ActionMovieOperationFieldInfo = ActionMovie
    attrGet _ = getActionMovieOperation
    attrSet _ = setActionMovieOperation
    attrConstruct = undefined
    attrClear _ = undefined

actionMovie_operation :: AttrLabelProxy "operation"
actionMovie_operation = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' actionMovie #movie
@
-}
getActionMovieMovie :: MonadIO m => ActionMovie -> m (Maybe Poppler.Movie.Movie)
getActionMovieMovie s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 24) :: IO (Ptr Poppler.Movie.Movie)
    result <- SP.convertIfNonNull val $ \val' -> do
        val'' <- (newObject Poppler.Movie.Movie) val'
        return val''
    return result

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

@
'Data.GI.Base.Attributes.set' actionMovie [ #movie 'Data.GI.Base.Attributes.:=' value ]
@
-}
setActionMovieMovie :: MonadIO m => ActionMovie -> Ptr Poppler.Movie.Movie -> m ()
setActionMovieMovie s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 24) (val :: Ptr Poppler.Movie.Movie)

{- |
Set the value of the “@movie@” 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' #movie
@
-}
clearActionMovieMovie :: MonadIO m => ActionMovie -> m ()
clearActionMovieMovie s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 24) (FP.nullPtr :: Ptr Poppler.Movie.Movie)

#if ENABLE_OVERLOADING
data ActionMovieMovieFieldInfo
instance AttrInfo ActionMovieMovieFieldInfo where
    type AttrAllowedOps ActionMovieMovieFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint ActionMovieMovieFieldInfo = (~) (Ptr Poppler.Movie.Movie)
    type AttrBaseTypeConstraint ActionMovieMovieFieldInfo = (~) ActionMovie
    type AttrGetType ActionMovieMovieFieldInfo = Maybe Poppler.Movie.Movie
    type AttrLabel ActionMovieMovieFieldInfo = "movie"
    type AttrOrigin ActionMovieMovieFieldInfo = ActionMovie
    attrGet _ = getActionMovieMovie
    attrSet _ = setActionMovieMovie
    attrConstruct = undefined
    attrClear _ = clearActionMovieMovie

actionMovie_movie :: AttrLabelProxy "movie"
actionMovie_movie = AttrLabelProxy

#endif



#if ENABLE_OVERLOADING
instance O.HasAttributeList ActionMovie
type instance O.AttributeList ActionMovie = ActionMovieAttributeList
type ActionMovieAttributeList = ('[ '("type", ActionMovieTypeFieldInfo), '("title", ActionMovieTitleFieldInfo), '("operation", ActionMovieOperationFieldInfo), '("movie", ActionMovieMovieFieldInfo)] :: [(Symbol, *)])
#endif

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

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