{-# 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.AnnotText
    ( 

-- * Exported types
    AnnotText(..)                           ,
    IsAnnotText                             ,
    toAnnotText                             ,


 -- * 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"), [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"), [getIcon]("GI.Poppler.Objects.AnnotText#g:method:getIcon"), [getIsOpen]("GI.Poppler.Objects.AnnotText#g:method:getIsOpen"), [getLabel]("GI.Poppler.Objects.AnnotMarkup#g:method:getLabel"), [getModified]("GI.Poppler.Objects.Annot#g:method:getModified"), [getName]("GI.Poppler.Objects.Annot#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"), [getState]("GI.Poppler.Objects.AnnotText#g:method:getState"), [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"), [setIcon]("GI.Poppler.Objects.AnnotText#g:method:setIcon"), [setIsOpen]("GI.Poppler.Objects.AnnotText#g:method:setIsOpen"), [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)
    ResolveAnnotTextMethod                  ,
#endif

-- ** getIcon #method:getIcon#

#if defined(ENABLE_OVERLOADING)
    AnnotTextGetIconMethodInfo              ,
#endif
    annotTextGetIcon                        ,


-- ** getIsOpen #method:getIsOpen#

#if defined(ENABLE_OVERLOADING)
    AnnotTextGetIsOpenMethodInfo            ,
#endif
    annotTextGetIsOpen                      ,


-- ** getState #method:getState#

#if defined(ENABLE_OVERLOADING)
    AnnotTextGetStateMethodInfo             ,
#endif
    annotTextGetState                       ,


-- ** new #method:new#

    annotTextNew                            ,


-- ** setIcon #method:setIcon#

#if defined(ENABLE_OVERLOADING)
    AnnotTextSetIconMethodInfo              ,
#endif
    annotTextSetIcon                        ,


-- ** setIsOpen #method:setIsOpen#

#if defined(ENABLE_OVERLOADING)
    AnnotTextSetIsOpenMethodInfo            ,
#endif
    annotTextSetIsOpen                      ,




    ) 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.Kind as DK
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 Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT

-- Workaround for https://gitlab.haskell.org/ghc/ghc/-/issues/23392
#if MIN_VERSION_base(4,18,0)
import qualified GI.Cairo.Structs.Context as Cairo.Context
import qualified GI.Cairo.Structs.Region as Cairo.Region
import qualified GI.Cairo.Structs.Surface as Cairo.Surface
import qualified GI.GLib.Structs.Bytes as GLib.Bytes
import qualified GI.GLib.Structs.Date as GLib.Date
import qualified GI.GLib.Structs.DateTime as GLib.DateTime
import qualified GI.GLib.Structs.String as GLib.String
import qualified GI.GLib.Structs.Tree as GLib.Tree
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gio.Callbacks as Gio.Callbacks
import qualified GI.Gio.Interfaces.AsyncResult as Gio.AsyncResult
import qualified GI.Gio.Interfaces.File as Gio.File
import qualified GI.Gio.Objects.Cancellable as Gio.Cancellable
import qualified GI.Gio.Objects.InputStream as Gio.InputStream
import qualified GI.Poppler.Callbacks as Poppler.Callbacks
import {-# SOURCE #-} qualified GI.Poppler.Enums as Poppler.Enums
import {-# SOURCE #-} qualified GI.Poppler.Flags as Poppler.Flags
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
import {-# SOURCE #-} qualified GI.Poppler.Objects.Document as Poppler.Document
import {-# SOURCE #-} qualified GI.Poppler.Objects.FormField as Poppler.FormField
import {-# SOURCE #-} qualified GI.Poppler.Objects.Layer as Poppler.Layer
import {-# SOURCE #-} qualified GI.Poppler.Objects.Media as Poppler.Media
import {-# SOURCE #-} qualified GI.Poppler.Objects.Movie as Poppler.Movie
import {-# SOURCE #-} qualified GI.Poppler.Objects.PSFile as Poppler.PSFile
import {-# SOURCE #-} qualified GI.Poppler.Objects.Page as Poppler.Page
import {-# SOURCE #-} qualified GI.Poppler.Structs.ActionAny as Poppler.ActionAny
import {-# SOURCE #-} qualified GI.Poppler.Structs.ActionGotoDest as Poppler.ActionGotoDest
import {-# SOURCE #-} qualified GI.Poppler.Structs.ActionGotoRemote as Poppler.ActionGotoRemote
import {-# SOURCE #-} qualified GI.Poppler.Structs.ActionJavascript as Poppler.ActionJavascript
import {-# SOURCE #-} qualified GI.Poppler.Structs.ActionLaunch as Poppler.ActionLaunch
import {-# SOURCE #-} qualified GI.Poppler.Structs.ActionLayer as Poppler.ActionLayer
import {-# SOURCE #-} qualified GI.Poppler.Structs.ActionMovie as Poppler.ActionMovie
import {-# SOURCE #-} qualified GI.Poppler.Structs.ActionNamed as Poppler.ActionNamed
import {-# SOURCE #-} qualified GI.Poppler.Structs.ActionOCGState as Poppler.ActionOCGState
import {-# SOURCE #-} qualified GI.Poppler.Structs.ActionRendition as Poppler.ActionRendition
import {-# SOURCE #-} qualified GI.Poppler.Structs.ActionResetForm as Poppler.ActionResetForm
import {-# SOURCE #-} qualified GI.Poppler.Structs.ActionUri as Poppler.ActionUri
import {-# SOURCE #-} qualified GI.Poppler.Structs.AnnotMapping as Poppler.AnnotMapping
import {-# SOURCE #-} qualified GI.Poppler.Structs.CertificateInfo as Poppler.CertificateInfo
import {-# SOURCE #-} qualified GI.Poppler.Structs.Color as Poppler.Color
import {-# SOURCE #-} qualified GI.Poppler.Structs.Dest as Poppler.Dest
import {-# SOURCE #-} qualified GI.Poppler.Structs.FormFieldMapping as Poppler.FormFieldMapping
import {-# SOURCE #-} qualified GI.Poppler.Structs.ImageMapping as Poppler.ImageMapping
import {-# SOURCE #-} qualified GI.Poppler.Structs.LinkMapping as Poppler.LinkMapping
import {-# SOURCE #-} qualified GI.Poppler.Structs.PageRange as Poppler.PageRange
import {-# SOURCE #-} qualified GI.Poppler.Structs.PageTransition as Poppler.PageTransition
import {-# SOURCE #-} qualified GI.Poppler.Structs.Rectangle as Poppler.Rectangle
import {-# SOURCE #-} qualified GI.Poppler.Structs.SignatureInfo as Poppler.SignatureInfo
import {-# SOURCE #-} qualified GI.Poppler.Structs.SigningData as Poppler.SigningData
import {-# SOURCE #-} qualified GI.Poppler.Structs.TextAttributes as Poppler.TextAttributes
import {-# SOURCE #-} qualified GI.Poppler.Unions.Action as Poppler.Action

#else
import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Poppler.Enums as Poppler.Enums
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.Document as Poppler.Document
import {-# SOURCE #-} qualified GI.Poppler.Structs.Rectangle as Poppler.Rectangle

#endif

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

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

foreign import ccall "poppler_annot_text_get_type"
    c_poppler_annot_text_get_type :: IO B.Types.GType

instance B.Types.TypedObject AnnotText where
    glibType :: IO GType
glibType = IO GType
c_poppler_annot_text_get_type

instance B.Types.GObject AnnotText

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

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

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

-- | Convert 'AnnotText' 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 AnnotText) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_poppler_annot_text_get_type
    gvalueSet_ :: Ptr GValue -> Maybe AnnotText -> IO ()
gvalueSet_ Ptr GValue
gv Maybe AnnotText
P.Nothing = Ptr GValue -> Ptr AnnotText -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr AnnotText
forall a. Ptr a
FP.nullPtr :: FP.Ptr AnnotText)
    gvalueSet_ Ptr GValue
gv (P.Just AnnotText
obj) = AnnotText -> (Ptr AnnotText -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr AnnotText
obj (Ptr GValue -> Ptr AnnotText -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe AnnotText)
gvalueGet_ Ptr GValue
gv = do
        Ptr AnnotText
ptr <- Ptr GValue -> IO (Ptr AnnotText)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr AnnotText)
        if Ptr AnnotText
ptr Ptr AnnotText -> Ptr AnnotText -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr AnnotText
forall a. Ptr a
FP.nullPtr
        then AnnotText -> Maybe AnnotText
forall a. a -> Maybe a
P.Just (AnnotText -> Maybe AnnotText)
-> IO AnnotText -> IO (Maybe AnnotText)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr AnnotText -> AnnotText)
-> Ptr AnnotText -> IO AnnotText
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr AnnotText -> AnnotText
AnnotText Ptr AnnotText
ptr
        else Maybe AnnotText -> IO (Maybe AnnotText)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe AnnotText
forall a. Maybe a
P.Nothing
        
    

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

instance (info ~ ResolveAnnotTextMethod t AnnotText, O.OverloadedMethod info AnnotText p) => OL.IsLabel t (AnnotText -> 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 ~ ResolveAnnotTextMethod t AnnotText, O.OverloadedMethod info AnnotText p, R.HasField t AnnotText p) => R.HasField t AnnotText p where
    getField = O.overloadedMethod @info

#endif

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

#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList AnnotText
type instance O.AttributeList AnnotText = AnnotTextAttributeList
type AnnotTextAttributeList = ('[ ] :: [(Symbol, DK.Type)])
#endif

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList AnnotText = AnnotTextSignalList
type AnnotTextSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, DK.Type)])

#endif

-- method AnnotText::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "doc"
--           , argType =
--               TInterface Name { namespace = "Poppler" , name = "Document" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #PopplerDocument" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "rect"
--           , argType =
--               TInterface Name { namespace = "Poppler" , name = "Rectangle" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #PopplerRectangle"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Poppler" , name = "AnnotText" })
-- throws : False
-- Skip return : False

foreign import ccall "poppler_annot_text_new" poppler_annot_text_new :: 
    Ptr Poppler.Document.Document ->        -- doc : TInterface (Name {namespace = "Poppler", name = "Document"})
    Ptr Poppler.Rectangle.Rectangle ->      -- rect : TInterface (Name {namespace = "Poppler", name = "Rectangle"})
    IO (Ptr AnnotText)

-- | Creates a new Text annotation that will be
-- located on /@rect@/ when added to a page. See
-- 'GI.Poppler.Objects.Page.pageAddAnnot'
-- 
-- /Since: 0.16/
annotTextNew ::
    (B.CallStack.HasCallStack, MonadIO m, Poppler.Document.IsDocument a) =>
    a
    -- ^ /@doc@/: a t'GI.Poppler.Objects.Document.Document'
    -> Poppler.Rectangle.Rectangle
    -- ^ /@rect@/: a t'GI.Poppler.Structs.Rectangle.Rectangle'
    -> m AnnotText
    -- ^ __Returns:__ A newly created t'GI.Poppler.Objects.AnnotText.AnnotText' annotation
annotTextNew :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDocument a) =>
a -> Rectangle -> m AnnotText
annotTextNew a
doc Rectangle
rect = IO AnnotText -> m AnnotText
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO AnnotText -> m AnnotText) -> IO AnnotText -> m AnnotText
forall a b. (a -> b) -> a -> b
$ do
    Ptr Document
doc' <- a -> IO (Ptr Document)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
doc
    Ptr Rectangle
rect' <- Rectangle -> IO (Ptr Rectangle)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rectangle
rect
    Ptr AnnotText
result <- Ptr Document -> Ptr Rectangle -> IO (Ptr AnnotText)
poppler_annot_text_new Ptr Document
doc' Ptr Rectangle
rect'
    Text -> Ptr AnnotText -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"annotTextNew" Ptr AnnotText
result
    AnnotText
result' <- ((ManagedPtr AnnotText -> AnnotText)
-> Ptr AnnotText -> IO AnnotText
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr AnnotText -> AnnotText
AnnotText) Ptr AnnotText
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
doc
    Rectangle -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rectangle
rect
    AnnotText -> IO AnnotText
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return AnnotText
result'

#if defined(ENABLE_OVERLOADING)
#endif

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

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

-- | Gets name of the icon of /@popplerAnnot@/.
annotTextGetIcon ::
    (B.CallStack.HasCallStack, MonadIO m, IsAnnotText a) =>
    a
    -- ^ /@popplerAnnot@/: a t'GI.Poppler.Objects.AnnotText.AnnotText'
    -> m T.Text
    -- ^ __Returns:__ a new allocated string containing the icon name
annotTextGetIcon :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsAnnotText a) =>
a -> m Text
annotTextGetIcon 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 AnnotText
popplerAnnot' <- a -> IO (Ptr AnnotText)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
popplerAnnot
    CString
result <- Ptr AnnotText -> IO CString
poppler_annot_text_get_icon Ptr AnnotText
popplerAnnot'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"annotTextGetIcon" 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 AnnotTextGetIconMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsAnnotText a) => O.OverloadedMethod AnnotTextGetIconMethodInfo a signature where
    overloadedMethod = annotTextGetIcon

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


#endif

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

foreign import ccall "poppler_annot_text_get_is_open" poppler_annot_text_get_is_open :: 
    Ptr AnnotText ->                        -- poppler_annot : TInterface (Name {namespace = "Poppler", name = "AnnotText"})
    IO CInt

-- | Retrieves the state of /@popplerAnnot@/.
annotTextGetIsOpen ::
    (B.CallStack.HasCallStack, MonadIO m, IsAnnotText a) =>
    a
    -- ^ /@popplerAnnot@/: a t'GI.Poppler.Objects.AnnotText.AnnotText'
    -> m Bool
    -- ^ __Returns:__ the state of /@popplerAnnot@/. 'P.True' if it\'s open, 'P.False' in
    --               other case.
annotTextGetIsOpen :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsAnnotText a) =>
a -> m Bool
annotTextGetIsOpen a
popplerAnnot = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr AnnotText
popplerAnnot' <- a -> IO (Ptr AnnotText)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
popplerAnnot
    CInt
result <- Ptr AnnotText -> IO CInt
poppler_annot_text_get_is_open Ptr AnnotText
popplerAnnot'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
popplerAnnot
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data AnnotTextGetIsOpenMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsAnnotText a) => O.OverloadedMethod AnnotTextGetIsOpenMethodInfo a signature where
    overloadedMethod = annotTextGetIsOpen

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


#endif

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

foreign import ccall "poppler_annot_text_get_state" poppler_annot_text_get_state :: 
    Ptr AnnotText ->                        -- poppler_annot : TInterface (Name {namespace = "Poppler", name = "AnnotText"})
    IO CUInt

-- | Retrieves the state of /@popplerAnnot@/.
annotTextGetState ::
    (B.CallStack.HasCallStack, MonadIO m, IsAnnotText a) =>
    a
    -- ^ /@popplerAnnot@/: a t'GI.Poppler.Objects.AnnotText.AnnotText'
    -> m Poppler.Enums.AnnotTextState
    -- ^ __Returns:__ t'GI.Poppler.Enums.AnnotTextState' of /@popplerAnnot@/.
annotTextGetState :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsAnnotText a) =>
a -> m AnnotTextState
annotTextGetState a
popplerAnnot = IO AnnotTextState -> m AnnotTextState
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO AnnotTextState -> m AnnotTextState)
-> IO AnnotTextState -> m AnnotTextState
forall a b. (a -> b) -> a -> b
$ do
    Ptr AnnotText
popplerAnnot' <- a -> IO (Ptr AnnotText)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
popplerAnnot
    CUInt
result <- Ptr AnnotText -> IO CUInt
poppler_annot_text_get_state Ptr AnnotText
popplerAnnot'
    let result' :: AnnotTextState
result' = (Int -> AnnotTextState
forall a. Enum a => Int -> a
toEnum (Int -> AnnotTextState)
-> (CUInt -> Int) -> CUInt -> AnnotTextState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
popplerAnnot
    AnnotTextState -> IO AnnotTextState
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return AnnotTextState
result'

#if defined(ENABLE_OVERLOADING)
data AnnotTextGetStateMethodInfo
instance (signature ~ (m Poppler.Enums.AnnotTextState), MonadIO m, IsAnnotText a) => O.OverloadedMethod AnnotTextGetStateMethodInfo a signature where
    overloadedMethod = annotTextGetState

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


#endif

-- method AnnotText::set_icon
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "poppler_annot"
--           , argType =
--               TInterface Name { namespace = "Poppler" , name = "AnnotText" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #PopplerAnnotText"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "icon"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the name of an icon"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "poppler_annot_text_set_icon" poppler_annot_text_set_icon :: 
    Ptr AnnotText ->                        -- poppler_annot : TInterface (Name {namespace = "Poppler", name = "AnnotText"})
    CString ->                              -- icon : TBasicType TUTF8
    IO ()

-- | Sets the icon of /@popplerAnnot@/. The following predefined
-- icons are currently supported:
-- \<variablelist>
--  \<varlistentry>
--   \<term>'GI.Poppler.Constants.ANNOT_TEXT_ICON_NOTE'\<\/term>
--  \<\/varlistentry>
--  \<varlistentry>
--   \<term>'GI.Poppler.Constants.ANNOT_TEXT_ICON_COMMENT'\<\/term>
--  \<\/varlistentry>
--  \<varlistentry>
--   \<term>'GI.Poppler.Constants.ANNOT_TEXT_ICON_KEY'\<\/term>
--  \<\/varlistentry>
--  \<varlistentry>
--   \<term>'GI.Poppler.Constants.ANNOT_TEXT_ICON_HELP'\<\/term>
--  \<\/varlistentry>
--  \<varlistentry>
--   \<term>'GI.Poppler.Constants.ANNOT_TEXT_ICON_NEW_PARAGRAPH'\<\/term>
--  \<\/varlistentry>
--  \<varlistentry>
--   \<term>'GI.Poppler.Constants.ANNOT_TEXT_ICON_PARAGRAPH'\<\/term>
--  \<\/varlistentry>
--  \<varlistentry>
--   \<term>'GI.Poppler.Constants.ANNOT_TEXT_ICON_INSERT'\<\/term>
--  \<\/varlistentry>
--  \<varlistentry>
--   \<term>'GI.Poppler.Constants.ANNOT_TEXT_ICON_CROSS'\<\/term>
--  \<\/varlistentry>
--  \<varlistentry>
--   \<term>'GI.Poppler.Constants.ANNOT_TEXT_ICON_CIRCLE'\<\/term>
--  \<\/varlistentry>
-- \<\/variablelist>
-- 
-- /Since: 0.16/
annotTextSetIcon ::
    (B.CallStack.HasCallStack, MonadIO m, IsAnnotText a) =>
    a
    -- ^ /@popplerAnnot@/: a t'GI.Poppler.Objects.AnnotText.AnnotText'
    -> T.Text
    -- ^ /@icon@/: the name of an icon
    -> m ()
annotTextSetIcon :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsAnnotText a) =>
a -> Text -> m ()
annotTextSetIcon a
popplerAnnot Text
icon = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr AnnotText
popplerAnnot' <- a -> IO (Ptr AnnotText)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
popplerAnnot
    CString
icon' <- Text -> IO CString
textToCString Text
icon
    Ptr AnnotText -> CString -> IO ()
poppler_annot_text_set_icon Ptr AnnotText
popplerAnnot' CString
icon'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
popplerAnnot
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
icon'
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data AnnotTextSetIconMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsAnnotText a) => O.OverloadedMethod AnnotTextSetIconMethodInfo a signature where
    overloadedMethod = annotTextSetIcon

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


#endif

-- method AnnotText::set_is_open
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "poppler_annot"
--           , argType =
--               TInterface Name { namespace = "Poppler" , name = "AnnotText" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #PopplerAnnotText"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "is_open"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "whether annotation should initially be displayed open"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "poppler_annot_text_set_is_open" poppler_annot_text_set_is_open :: 
    Ptr AnnotText ->                        -- poppler_annot : TInterface (Name {namespace = "Poppler", name = "AnnotText"})
    CInt ->                                 -- is_open : TBasicType TBoolean
    IO ()

-- | Sets whether /@popplerAnnot@/ should initially be displayed open
-- 
-- /Since: 0.16/
annotTextSetIsOpen ::
    (B.CallStack.HasCallStack, MonadIO m, IsAnnotText a) =>
    a
    -- ^ /@popplerAnnot@/: a t'GI.Poppler.Objects.AnnotText.AnnotText'
    -> Bool
    -- ^ /@isOpen@/: whether annotation should initially be displayed open
    -> m ()
annotTextSetIsOpen :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsAnnotText a) =>
a -> Bool -> m ()
annotTextSetIsOpen a
popplerAnnot Bool
isOpen = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr AnnotText
popplerAnnot' <- a -> IO (Ptr AnnotText)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
popplerAnnot
    let isOpen' :: CInt
isOpen' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
P.fromEnum) Bool
isOpen
    Ptr AnnotText -> CInt -> IO ()
poppler_annot_text_set_is_open Ptr AnnotText
popplerAnnot' CInt
isOpen'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
popplerAnnot
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data AnnotTextSetIsOpenMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsAnnotText a) => O.OverloadedMethod AnnotTextSetIsOpenMethodInfo a signature where
    overloadedMethod = annotTextSetIsOpen

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


#endif