{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- /No description available in the introspection data./

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

module GI.Poppler.Objects.AnnotFileAttachment
    ( 

-- * Exported types
    AnnotFileAttachment(..)                 ,
    IsAnnotFileAttachment                   ,
    toAnnotFileAttachment                   ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [hasPopup]("GI.Poppler.Objects.AnnotMarkup#g:method:hasPopup"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getAnnotType]("GI.Poppler.Objects.Annot#g:method:getAnnotType"), [getAttachment]("GI.Poppler.Objects.AnnotFileAttachment#g:method:getAttachment"), [getColor]("GI.Poppler.Objects.Annot#g:method:getColor"), [getContents]("GI.Poppler.Objects.Annot#g:method:getContents"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getDate]("GI.Poppler.Objects.AnnotMarkup#g:method:getDate"), [getExternalData]("GI.Poppler.Objects.AnnotMarkup#g:method:getExternalData"), [getFlags]("GI.Poppler.Objects.Annot#g:method:getFlags"), [getLabel]("GI.Poppler.Objects.AnnotMarkup#g:method:getLabel"), [getModified]("GI.Poppler.Objects.Annot#g:method:getModified"), [getName]("GI.Poppler.Objects.AnnotFileAttachment#g:method:getName"), [getOpacity]("GI.Poppler.Objects.AnnotMarkup#g:method:getOpacity"), [getPageIndex]("GI.Poppler.Objects.Annot#g:method:getPageIndex"), [getPopupIsOpen]("GI.Poppler.Objects.AnnotMarkup#g:method:getPopupIsOpen"), [getPopupRectangle]("GI.Poppler.Objects.AnnotMarkup#g:method:getPopupRectangle"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getRectangle]("GI.Poppler.Objects.Annot#g:method:getRectangle"), [getReplyTo]("GI.Poppler.Objects.AnnotMarkup#g:method:getReplyTo"), [getSubject]("GI.Poppler.Objects.AnnotMarkup#g:method:getSubject").
-- 
-- ==== Setters
-- [setColor]("GI.Poppler.Objects.Annot#g:method:setColor"), [setContents]("GI.Poppler.Objects.Annot#g:method:setContents"), [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setFlags]("GI.Poppler.Objects.Annot#g:method:setFlags"), [setLabel]("GI.Poppler.Objects.AnnotMarkup#g:method:setLabel"), [setOpacity]("GI.Poppler.Objects.AnnotMarkup#g:method:setOpacity"), [setPopup]("GI.Poppler.Objects.AnnotMarkup#g:method:setPopup"), [setPopupIsOpen]("GI.Poppler.Objects.AnnotMarkup#g:method:setPopupIsOpen"), [setPopupRectangle]("GI.Poppler.Objects.AnnotMarkup#g:method:setPopupRectangle"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setRectangle]("GI.Poppler.Objects.Annot#g:method:setRectangle").

#if defined(ENABLE_OVERLOADING)
    ResolveAnnotFileAttachmentMethod        ,
#endif

-- ** getAttachment #method:getAttachment#

#if defined(ENABLE_OVERLOADING)
    AnnotFileAttachmentGetAttachmentMethodInfo,
#endif
    annotFileAttachmentGetAttachment        ,


-- ** getName #method:getName#

#if defined(ENABLE_OVERLOADING)
    AnnotFileAttachmentGetNameMethodInfo    ,
#endif
    annotFileAttachmentGetName              ,




    ) 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.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
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.Coerce as Coerce
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 qualified GHC.Records as R

import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Poppler.Objects.Annot as Poppler.Annot
import {-# SOURCE #-} qualified GI.Poppler.Objects.AnnotMarkup as Poppler.AnnotMarkup
import {-# SOURCE #-} qualified GI.Poppler.Objects.Attachment as Poppler.Attachment

-- | Memory-managed wrapper type.
newtype AnnotFileAttachment = AnnotFileAttachment (SP.ManagedPtr AnnotFileAttachment)
    deriving (AnnotFileAttachment -> AnnotFileAttachment -> Bool
(AnnotFileAttachment -> AnnotFileAttachment -> Bool)
-> (AnnotFileAttachment -> AnnotFileAttachment -> Bool)
-> Eq AnnotFileAttachment
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AnnotFileAttachment -> AnnotFileAttachment -> Bool
== :: AnnotFileAttachment -> AnnotFileAttachment -> Bool
$c/= :: AnnotFileAttachment -> AnnotFileAttachment -> Bool
/= :: AnnotFileAttachment -> AnnotFileAttachment -> Bool
Eq)

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

foreign import ccall "poppler_annot_file_attachment_get_type"
    c_poppler_annot_file_attachment_get_type :: IO B.Types.GType

instance B.Types.TypedObject AnnotFileAttachment where
    glibType :: IO GType
glibType = IO GType
c_poppler_annot_file_attachment_get_type

instance B.Types.GObject AnnotFileAttachment

-- | Type class for types which can be safely cast to `AnnotFileAttachment`, for instance with `toAnnotFileAttachment`.
class (SP.GObject o, O.IsDescendantOf AnnotFileAttachment o) => IsAnnotFileAttachment o
instance (SP.GObject o, O.IsDescendantOf AnnotFileAttachment o) => IsAnnotFileAttachment o

instance O.HasParentTypes AnnotFileAttachment
type instance O.ParentTypes AnnotFileAttachment = '[Poppler.AnnotMarkup.AnnotMarkup, Poppler.Annot.Annot, GObject.Object.Object]

-- | Cast to `AnnotFileAttachment`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toAnnotFileAttachment :: (MIO.MonadIO m, IsAnnotFileAttachment o) => o -> m AnnotFileAttachment
toAnnotFileAttachment :: forall (m :: * -> *) o.
(MonadIO m, IsAnnotFileAttachment o) =>
o -> m AnnotFileAttachment
toAnnotFileAttachment = IO AnnotFileAttachment -> m AnnotFileAttachment
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO AnnotFileAttachment -> m AnnotFileAttachment)
-> (o -> IO AnnotFileAttachment) -> o -> m AnnotFileAttachment
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr AnnotFileAttachment -> AnnotFileAttachment)
-> o -> IO AnnotFileAttachment
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr AnnotFileAttachment -> AnnotFileAttachment
AnnotFileAttachment

-- | Convert 'AnnotFileAttachment' to and from 'Data.GI.Base.GValue.GValue'. See 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue (Maybe AnnotFileAttachment) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_poppler_annot_file_attachment_get_type
    gvalueSet_ :: Ptr GValue -> Maybe AnnotFileAttachment -> IO ()
gvalueSet_ Ptr GValue
gv Maybe AnnotFileAttachment
P.Nothing = Ptr GValue -> Ptr AnnotFileAttachment -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr AnnotFileAttachment
forall a. Ptr a
FP.nullPtr :: FP.Ptr AnnotFileAttachment)
    gvalueSet_ Ptr GValue
gv (P.Just AnnotFileAttachment
obj) = AnnotFileAttachment -> (Ptr AnnotFileAttachment -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr AnnotFileAttachment
obj (Ptr GValue -> Ptr AnnotFileAttachment -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe AnnotFileAttachment)
gvalueGet_ Ptr GValue
gv = do
        Ptr AnnotFileAttachment
ptr <- Ptr GValue -> IO (Ptr AnnotFileAttachment)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr AnnotFileAttachment)
        if Ptr AnnotFileAttachment
ptr Ptr AnnotFileAttachment -> Ptr AnnotFileAttachment -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr AnnotFileAttachment
forall a. Ptr a
FP.nullPtr
        then AnnotFileAttachment -> Maybe AnnotFileAttachment
forall a. a -> Maybe a
P.Just (AnnotFileAttachment -> Maybe AnnotFileAttachment)
-> IO AnnotFileAttachment -> IO (Maybe AnnotFileAttachment)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr AnnotFileAttachment -> AnnotFileAttachment)
-> Ptr AnnotFileAttachment -> IO AnnotFileAttachment
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr AnnotFileAttachment -> AnnotFileAttachment
AnnotFileAttachment Ptr AnnotFileAttachment
ptr
        else Maybe AnnotFileAttachment -> IO (Maybe AnnotFileAttachment)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe AnnotFileAttachment
forall a. Maybe a
P.Nothing
        
    

#if defined(ENABLE_OVERLOADING)
type family ResolveAnnotFileAttachmentMethod (t :: Symbol) (o :: *) :: * where
    ResolveAnnotFileAttachmentMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveAnnotFileAttachmentMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveAnnotFileAttachmentMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveAnnotFileAttachmentMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveAnnotFileAttachmentMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveAnnotFileAttachmentMethod "hasPopup" o = Poppler.AnnotMarkup.AnnotMarkupHasPopupMethodInfo
    ResolveAnnotFileAttachmentMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveAnnotFileAttachmentMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveAnnotFileAttachmentMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveAnnotFileAttachmentMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveAnnotFileAttachmentMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveAnnotFileAttachmentMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveAnnotFileAttachmentMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveAnnotFileAttachmentMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveAnnotFileAttachmentMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveAnnotFileAttachmentMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveAnnotFileAttachmentMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveAnnotFileAttachmentMethod "getAnnotType" o = Poppler.Annot.AnnotGetAnnotTypeMethodInfo
    ResolveAnnotFileAttachmentMethod "getAttachment" o = AnnotFileAttachmentGetAttachmentMethodInfo
    ResolveAnnotFileAttachmentMethod "getColor" o = Poppler.Annot.AnnotGetColorMethodInfo
    ResolveAnnotFileAttachmentMethod "getContents" o = Poppler.Annot.AnnotGetContentsMethodInfo
    ResolveAnnotFileAttachmentMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveAnnotFileAttachmentMethod "getDate" o = Poppler.AnnotMarkup.AnnotMarkupGetDateMethodInfo
    ResolveAnnotFileAttachmentMethod "getExternalData" o = Poppler.AnnotMarkup.AnnotMarkupGetExternalDataMethodInfo
    ResolveAnnotFileAttachmentMethod "getFlags" o = Poppler.Annot.AnnotGetFlagsMethodInfo
    ResolveAnnotFileAttachmentMethod "getLabel" o = Poppler.AnnotMarkup.AnnotMarkupGetLabelMethodInfo
    ResolveAnnotFileAttachmentMethod "getModified" o = Poppler.Annot.AnnotGetModifiedMethodInfo
    ResolveAnnotFileAttachmentMethod "getName" o = AnnotFileAttachmentGetNameMethodInfo
    ResolveAnnotFileAttachmentMethod "getOpacity" o = Poppler.AnnotMarkup.AnnotMarkupGetOpacityMethodInfo
    ResolveAnnotFileAttachmentMethod "getPageIndex" o = Poppler.Annot.AnnotGetPageIndexMethodInfo
    ResolveAnnotFileAttachmentMethod "getPopupIsOpen" o = Poppler.AnnotMarkup.AnnotMarkupGetPopupIsOpenMethodInfo
    ResolveAnnotFileAttachmentMethod "getPopupRectangle" o = Poppler.AnnotMarkup.AnnotMarkupGetPopupRectangleMethodInfo
    ResolveAnnotFileAttachmentMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveAnnotFileAttachmentMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveAnnotFileAttachmentMethod "getRectangle" o = Poppler.Annot.AnnotGetRectangleMethodInfo
    ResolveAnnotFileAttachmentMethod "getReplyTo" o = Poppler.AnnotMarkup.AnnotMarkupGetReplyToMethodInfo
    ResolveAnnotFileAttachmentMethod "getSubject" o = Poppler.AnnotMarkup.AnnotMarkupGetSubjectMethodInfo
    ResolveAnnotFileAttachmentMethod "setColor" o = Poppler.Annot.AnnotSetColorMethodInfo
    ResolveAnnotFileAttachmentMethod "setContents" o = Poppler.Annot.AnnotSetContentsMethodInfo
    ResolveAnnotFileAttachmentMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveAnnotFileAttachmentMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveAnnotFileAttachmentMethod "setFlags" o = Poppler.Annot.AnnotSetFlagsMethodInfo
    ResolveAnnotFileAttachmentMethod "setLabel" o = Poppler.AnnotMarkup.AnnotMarkupSetLabelMethodInfo
    ResolveAnnotFileAttachmentMethod "setOpacity" o = Poppler.AnnotMarkup.AnnotMarkupSetOpacityMethodInfo
    ResolveAnnotFileAttachmentMethod "setPopup" o = Poppler.AnnotMarkup.AnnotMarkupSetPopupMethodInfo
    ResolveAnnotFileAttachmentMethod "setPopupIsOpen" o = Poppler.AnnotMarkup.AnnotMarkupSetPopupIsOpenMethodInfo
    ResolveAnnotFileAttachmentMethod "setPopupRectangle" o = Poppler.AnnotMarkup.AnnotMarkupSetPopupRectangleMethodInfo
    ResolveAnnotFileAttachmentMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveAnnotFileAttachmentMethod "setRectangle" o = Poppler.Annot.AnnotSetRectangleMethodInfo
    ResolveAnnotFileAttachmentMethod l o = O.MethodResolutionFailed l o

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

#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveAnnotFileAttachmentMethod t AnnotFileAttachment, O.OverloadedMethod info AnnotFileAttachment p, R.HasField t AnnotFileAttachment p) => R.HasField t AnnotFileAttachment p where
    getField = O.overloadedMethod @info

#endif

instance (info ~ ResolveAnnotFileAttachmentMethod t AnnotFileAttachment, O.OverloadedMethodInfo info AnnotFileAttachment) => OL.IsLabel t (O.MethodProxy info AnnotFileAttachment) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif

#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList AnnotFileAttachment
type instance O.AttributeList AnnotFileAttachment = AnnotFileAttachmentAttributeList
type AnnotFileAttachmentAttributeList = ('[ ] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList AnnotFileAttachment = AnnotFileAttachmentSignalList
type AnnotFileAttachmentSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])

#endif

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

foreign import ccall "poppler_annot_file_attachment_get_attachment" poppler_annot_file_attachment_get_attachment :: 
    Ptr AnnotFileAttachment ->              -- poppler_annot : TInterface (Name {namespace = "Poppler", name = "AnnotFileAttachment"})
    IO (Ptr Poppler.Attachment.Attachment)

-- | Creates a t'GI.Poppler.Objects.Attachment.Attachment' for the file of the file attachment annotation /@annot@/.
-- The t'GI.Poppler.Objects.Attachment.Attachment' must be unrefed with g_object_unref by the caller.
-- 
-- /Since: 0.14/
annotFileAttachmentGetAttachment ::
    (B.CallStack.HasCallStack, MonadIO m, IsAnnotFileAttachment a) =>
    a
    -- ^ /@popplerAnnot@/: a t'GI.Poppler.Objects.AnnotFileAttachment.AnnotFileAttachment'
    -> m Poppler.Attachment.Attachment
    -- ^ __Returns:__ /@popplerAttachment@/
annotFileAttachmentGetAttachment :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsAnnotFileAttachment a) =>
a -> m Attachment
annotFileAttachmentGetAttachment a
popplerAnnot = IO Attachment -> m Attachment
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Attachment -> m Attachment) -> IO Attachment -> m Attachment
forall a b. (a -> b) -> a -> b
$ do
    Ptr AnnotFileAttachment
popplerAnnot' <- a -> IO (Ptr AnnotFileAttachment)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
popplerAnnot
    Ptr Attachment
result <- Ptr AnnotFileAttachment -> IO (Ptr Attachment)
poppler_annot_file_attachment_get_attachment Ptr AnnotFileAttachment
popplerAnnot'
    Text -> Ptr Attachment -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"annotFileAttachmentGetAttachment" Ptr Attachment
result
    Attachment
result' <- ((ManagedPtr Attachment -> Attachment)
-> Ptr Attachment -> IO Attachment
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Attachment -> Attachment
Poppler.Attachment.Attachment) Ptr Attachment
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
popplerAnnot
    Attachment -> IO Attachment
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Attachment
result'

#if defined(ENABLE_OVERLOADING)
data AnnotFileAttachmentGetAttachmentMethodInfo
instance (signature ~ (m Poppler.Attachment.Attachment), MonadIO m, IsAnnotFileAttachment a) => O.OverloadedMethod AnnotFileAttachmentGetAttachmentMethodInfo a signature where
    overloadedMethod = annotFileAttachmentGetAttachment

instance O.OverloadedMethodInfo AnnotFileAttachmentGetAttachmentMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Poppler.Objects.AnnotFileAttachment.annotFileAttachmentGetAttachment",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-poppler-0.18.27/docs/GI-Poppler-Objects-AnnotFileAttachment.html#v:annotFileAttachmentGetAttachment"
        })


#endif

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

foreign import ccall "poppler_annot_file_attachment_get_name" poppler_annot_file_attachment_get_name :: 
    Ptr AnnotFileAttachment ->              -- poppler_annot : TInterface (Name {namespace = "Poppler", name = "AnnotFileAttachment"})
    IO CString

-- | Retrieves the name of /@popplerAnnot@/.
-- 
-- /Since: 0.14/
annotFileAttachmentGetName ::
    (B.CallStack.HasCallStack, MonadIO m, IsAnnotFileAttachment a) =>
    a
    -- ^ /@popplerAnnot@/: a t'GI.Poppler.Objects.AnnotFileAttachment.AnnotFileAttachment'
    -> m T.Text
    -- ^ __Returns:__ a new allocated string with the name of /@popplerAnnot@/. It must
    --               be freed with 'GI.GLib.Functions.free' when done.
annotFileAttachmentGetName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsAnnotFileAttachment a) =>
a -> m Text
annotFileAttachmentGetName a
popplerAnnot = IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr AnnotFileAttachment
popplerAnnot' <- a -> IO (Ptr AnnotFileAttachment)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
popplerAnnot
    CString
result <- Ptr AnnotFileAttachment -> IO CString
poppler_annot_file_attachment_get_name Ptr AnnotFileAttachment
popplerAnnot'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"annotFileAttachmentGetName" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
popplerAnnot
    Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data AnnotFileAttachmentGetNameMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsAnnotFileAttachment a) => O.OverloadedMethod AnnotFileAttachmentGetNameMethodInfo a signature where
    overloadedMethod = annotFileAttachmentGetName

instance O.OverloadedMethodInfo AnnotFileAttachmentGetNameMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Poppler.Objects.AnnotFileAttachment.annotFileAttachmentGetName",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-poppler-0.18.27/docs/GI-Poppler-Objects-AnnotFileAttachment.html#v:annotFileAttachmentGetName"
        })


#endif