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

A 'GI.Poppler.Structs.AnnotMapping.AnnotMapping' structure represents the location
of /@annot@/ on the page
-}

module GI.Poppler.Structs.AnnotMapping
    ( 

-- * Exported types
    AnnotMapping(..)                        ,
    newZeroAnnotMapping                     ,
    noAnnotMapping                          ,


 -- * Methods
-- ** copy #method:copy#
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    AnnotMappingCopyMethodInfo              ,
#endif
    annotMappingCopy                        ,


-- ** free #method:free#
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    AnnotMappingFreeMethodInfo              ,
#endif
    annotMappingFree                        ,


-- ** new #method:new#
    annotMappingNew                         ,




 -- * Properties
-- ** annot #attr:annot#
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    annotMapping_annot                      ,
#endif
    clearAnnotMappingAnnot                  ,
    getAnnotMappingAnnot                    ,
    setAnnotMappingAnnot                    ,


-- ** area #attr:area#
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    annotMapping_area                       ,
#endif
    getAnnotMappingArea                     ,




    ) 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.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
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 {-# SOURCE #-} qualified GI.Poppler.Objects.Annot as Poppler.Annot
import {-# SOURCE #-} qualified GI.Poppler.Structs.Rectangle as Poppler.Rectangle

newtype AnnotMapping = AnnotMapping (ManagedPtr AnnotMapping)
foreign import ccall "poppler_annot_mapping_get_type" c_poppler_annot_mapping_get_type :: 
    IO GType

instance BoxedObject AnnotMapping where
    boxedType _ = c_poppler_annot_mapping_get_type

-- | Construct a `AnnotMapping` struct initialized to zero.
newZeroAnnotMapping :: MonadIO m => m AnnotMapping
newZeroAnnotMapping = liftIO $ callocBoxedBytes 40 >>= wrapBoxed AnnotMapping

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


noAnnotMapping :: Maybe AnnotMapping
noAnnotMapping = Nothing

getAnnotMappingArea :: MonadIO m => AnnotMapping -> m Poppler.Rectangle.Rectangle
getAnnotMappingArea s = liftIO $ withManagedPtr s $ \ptr -> do
    let val = ptr `plusPtr` 0 :: (Ptr Poppler.Rectangle.Rectangle)
    val' <- (newBoxed Poppler.Rectangle.Rectangle) val
    return val'

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data AnnotMappingAreaFieldInfo
instance AttrInfo AnnotMappingAreaFieldInfo where
    type AttrAllowedOps AnnotMappingAreaFieldInfo = '[ 'AttrGet]
    type AttrSetTypeConstraint AnnotMappingAreaFieldInfo = (~) (Ptr Poppler.Rectangle.Rectangle)
    type AttrBaseTypeConstraint AnnotMappingAreaFieldInfo = (~) AnnotMapping
    type AttrGetType AnnotMappingAreaFieldInfo = Poppler.Rectangle.Rectangle
    type AttrLabel AnnotMappingAreaFieldInfo = "area"
    type AttrOrigin AnnotMappingAreaFieldInfo = AnnotMapping
    attrGet _ = getAnnotMappingArea
    attrSet _ = undefined
    attrConstruct = undefined
    attrClear _ = undefined

annotMapping_area :: AttrLabelProxy "area"
annotMapping_area = AttrLabelProxy

#endif


getAnnotMappingAnnot :: MonadIO m => AnnotMapping -> m (Maybe Poppler.Annot.Annot)
getAnnotMappingAnnot s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 32) :: IO (Ptr Poppler.Annot.Annot)
    result <- SP.convertIfNonNull val $ \val' -> do
        val'' <- (newObject Poppler.Annot.Annot) val'
        return val''
    return result

setAnnotMappingAnnot :: MonadIO m => AnnotMapping -> Ptr Poppler.Annot.Annot -> m ()
setAnnotMappingAnnot s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 32) (val :: Ptr Poppler.Annot.Annot)

clearAnnotMappingAnnot :: MonadIO m => AnnotMapping -> m ()
clearAnnotMappingAnnot s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 32) (FP.nullPtr :: Ptr Poppler.Annot.Annot)

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data AnnotMappingAnnotFieldInfo
instance AttrInfo AnnotMappingAnnotFieldInfo where
    type AttrAllowedOps AnnotMappingAnnotFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint AnnotMappingAnnotFieldInfo = (~) (Ptr Poppler.Annot.Annot)
    type AttrBaseTypeConstraint AnnotMappingAnnotFieldInfo = (~) AnnotMapping
    type AttrGetType AnnotMappingAnnotFieldInfo = Maybe Poppler.Annot.Annot
    type AttrLabel AnnotMappingAnnotFieldInfo = "annot"
    type AttrOrigin AnnotMappingAnnotFieldInfo = AnnotMapping
    attrGet _ = getAnnotMappingAnnot
    attrSet _ = setAnnotMappingAnnot
    attrConstruct = undefined
    attrClear _ = clearAnnotMappingAnnot

annotMapping_annot :: AttrLabelProxy "annot"
annotMapping_annot = AttrLabelProxy

#endif



#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
instance O.HasAttributeList AnnotMapping
type instance O.AttributeList AnnotMapping = AnnotMappingAttributeList
type AnnotMappingAttributeList = ('[ '("area", AnnotMappingAreaFieldInfo), '("annot", AnnotMappingAnnotFieldInfo)] :: [(Symbol, *)])
#endif

-- method AnnotMapping::new
-- method type : Constructor
-- Args : []
-- Lengths : []
-- returnType : Just (TInterface (Name {namespace = "Poppler", name = "AnnotMapping"}))
-- throws : False
-- Skip return : False

foreign import ccall "poppler_annot_mapping_new" poppler_annot_mapping_new :: 
    IO (Ptr AnnotMapping)

{- |
Creates a new 'GI.Poppler.Structs.AnnotMapping.AnnotMapping'
-}
annotMappingNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m AnnotMapping
    {- ^ __Returns:__ a new 'GI.Poppler.Structs.AnnotMapping.AnnotMapping', use 'GI.Poppler.Structs.AnnotMapping.annotMappingFree' to free it -}
annotMappingNew  = liftIO $ do
    result <- poppler_annot_mapping_new
    checkUnexpectedReturnNULL "annotMappingNew" result
    result' <- (wrapBoxed AnnotMapping) result
    return result'

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
#endif

-- method AnnotMapping::copy
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "mapping", argType = TInterface (Name {namespace = "Poppler", name = "AnnotMapping"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #PopplerAnnotMapping to copy", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TInterface (Name {namespace = "Poppler", name = "AnnotMapping"}))
-- throws : False
-- Skip return : False

foreign import ccall "poppler_annot_mapping_copy" poppler_annot_mapping_copy :: 
    Ptr AnnotMapping ->                     -- mapping : TInterface (Name {namespace = "Poppler", name = "AnnotMapping"})
    IO (Ptr AnnotMapping)

{- |
Creates a copy of /@mapping@/
-}
annotMappingCopy ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AnnotMapping
    {- ^ /@mapping@/: a 'GI.Poppler.Structs.AnnotMapping.AnnotMapping' to copy -}
    -> m AnnotMapping
    {- ^ __Returns:__ a new allocated copy of /@mapping@/ -}
annotMappingCopy mapping = liftIO $ do
    mapping' <- unsafeManagedPtrGetPtr mapping
    result <- poppler_annot_mapping_copy mapping'
    checkUnexpectedReturnNULL "annotMappingCopy" result
    result' <- (wrapBoxed AnnotMapping) result
    touchManagedPtr mapping
    return result'

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data AnnotMappingCopyMethodInfo
instance (signature ~ (m AnnotMapping), MonadIO m) => O.MethodInfo AnnotMappingCopyMethodInfo AnnotMapping signature where
    overloadedMethod _ = annotMappingCopy

#endif

-- method AnnotMapping::free
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "mapping", argType = TInterface (Name {namespace = "Poppler", name = "AnnotMapping"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #PopplerAnnotMapping", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Nothing
-- throws : False
-- Skip return : False

foreign import ccall "poppler_annot_mapping_free" poppler_annot_mapping_free :: 
    Ptr AnnotMapping ->                     -- mapping : TInterface (Name {namespace = "Poppler", name = "AnnotMapping"})
    IO ()

{- |
Frees the given 'GI.Poppler.Structs.AnnotMapping.AnnotMapping'
-}
annotMappingFree ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AnnotMapping
    {- ^ /@mapping@/: a 'GI.Poppler.Structs.AnnotMapping.AnnotMapping' -}
    -> m ()
annotMappingFree mapping = liftIO $ do
    mapping' <- unsafeManagedPtrGetPtr mapping
    poppler_annot_mapping_free mapping'
    touchManagedPtr mapping
    return ()

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data AnnotMappingFreeMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo AnnotMappingFreeMethodInfo AnnotMapping signature where
    overloadedMethod _ = annotMappingFree

#endif

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
type family ResolveAnnotMappingMethod (t :: Symbol) (o :: *) :: * where
    ResolveAnnotMappingMethod "copy" o = AnnotMappingCopyMethodInfo
    ResolveAnnotMappingMethod "free" o = AnnotMappingFreeMethodInfo
    ResolveAnnotMappingMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveAnnotMappingMethod t AnnotMapping, O.MethodInfo info AnnotMapping p) => O.IsLabelProxy t (AnnotMapping -> p) where
    fromLabelProxy _ = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)

#if MIN_VERSION_base(4,9,0)
instance (info ~ ResolveAnnotMappingMethod t AnnotMapping, O.MethodInfo info AnnotMapping p) => O.IsLabel t (AnnotMapping -> 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

#endif