{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- Action to perform over a list of layers

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

module GI.Poppler.Structs.ActionLayer
    ( 

-- * Exported types
    ActionLayer(..)                         ,
    newZeroActionLayer                      ,


 -- * Methods
-- ** Overloaded methods #method:Overloaded methods#

#if defined(ENABLE_OVERLOADING)
    ResolveActionLayerMethod                ,
#endif




 -- * Properties
-- ** action #attr:action#
-- | a t'GI.Poppler.Enums.ActionLayerAction'

#if defined(ENABLE_OVERLOADING)
    actionLayer_action                      ,
#endif
    getActionLayerAction                    ,
    setActionLayerAction                    ,


-- ** layers #attr:layers#
-- | list of t'GI.Poppler.Objects.Layer.Layer's

#if defined(ENABLE_OVERLOADING)
    actionLayer_layers                      ,
#endif
    clearActionLayerLayers                  ,
    getActionLayerLayers                    ,
    setActionLayerLayers                    ,




    ) 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.BasicTypes as B.Types
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.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
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 ActionLayer = ActionLayer (SP.ManagedPtr ActionLayer)
    deriving (ActionLayer -> ActionLayer -> Bool
(ActionLayer -> ActionLayer -> Bool)
-> (ActionLayer -> ActionLayer -> Bool) -> Eq ActionLayer
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ActionLayer -> ActionLayer -> Bool
$c/= :: ActionLayer -> ActionLayer -> Bool
== :: ActionLayer -> ActionLayer -> Bool
$c== :: ActionLayer -> ActionLayer -> Bool
Eq)

instance SP.ManagedPtrNewtype ActionLayer where
    toManagedPtr :: ActionLayer -> ManagedPtr ActionLayer
toManagedPtr (ActionLayer ManagedPtr ActionLayer
p) = ManagedPtr ActionLayer
p

instance BoxedPtr ActionLayer where
    boxedPtrCopy :: ActionLayer -> IO ActionLayer
boxedPtrCopy = \ActionLayer
p -> ActionLayer
-> (Ptr ActionLayer -> IO ActionLayer) -> IO ActionLayer
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr ActionLayer
p (Int -> Ptr ActionLayer -> IO (Ptr ActionLayer)
forall a. (HasCallStack, CallocPtr a) => Int -> Ptr a -> IO (Ptr a)
copyBytes Int
16 (Ptr ActionLayer -> IO (Ptr ActionLayer))
-> (Ptr ActionLayer -> IO ActionLayer)
-> Ptr ActionLayer
-> IO ActionLayer
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (ManagedPtr ActionLayer -> ActionLayer)
-> Ptr ActionLayer -> IO ActionLayer
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.wrapPtr ManagedPtr ActionLayer -> ActionLayer
ActionLayer)
    boxedPtrFree :: ActionLayer -> IO ()
boxedPtrFree = \ActionLayer
x -> ActionLayer -> (Ptr ActionLayer -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
SP.withManagedPtr ActionLayer
x Ptr ActionLayer -> IO ()
forall a. Ptr a -> IO ()
SP.freeMem
instance CallocPtr ActionLayer where
    boxedPtrCalloc :: IO (Ptr ActionLayer)
boxedPtrCalloc = Int -> IO (Ptr ActionLayer)
forall a. Int -> IO (Ptr a)
callocBytes Int
16


-- | Construct a `ActionLayer` struct initialized to zero.
newZeroActionLayer :: MonadIO m => m ActionLayer
newZeroActionLayer :: m ActionLayer
newZeroActionLayer = IO ActionLayer -> m ActionLayer
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ActionLayer -> m ActionLayer)
-> IO ActionLayer -> m ActionLayer
forall a b. (a -> b) -> a -> b
$ IO (Ptr ActionLayer)
forall a. CallocPtr a => IO (Ptr a)
boxedPtrCalloc IO (Ptr ActionLayer)
-> (Ptr ActionLayer -> IO ActionLayer) -> IO ActionLayer
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr ActionLayer -> ActionLayer)
-> Ptr ActionLayer -> IO ActionLayer
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr ActionLayer -> ActionLayer
ActionLayer

instance tag ~ 'AttrSet => Constructible ActionLayer tag where
    new :: (ManagedPtr ActionLayer -> ActionLayer)
-> [AttrOp ActionLayer tag] -> m ActionLayer
new ManagedPtr ActionLayer -> ActionLayer
_ [AttrOp ActionLayer tag]
attrs = do
        ActionLayer
o <- m ActionLayer
forall (m :: * -> *). MonadIO m => m ActionLayer
newZeroActionLayer
        ActionLayer -> [AttrOp ActionLayer 'AttrSet] -> m ()
forall o (m :: * -> *).
MonadIO m =>
o -> [AttrOp o 'AttrSet] -> m ()
GI.Attributes.set ActionLayer
o [AttrOp ActionLayer tag]
[AttrOp ActionLayer 'AttrSet]
attrs
        ActionLayer -> m ActionLayer
forall (m :: * -> *) a. Monad m => a -> m a
return ActionLayer
o


-- | Get the value of the “@action@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' actionLayer #action
-- @
getActionLayerAction :: MonadIO m => ActionLayer -> m Poppler.Enums.ActionLayerAction
getActionLayerAction :: ActionLayer -> m ActionLayerAction
getActionLayerAction ActionLayer
s = IO ActionLayerAction -> m ActionLayerAction
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ActionLayerAction -> m ActionLayerAction)
-> IO ActionLayerAction -> m ActionLayerAction
forall a b. (a -> b) -> a -> b
$ ActionLayer
-> (Ptr ActionLayer -> IO ActionLayerAction)
-> IO ActionLayerAction
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr ActionLayer
s ((Ptr ActionLayer -> IO ActionLayerAction) -> IO ActionLayerAction)
-> (Ptr ActionLayer -> IO ActionLayerAction)
-> IO ActionLayerAction
forall a b. (a -> b) -> a -> b
$ \Ptr ActionLayer
ptr -> do
    CUInt
val <- Ptr CUInt -> IO CUInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr ActionLayer
ptr Ptr ActionLayer -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) :: IO CUInt
    let val' :: ActionLayerAction
val' = (Int -> ActionLayerAction
forall a. Enum a => Int -> a
toEnum (Int -> ActionLayerAction)
-> (CUInt -> Int) -> CUInt -> ActionLayerAction
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
val
    ActionLayerAction -> IO ActionLayerAction
forall (m :: * -> *) a. Monad m => a -> m a
return ActionLayerAction
val'

-- | Set the value of the “@action@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' actionLayer [ #action 'Data.GI.Base.Attributes.:=' value ]
-- @
setActionLayerAction :: MonadIO m => ActionLayer -> Poppler.Enums.ActionLayerAction -> m ()
setActionLayerAction :: ActionLayer -> ActionLayerAction -> m ()
setActionLayerAction ActionLayer
s ActionLayerAction
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ ActionLayer -> (Ptr ActionLayer -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr ActionLayer
s ((Ptr ActionLayer -> IO ()) -> IO ())
-> (Ptr ActionLayer -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr ActionLayer
ptr -> do
    let val' :: CUInt
val' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (ActionLayerAction -> Int) -> ActionLayerAction -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ActionLayerAction -> Int
forall a. Enum a => a -> Int
fromEnum) ActionLayerAction
val
    Ptr CUInt -> CUInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ActionLayer
ptr Ptr ActionLayer -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) (CUInt
val' :: CUInt)

#if defined(ENABLE_OVERLOADING)
data ActionLayerActionFieldInfo
instance AttrInfo ActionLayerActionFieldInfo where
    type AttrBaseTypeConstraint ActionLayerActionFieldInfo = (~) ActionLayer
    type AttrAllowedOps ActionLayerActionFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint ActionLayerActionFieldInfo = (~) Poppler.Enums.ActionLayerAction
    type AttrTransferTypeConstraint ActionLayerActionFieldInfo = (~)Poppler.Enums.ActionLayerAction
    type AttrTransferType ActionLayerActionFieldInfo = Poppler.Enums.ActionLayerAction
    type AttrGetType ActionLayerActionFieldInfo = Poppler.Enums.ActionLayerAction
    type AttrLabel ActionLayerActionFieldInfo = "action"
    type AttrOrigin ActionLayerActionFieldInfo = ActionLayer
    attrGet = getActionLayerAction
    attrSet = setActionLayerAction
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

actionLayer_action :: AttrLabelProxy "action"
actionLayer_action = AttrLabelProxy

#endif


-- | Get the value of the “@layers@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' actionLayer #layers
-- @
getActionLayerLayers :: MonadIO m => ActionLayer -> m ([Ptr ()])
getActionLayerLayers :: ActionLayer -> m [Ptr ()]
getActionLayerLayers ActionLayer
s = IO [Ptr ()] -> m [Ptr ()]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Ptr ()] -> m [Ptr ()]) -> IO [Ptr ()] -> m [Ptr ()]
forall a b. (a -> b) -> a -> b
$ ActionLayer -> (Ptr ActionLayer -> IO [Ptr ()]) -> IO [Ptr ()]
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr ActionLayer
s ((Ptr ActionLayer -> IO [Ptr ()]) -> IO [Ptr ()])
-> (Ptr ActionLayer -> IO [Ptr ()]) -> IO [Ptr ()]
forall a b. (a -> b) -> a -> b
$ \Ptr ActionLayer
ptr -> do
    Ptr (GList (Ptr ()))
val <- Ptr (Ptr (GList (Ptr ()))) -> IO (Ptr (GList (Ptr ())))
forall a. Storable a => Ptr a -> IO a
peek (Ptr ActionLayer
ptr Ptr ActionLayer -> Int -> Ptr (Ptr (GList (Ptr ())))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) :: IO (Ptr (GList (Ptr ())))
    [Ptr ()]
val' <- Ptr (GList (Ptr ())) -> IO [Ptr ()]
forall a. Ptr (GList (Ptr a)) -> IO [Ptr a]
unpackGList Ptr (GList (Ptr ()))
val
    [Ptr ()] -> IO [Ptr ()]
forall (m :: * -> *) a. Monad m => a -> m a
return [Ptr ()]
val'

-- | Set the value of the “@layers@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' actionLayer [ #layers 'Data.GI.Base.Attributes.:=' value ]
-- @
setActionLayerLayers :: MonadIO m => ActionLayer -> Ptr (GList (Ptr ())) -> m ()
setActionLayerLayers :: ActionLayer -> Ptr (GList (Ptr ())) -> m ()
setActionLayerLayers ActionLayer
s Ptr (GList (Ptr ()))
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ ActionLayer -> (Ptr ActionLayer -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr ActionLayer
s ((Ptr ActionLayer -> IO ()) -> IO ())
-> (Ptr ActionLayer -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr ActionLayer
ptr -> do
    Ptr (Ptr (GList (Ptr ()))) -> Ptr (GList (Ptr ())) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ActionLayer
ptr Ptr ActionLayer -> Int -> Ptr (Ptr (GList (Ptr ())))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) (Ptr (GList (Ptr ()))
val :: Ptr (GList (Ptr ())))

-- | Set the value of the “@layers@” 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' #layers
-- @
clearActionLayerLayers :: MonadIO m => ActionLayer -> m ()
clearActionLayerLayers :: ActionLayer -> m ()
clearActionLayerLayers ActionLayer
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ ActionLayer -> (Ptr ActionLayer -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr ActionLayer
s ((Ptr ActionLayer -> IO ()) -> IO ())
-> (Ptr ActionLayer -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr ActionLayer
ptr -> do
    Ptr (Ptr (GList (Ptr ()))) -> Ptr (GList (Ptr ())) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ActionLayer
ptr Ptr ActionLayer -> Int -> Ptr (Ptr (GList (Ptr ())))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) (Ptr (GList (Ptr ()))
forall a. Ptr a
FP.nullPtr :: Ptr (GList (Ptr ())))

#if defined(ENABLE_OVERLOADING)
data ActionLayerLayersFieldInfo
instance AttrInfo ActionLayerLayersFieldInfo where
    type AttrBaseTypeConstraint ActionLayerLayersFieldInfo = (~) ActionLayer
    type AttrAllowedOps ActionLayerLayersFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint ActionLayerLayersFieldInfo = (~) (Ptr (GList (Ptr ())))
    type AttrTransferTypeConstraint ActionLayerLayersFieldInfo = (~)(Ptr (GList (Ptr ())))
    type AttrTransferType ActionLayerLayersFieldInfo = (Ptr (GList (Ptr ())))
    type AttrGetType ActionLayerLayersFieldInfo = [Ptr ()]
    type AttrLabel ActionLayerLayersFieldInfo = "layers"
    type AttrOrigin ActionLayerLayersFieldInfo = ActionLayer
    attrGet = getActionLayerLayers
    attrSet = setActionLayerLayers
    attrConstruct = undefined
    attrClear = clearActionLayerLayers
    attrTransfer _ v = do
        return v

actionLayer_layers :: AttrLabelProxy "layers"
actionLayer_layers = AttrLabelProxy

#endif



#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList ActionLayer
type instance O.AttributeList ActionLayer = ActionLayerAttributeList
type ActionLayerAttributeList = ('[ '("action", ActionLayerActionFieldInfo), '("layers", ActionLayerLayersFieldInfo)] :: [(Symbol, *)])
#endif

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

instance (info ~ ResolveActionLayerMethod t ActionLayer, O.MethodInfo info ActionLayer p) => OL.IsLabel t (ActionLayer -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif

#endif