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

-- * Exported types
    AnnotLine(..)                           ,
    IsAnnotLine                             ,
    toAnnotLine                             ,


 -- * 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"), [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"), [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"), [setVertices]("GI.Poppler.Objects.AnnotLine#g:method:setVertices").

#if defined(ENABLE_OVERLOADING)
    ResolveAnnotLineMethod                  ,
#endif

-- ** new #method:new#

    annotLineNew                            ,


-- ** setVertices #method:setVertices#

#if defined(ENABLE_OVERLOADING)
    AnnotLineSetVerticesMethodInfo          ,
#endif
    annotLineSetVertices                    ,




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

#endif

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

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

foreign import ccall "poppler_annot_line_get_type"
    c_poppler_annot_line_get_type :: IO B.Types.GType

instance B.Types.TypedObject AnnotLine where
    glibType :: IO GType
glibType = IO GType
c_poppler_annot_line_get_type

instance B.Types.GObject AnnotLine

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

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

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

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

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

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

#endif

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

#endif

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

#if defined(ENABLE_OVERLOADING)
#endif

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

#endif

-- method AnnotLine::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
--           }
--       , Arg
--           { argCName = "start"
--           , argType =
--               TInterface Name { namespace = "Poppler" , name = "Point" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #PopplerPoint of the starting vertice"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "end"
--           , argType =
--               TInterface Name { namespace = "Poppler" , name = "Point" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #PopplerPoint of the ending vertice"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Poppler" , name = "AnnotLine" })
-- throws : False
-- Skip return : False

foreign import ccall "poppler_annot_line_new" poppler_annot_line_new :: 
    Ptr Poppler.Document.Document ->        -- doc : TInterface (Name {namespace = "Poppler", name = "Document"})
    Ptr Poppler.Rectangle.Rectangle ->      -- rect : TInterface (Name {namespace = "Poppler", name = "Rectangle"})
    Ptr Poppler.Point.Point ->              -- start : TInterface (Name {namespace = "Poppler", name = "Point"})
    Ptr Poppler.Point.Point ->              -- end : TInterface (Name {namespace = "Poppler", name = "Point"})
    IO (Ptr AnnotLine)

-- | Creates a new Line annotation that will be
-- located on /@rect@/ when added to a page. See
-- 'GI.Poppler.Objects.Page.pageAddAnnot'
-- 
-- /Since: 0.26/
annotLineNew ::
    (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'
    -> Poppler.Point.Point
    -- ^ /@start@/: a t'GI.Poppler.Structs.Point.Point' of the starting vertice
    -> Poppler.Point.Point
    -- ^ /@end@/: a t'GI.Poppler.Structs.Point.Point' of the ending vertice
    -> m AnnotLine
    -- ^ __Returns:__ A newly created t'GI.Poppler.Objects.AnnotLine.AnnotLine' annotation
annotLineNew :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDocument a) =>
a -> Rectangle -> Point -> Point -> m AnnotLine
annotLineNew a
doc Rectangle
rect Point
start Point
end = IO AnnotLine -> m AnnotLine
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO AnnotLine -> m AnnotLine) -> IO AnnotLine -> m AnnotLine
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 Point
start' <- Point -> IO (Ptr Point)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Point
start
    Ptr Point
end' <- Point -> IO (Ptr Point)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Point
end
    Ptr AnnotLine
result <- Ptr Document
-> Ptr Rectangle -> Ptr Point -> Ptr Point -> IO (Ptr AnnotLine)
poppler_annot_line_new Ptr Document
doc' Ptr Rectangle
rect' Ptr Point
start' Ptr Point
end'
    Text -> Ptr AnnotLine -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"annotLineNew" Ptr AnnotLine
result
    AnnotLine
result' <- ((ManagedPtr AnnotLine -> AnnotLine)
-> Ptr AnnotLine -> IO AnnotLine
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr AnnotLine -> AnnotLine
AnnotLine) Ptr AnnotLine
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
doc
    Rectangle -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rectangle
rect
    Point -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Point
start
    Point -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Point
end
    AnnotLine -> IO AnnotLine
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return AnnotLine
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method AnnotLine::set_vertices
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "poppler_annot"
--           , argType =
--               TInterface Name { namespace = "Poppler" , name = "AnnotLine" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #PopplerAnnotLine"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "start"
--           , argType =
--               TInterface Name { namespace = "Poppler" , name = "Point" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #PopplerPoint of the starting vertice"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "end"
--           , argType =
--               TInterface Name { namespace = "Poppler" , name = "Point" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #PopplerPoint of the ending vertice"
--                 , 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_line_set_vertices" poppler_annot_line_set_vertices :: 
    Ptr AnnotLine ->                        -- poppler_annot : TInterface (Name {namespace = "Poppler", name = "AnnotLine"})
    Ptr Poppler.Point.Point ->              -- start : TInterface (Name {namespace = "Poppler", name = "Point"})
    Ptr Poppler.Point.Point ->              -- end : TInterface (Name {namespace = "Poppler", name = "Point"})
    IO ()

-- | Set the coordinate points where the /@popplerAnnot@/ starts and ends.
-- 
-- /Since: 0.26/
annotLineSetVertices ::
    (B.CallStack.HasCallStack, MonadIO m, IsAnnotLine a) =>
    a
    -- ^ /@popplerAnnot@/: a t'GI.Poppler.Objects.AnnotLine.AnnotLine'
    -> Poppler.Point.Point
    -- ^ /@start@/: a t'GI.Poppler.Structs.Point.Point' of the starting vertice
    -> Poppler.Point.Point
    -- ^ /@end@/: a t'GI.Poppler.Structs.Point.Point' of the ending vertice
    -> m ()
annotLineSetVertices :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsAnnotLine a) =>
a -> Point -> Point -> m ()
annotLineSetVertices a
popplerAnnot Point
start Point
end = 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 AnnotLine
popplerAnnot' <- a -> IO (Ptr AnnotLine)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
popplerAnnot
    Ptr Point
start' <- Point -> IO (Ptr Point)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Point
start
    Ptr Point
end' <- Point -> IO (Ptr Point)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Point
end
    Ptr AnnotLine -> Ptr Point -> Ptr Point -> IO ()
poppler_annot_line_set_vertices Ptr AnnotLine
popplerAnnot' Ptr Point
start' Ptr Point
end'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
popplerAnnot
    Point -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Point
start
    Point -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Point
end
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data AnnotLineSetVerticesMethodInfo
instance (signature ~ (Poppler.Point.Point -> Poppler.Point.Point -> m ()), MonadIO m, IsAnnotLine a) => O.OverloadedMethod AnnotLineSetVerticesMethodInfo a signature where
    overloadedMethod = annotLineSetVertices

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


#endif