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

-- * Exported types
    AnnotCircle(..)                         ,
    IsAnnotCircle                           ,
    toAnnotCircle                           ,


 -- * 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"), [getInteriorColor]("GI.Poppler.Objects.AnnotCircle#g:method:getInteriorColor"), [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"), [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"), [setInteriorColor]("GI.Poppler.Objects.AnnotCircle#g:method:setInteriorColor"), [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)
    ResolveAnnotCircleMethod                ,
#endif

-- ** getInteriorColor #method:getInteriorColor#

#if defined(ENABLE_OVERLOADING)
    AnnotCircleGetInteriorColorMethodInfo   ,
#endif
    annotCircleGetInteriorColor             ,


-- ** new #method:new#

    annotCircleNew                          ,


-- ** setInteriorColor #method:setInteriorColor#

#if defined(ENABLE_OVERLOADING)
    AnnotCircleSetInteriorColorMethodInfo   ,
#endif
    annotCircleSetInteriorColor             ,




    ) 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.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.Color as Poppler.Color
import {-# SOURCE #-} qualified GI.Poppler.Structs.Rectangle as Poppler.Rectangle

#endif

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

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

foreign import ccall "poppler_annot_circle_get_type"
    c_poppler_annot_circle_get_type :: IO B.Types.GType

instance B.Types.TypedObject AnnotCircle where
    glibType :: IO GType
glibType = IO GType
c_poppler_annot_circle_get_type

instance B.Types.GObject AnnotCircle

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

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

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

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

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

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

#endif

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

#endif

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

#if defined(ENABLE_OVERLOADING)
#endif

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

#endif

-- method AnnotCircle::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 = "AnnotCircle" })
-- throws : False
-- Skip return : False

foreign import ccall "poppler_annot_circle_new" poppler_annot_circle_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 AnnotCircle)

-- | Creates a new Circle annotation that will be
-- located on /@rect@/ when added to a page. See
-- 'GI.Poppler.Objects.Page.pageAddAnnot'
-- 
-- /Since: 0.26/
annotCircleNew ::
    (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 AnnotCircle
    -- ^ __Returns:__ a newly created t'GI.Poppler.Objects.AnnotCircle.AnnotCircle' annotation
annotCircleNew :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDocument a) =>
a -> Rectangle -> m AnnotCircle
annotCircleNew a
doc Rectangle
rect = IO AnnotCircle -> m AnnotCircle
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO AnnotCircle -> m AnnotCircle)
-> IO AnnotCircle -> m AnnotCircle
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 AnnotCircle
result <- Ptr Document -> Ptr Rectangle -> IO (Ptr AnnotCircle)
poppler_annot_circle_new Ptr Document
doc' Ptr Rectangle
rect'
    Text -> Ptr AnnotCircle -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"annotCircleNew" Ptr AnnotCircle
result
    AnnotCircle
result' <- ((ManagedPtr AnnotCircle -> AnnotCircle)
-> Ptr AnnotCircle -> IO AnnotCircle
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr AnnotCircle -> AnnotCircle
AnnotCircle) Ptr AnnotCircle
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
doc
    Rectangle -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rectangle
rect
    AnnotCircle -> IO AnnotCircle
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return AnnotCircle
result'

#if defined(ENABLE_OVERLOADING)
#endif

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

foreign import ccall "poppler_annot_circle_get_interior_color" poppler_annot_circle_get_interior_color :: 
    Ptr AnnotCircle ->                      -- poppler_annot : TInterface (Name {namespace = "Poppler", name = "AnnotCircle"})
    IO (Ptr Poppler.Color.Color)

-- | Retrieves the interior color of /@popplerAnnot@/.
-- 
-- /Since: 0.26/
annotCircleGetInteriorColor ::
    (B.CallStack.HasCallStack, MonadIO m, IsAnnotCircle a) =>
    a
    -- ^ /@popplerAnnot@/: a t'GI.Poppler.Objects.AnnotCircle.AnnotCircle'
    -> m Poppler.Color.Color
    -- ^ __Returns:__ a new allocated t'GI.Poppler.Structs.Color.Color' with the color values of
    --               /@popplerAnnot@/, or 'P.Nothing'. It must be freed with 'GI.GLib.Functions.free' when done.
annotCircleGetInteriorColor :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsAnnotCircle a) =>
a -> m Color
annotCircleGetInteriorColor a
popplerAnnot = IO Color -> m Color
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Color -> m Color) -> IO Color -> m Color
forall a b. (a -> b) -> a -> b
$ do
    Ptr AnnotCircle
popplerAnnot' <- a -> IO (Ptr AnnotCircle)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
popplerAnnot
    Ptr Color
result <- Ptr AnnotCircle -> IO (Ptr Color)
poppler_annot_circle_get_interior_color Ptr AnnotCircle
popplerAnnot'
    Text -> Ptr Color -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"annotCircleGetInteriorColor" Ptr Color
result
    Color
result' <- ((ManagedPtr Color -> Color) -> Ptr Color -> IO Color
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Color -> Color
Poppler.Color.Color) Ptr Color
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
popplerAnnot
    Color -> IO Color
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Color
result'

#if defined(ENABLE_OVERLOADING)
data AnnotCircleGetInteriorColorMethodInfo
instance (signature ~ (m Poppler.Color.Color), MonadIO m, IsAnnotCircle a) => O.OverloadedMethod AnnotCircleGetInteriorColorMethodInfo a signature where
    overloadedMethod = annotCircleGetInteriorColor

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


#endif

-- method AnnotCircle::set_interior_color
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "poppler_annot"
--           , argType =
--               TInterface Name { namespace = "Poppler" , name = "AnnotCircle" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #PopplerAnnotCircle"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "poppler_color"
--           , argType =
--               TInterface Name { namespace = "Poppler" , name = "Color" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #PopplerColor, or %NULL"
--                 , 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_circle_set_interior_color" poppler_annot_circle_set_interior_color :: 
    Ptr AnnotCircle ->                      -- poppler_annot : TInterface (Name {namespace = "Poppler", name = "AnnotCircle"})
    Ptr Poppler.Color.Color ->              -- poppler_color : TInterface (Name {namespace = "Poppler", name = "Color"})
    IO ()

-- | Sets the interior color of /@popplerAnnot@/.
-- 
-- /Since: 0.26/
annotCircleSetInteriorColor ::
    (B.CallStack.HasCallStack, MonadIO m, IsAnnotCircle a) =>
    a
    -- ^ /@popplerAnnot@/: a t'GI.Poppler.Objects.AnnotCircle.AnnotCircle'
    -> Maybe (Poppler.Color.Color)
    -- ^ /@popplerColor@/: a t'GI.Poppler.Structs.Color.Color', or 'P.Nothing'
    -> m ()
annotCircleSetInteriorColor :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsAnnotCircle a) =>
a -> Maybe Color -> m ()
annotCircleSetInteriorColor a
popplerAnnot Maybe Color
popplerColor = 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 AnnotCircle
popplerAnnot' <- a -> IO (Ptr AnnotCircle)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
popplerAnnot
    Ptr Color
maybePopplerColor <- case Maybe Color
popplerColor of
        Maybe Color
Nothing -> Ptr Color -> IO (Ptr Color)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Color
forall a. Ptr a
nullPtr
        Just Color
jPopplerColor -> do
            Ptr Color
jPopplerColor' <- Color -> IO (Ptr Color)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Color
jPopplerColor
            Ptr Color -> IO (Ptr Color)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Color
jPopplerColor'
    Ptr AnnotCircle -> Ptr Color -> IO ()
poppler_annot_circle_set_interior_color Ptr AnnotCircle
popplerAnnot' Ptr Color
maybePopplerColor
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
popplerAnnot
    Maybe Color -> (Color -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe Color
popplerColor Color -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data AnnotCircleSetInteriorColorMethodInfo
instance (signature ~ (Maybe (Poppler.Color.Color) -> m ()), MonadIO m, IsAnnotCircle a) => O.OverloadedMethod AnnotCircleSetInteriorColorMethodInfo a signature where
    overloadedMethod = annotCircleSetInteriorColor

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


#endif