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

-- * Exported types
    SigningData(..)                         ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [copy]("GI.Poppler.Structs.SigningData#g:method:copy"), [free]("GI.Poppler.Structs.SigningData#g:method:free").
-- 
-- ==== Getters
-- [getBackgroundColor]("GI.Poppler.Structs.SigningData#g:method:getBackgroundColor"), [getBorderColor]("GI.Poppler.Structs.SigningData#g:method:getBorderColor"), [getBorderWidth]("GI.Poppler.Structs.SigningData#g:method:getBorderWidth"), [getCertificateInfo]("GI.Poppler.Structs.SigningData#g:method:getCertificateInfo"), [getDestinationFilename]("GI.Poppler.Structs.SigningData#g:method:getDestinationFilename"), [getDocumentOwnerPassword]("GI.Poppler.Structs.SigningData#g:method:getDocumentOwnerPassword"), [getDocumentUserPassword]("GI.Poppler.Structs.SigningData#g:method:getDocumentUserPassword"), [getFieldPartialName]("GI.Poppler.Structs.SigningData#g:method:getFieldPartialName"), [getFontColor]("GI.Poppler.Structs.SigningData#g:method:getFontColor"), [getFontSize]("GI.Poppler.Structs.SigningData#g:method:getFontSize"), [getImagePath]("GI.Poppler.Structs.SigningData#g:method:getImagePath"), [getLeftFontSize]("GI.Poppler.Structs.SigningData#g:method:getLeftFontSize"), [getLocation]("GI.Poppler.Structs.SigningData#g:method:getLocation"), [getPage]("GI.Poppler.Structs.SigningData#g:method:getPage"), [getPassword]("GI.Poppler.Structs.SigningData#g:method:getPassword"), [getReason]("GI.Poppler.Structs.SigningData#g:method:getReason"), [getSignatureRectangle]("GI.Poppler.Structs.SigningData#g:method:getSignatureRectangle"), [getSignatureText]("GI.Poppler.Structs.SigningData#g:method:getSignatureText"), [getSignatureTextLeft]("GI.Poppler.Structs.SigningData#g:method:getSignatureTextLeft").
-- 
-- ==== Setters
-- [setBackgroundColor]("GI.Poppler.Structs.SigningData#g:method:setBackgroundColor"), [setBorderColor]("GI.Poppler.Structs.SigningData#g:method:setBorderColor"), [setBorderWidth]("GI.Poppler.Structs.SigningData#g:method:setBorderWidth"), [setCertificateInfo]("GI.Poppler.Structs.SigningData#g:method:setCertificateInfo"), [setDestinationFilename]("GI.Poppler.Structs.SigningData#g:method:setDestinationFilename"), [setDocumentOwnerPassword]("GI.Poppler.Structs.SigningData#g:method:setDocumentOwnerPassword"), [setDocumentUserPassword]("GI.Poppler.Structs.SigningData#g:method:setDocumentUserPassword"), [setFieldPartialName]("GI.Poppler.Structs.SigningData#g:method:setFieldPartialName"), [setFontColor]("GI.Poppler.Structs.SigningData#g:method:setFontColor"), [setFontSize]("GI.Poppler.Structs.SigningData#g:method:setFontSize"), [setImagePath]("GI.Poppler.Structs.SigningData#g:method:setImagePath"), [setLeftFontSize]("GI.Poppler.Structs.SigningData#g:method:setLeftFontSize"), [setLocation]("GI.Poppler.Structs.SigningData#g:method:setLocation"), [setPage]("GI.Poppler.Structs.SigningData#g:method:setPage"), [setPassword]("GI.Poppler.Structs.SigningData#g:method:setPassword"), [setReason]("GI.Poppler.Structs.SigningData#g:method:setReason"), [setSignatureRectangle]("GI.Poppler.Structs.SigningData#g:method:setSignatureRectangle"), [setSignatureText]("GI.Poppler.Structs.SigningData#g:method:setSignatureText"), [setSignatureTextLeft]("GI.Poppler.Structs.SigningData#g:method:setSignatureTextLeft").

#if defined(ENABLE_OVERLOADING)
    ResolveSigningDataMethod                ,
#endif

-- ** copy #method:copy#

#if defined(ENABLE_OVERLOADING)
    SigningDataCopyMethodInfo               ,
#endif
    signingDataCopy                         ,


-- ** free #method:free#

#if defined(ENABLE_OVERLOADING)
    SigningDataFreeMethodInfo               ,
#endif
    signingDataFree                         ,


-- ** getBackgroundColor #method:getBackgroundColor#

#if defined(ENABLE_OVERLOADING)
    SigningDataGetBackgroundColorMethodInfo ,
#endif
    signingDataGetBackgroundColor           ,


-- ** getBorderColor #method:getBorderColor#

#if defined(ENABLE_OVERLOADING)
    SigningDataGetBorderColorMethodInfo     ,
#endif
    signingDataGetBorderColor               ,


-- ** getBorderWidth #method:getBorderWidth#

#if defined(ENABLE_OVERLOADING)
    SigningDataGetBorderWidthMethodInfo     ,
#endif
    signingDataGetBorderWidth               ,


-- ** getCertificateInfo #method:getCertificateInfo#

#if defined(ENABLE_OVERLOADING)
    SigningDataGetCertificateInfoMethodInfo ,
#endif
    signingDataGetCertificateInfo           ,


-- ** getDestinationFilename #method:getDestinationFilename#

#if defined(ENABLE_OVERLOADING)
    SigningDataGetDestinationFilenameMethodInfo,
#endif
    signingDataGetDestinationFilename       ,


-- ** getDocumentOwnerPassword #method:getDocumentOwnerPassword#

#if defined(ENABLE_OVERLOADING)
    SigningDataGetDocumentOwnerPasswordMethodInfo,
#endif
    signingDataGetDocumentOwnerPassword     ,


-- ** getDocumentUserPassword #method:getDocumentUserPassword#

#if defined(ENABLE_OVERLOADING)
    SigningDataGetDocumentUserPasswordMethodInfo,
#endif
    signingDataGetDocumentUserPassword      ,


-- ** getFieldPartialName #method:getFieldPartialName#

#if defined(ENABLE_OVERLOADING)
    SigningDataGetFieldPartialNameMethodInfo,
#endif
    signingDataGetFieldPartialName          ,


-- ** getFontColor #method:getFontColor#

#if defined(ENABLE_OVERLOADING)
    SigningDataGetFontColorMethodInfo       ,
#endif
    signingDataGetFontColor                 ,


-- ** getFontSize #method:getFontSize#

#if defined(ENABLE_OVERLOADING)
    SigningDataGetFontSizeMethodInfo        ,
#endif
    signingDataGetFontSize                  ,


-- ** getImagePath #method:getImagePath#

#if defined(ENABLE_OVERLOADING)
    SigningDataGetImagePathMethodInfo       ,
#endif
    signingDataGetImagePath                 ,


-- ** getLeftFontSize #method:getLeftFontSize#

#if defined(ENABLE_OVERLOADING)
    SigningDataGetLeftFontSizeMethodInfo    ,
#endif
    signingDataGetLeftFontSize              ,


-- ** getLocation #method:getLocation#

#if defined(ENABLE_OVERLOADING)
    SigningDataGetLocationMethodInfo        ,
#endif
    signingDataGetLocation                  ,


-- ** getPage #method:getPage#

#if defined(ENABLE_OVERLOADING)
    SigningDataGetPageMethodInfo            ,
#endif
    signingDataGetPage                      ,


-- ** getPassword #method:getPassword#

#if defined(ENABLE_OVERLOADING)
    SigningDataGetPasswordMethodInfo        ,
#endif
    signingDataGetPassword                  ,


-- ** getReason #method:getReason#

#if defined(ENABLE_OVERLOADING)
    SigningDataGetReasonMethodInfo          ,
#endif
    signingDataGetReason                    ,


-- ** getSignatureRectangle #method:getSignatureRectangle#

#if defined(ENABLE_OVERLOADING)
    SigningDataGetSignatureRectangleMethodInfo,
#endif
    signingDataGetSignatureRectangle        ,


-- ** getSignatureText #method:getSignatureText#

#if defined(ENABLE_OVERLOADING)
    SigningDataGetSignatureTextMethodInfo   ,
#endif
    signingDataGetSignatureText             ,


-- ** getSignatureTextLeft #method:getSignatureTextLeft#

#if defined(ENABLE_OVERLOADING)
    SigningDataGetSignatureTextLeftMethodInfo,
#endif
    signingDataGetSignatureTextLeft         ,


-- ** new #method:new#

    signingDataNew                          ,


-- ** setBackgroundColor #method:setBackgroundColor#

#if defined(ENABLE_OVERLOADING)
    SigningDataSetBackgroundColorMethodInfo ,
#endif
    signingDataSetBackgroundColor           ,


-- ** setBorderColor #method:setBorderColor#

#if defined(ENABLE_OVERLOADING)
    SigningDataSetBorderColorMethodInfo     ,
#endif
    signingDataSetBorderColor               ,


-- ** setBorderWidth #method:setBorderWidth#

#if defined(ENABLE_OVERLOADING)
    SigningDataSetBorderWidthMethodInfo     ,
#endif
    signingDataSetBorderWidth               ,


-- ** setCertificateInfo #method:setCertificateInfo#

#if defined(ENABLE_OVERLOADING)
    SigningDataSetCertificateInfoMethodInfo ,
#endif
    signingDataSetCertificateInfo           ,


-- ** setDestinationFilename #method:setDestinationFilename#

#if defined(ENABLE_OVERLOADING)
    SigningDataSetDestinationFilenameMethodInfo,
#endif
    signingDataSetDestinationFilename       ,


-- ** setDocumentOwnerPassword #method:setDocumentOwnerPassword#

#if defined(ENABLE_OVERLOADING)
    SigningDataSetDocumentOwnerPasswordMethodInfo,
#endif
    signingDataSetDocumentOwnerPassword     ,


-- ** setDocumentUserPassword #method:setDocumentUserPassword#

#if defined(ENABLE_OVERLOADING)
    SigningDataSetDocumentUserPasswordMethodInfo,
#endif
    signingDataSetDocumentUserPassword      ,


-- ** setFieldPartialName #method:setFieldPartialName#

#if defined(ENABLE_OVERLOADING)
    SigningDataSetFieldPartialNameMethodInfo,
#endif
    signingDataSetFieldPartialName          ,


-- ** setFontColor #method:setFontColor#

#if defined(ENABLE_OVERLOADING)
    SigningDataSetFontColorMethodInfo       ,
#endif
    signingDataSetFontColor                 ,


-- ** setFontSize #method:setFontSize#

#if defined(ENABLE_OVERLOADING)
    SigningDataSetFontSizeMethodInfo        ,
#endif
    signingDataSetFontSize                  ,


-- ** setImagePath #method:setImagePath#

#if defined(ENABLE_OVERLOADING)
    SigningDataSetImagePathMethodInfo       ,
#endif
    signingDataSetImagePath                 ,


-- ** setLeftFontSize #method:setLeftFontSize#

#if defined(ENABLE_OVERLOADING)
    SigningDataSetLeftFontSizeMethodInfo    ,
#endif
    signingDataSetLeftFontSize              ,


-- ** setLocation #method:setLocation#

#if defined(ENABLE_OVERLOADING)
    SigningDataSetLocationMethodInfo        ,
#endif
    signingDataSetLocation                  ,


-- ** setPage #method:setPage#

#if defined(ENABLE_OVERLOADING)
    SigningDataSetPageMethodInfo            ,
#endif
    signingDataSetPage                      ,


-- ** setPassword #method:setPassword#

#if defined(ENABLE_OVERLOADING)
    SigningDataSetPasswordMethodInfo        ,
#endif
    signingDataSetPassword                  ,


-- ** setReason #method:setReason#

#if defined(ENABLE_OVERLOADING)
    SigningDataSetReasonMethodInfo          ,
#endif
    signingDataSetReason                    ,


-- ** setSignatureRectangle #method:setSignatureRectangle#

#if defined(ENABLE_OVERLOADING)
    SigningDataSetSignatureRectangleMethodInfo,
#endif
    signingDataSetSignatureRectangle        ,


-- ** setSignatureText #method:setSignatureText#

#if defined(ENABLE_OVERLOADING)
    SigningDataSetSignatureTextMethodInfo   ,
#endif
    signingDataSetSignatureText             ,


-- ** setSignatureTextLeft #method:setSignatureTextLeft#

#if defined(ENABLE_OVERLOADING)
    SigningDataSetSignatureTextLeftMethodInfo,
#endif
    signingDataSetSignatureTextLeft         ,




    ) 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.GLib.Structs.DateTime as GLib.DateTime
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.Rectangle as Poppler.Rectangle

#else
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.Rectangle as Poppler.Rectangle

#endif

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

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

foreign import ccall "poppler_signing_data_get_type" c_poppler_signing_data_get_type :: 
    IO GType

type instance O.ParentTypes SigningData = '[]
instance O.HasParentTypes SigningData

instance B.Types.TypedObject SigningData where
    glibType :: IO GType
glibType = IO GType
c_poppler_signing_data_get_type

instance B.Types.GBoxed SigningData

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


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

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

foreign import ccall "poppler_signing_data_new" poppler_signing_data_new :: 
    IO (Ptr SigningData)

-- | Creates a new t'GI.Poppler.Structs.SigningData.SigningData' with default content.
-- 
-- /Since: 23.07.0/
signingDataNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m SigningData
    -- ^ __Returns:__ a new t'GI.Poppler.Structs.SigningData.SigningData'. It must be freed with 'GI.Poppler.Structs.SigningData.signingDataFree' when done.
signingDataNew :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m SigningData
signingDataNew  = IO SigningData -> m SigningData
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SigningData -> m SigningData)
-> IO SigningData -> m SigningData
forall a b. (a -> b) -> a -> b
$ do
    Ptr SigningData
result <- IO (Ptr SigningData)
poppler_signing_data_new
    Text -> Ptr SigningData -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"signingDataNew" Ptr SigningData
result
    SigningData
result' <- ((ManagedPtr SigningData -> SigningData)
-> Ptr SigningData -> IO SigningData
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr SigningData -> SigningData
SigningData) Ptr SigningData
result
    SigningData -> IO SigningData
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return SigningData
result'

#if defined(ENABLE_OVERLOADING)
#endif

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

foreign import ccall "poppler_signing_data_copy" poppler_signing_data_copy :: 
    Ptr SigningData ->                      -- signing_data : TInterface (Name {namespace = "Poppler", name = "SigningData"})
    IO (Ptr SigningData)

-- | Copies /@signingData@/, creating an identical t'GI.Poppler.Structs.SigningData.SigningData'.
-- 
-- /Since: 23.07.0/
signingDataCopy ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    SigningData
    -- ^ /@signingData@/: a t'GI.Poppler.Structs.SigningData.SigningData' structure containing signing data
    -> m SigningData
    -- ^ __Returns:__ a new t'GI.Poppler.Structs.SigningData.SigningData' structure identical to /@signingData@/
signingDataCopy :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
SigningData -> m SigningData
signingDataCopy SigningData
signingData = IO SigningData -> m SigningData
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SigningData -> m SigningData)
-> IO SigningData -> m SigningData
forall a b. (a -> b) -> a -> b
$ do
    Ptr SigningData
signingData' <- SigningData -> IO (Ptr SigningData)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SigningData
signingData
    Ptr SigningData
result <- Ptr SigningData -> IO (Ptr SigningData)
poppler_signing_data_copy Ptr SigningData
signingData'
    Text -> Ptr SigningData -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"signingDataCopy" Ptr SigningData
result
    SigningData
result' <- ((ManagedPtr SigningData -> SigningData)
-> Ptr SigningData -> IO SigningData
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr SigningData -> SigningData
SigningData) Ptr SigningData
result
    SigningData -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SigningData
signingData
    SigningData -> IO SigningData
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return SigningData
result'

#if defined(ENABLE_OVERLOADING)
data SigningDataCopyMethodInfo
instance (signature ~ (m SigningData), MonadIO m) => O.OverloadedMethod SigningDataCopyMethodInfo SigningData signature where
    overloadedMethod = signingDataCopy

instance O.OverloadedMethodInfo SigningDataCopyMethodInfo SigningData where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Poppler.Structs.SigningData.signingDataCopy",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-poppler-0.18.30/docs/GI-Poppler-Structs-SigningData.html#v:signingDataCopy"
        })


#endif

-- method SigningData::free
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "signing_data"
--           , argType =
--               TInterface Name { namespace = "Poppler" , name = "SigningData" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #PopplerSigningData structure containing signing data"
--                 , 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_signing_data_free" poppler_signing_data_free :: 
    Ptr SigningData ->                      -- signing_data : TInterface (Name {namespace = "Poppler", name = "SigningData"})
    IO ()

-- | Frees /@signingData@/
-- 
-- /Since: 23.07.0/
signingDataFree ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Maybe (SigningData)
    -- ^ /@signingData@/: a t'GI.Poppler.Structs.SigningData.SigningData' structure containing signing data
    -> m ()
signingDataFree :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Maybe SigningData -> m ()
signingDataFree Maybe SigningData
signingData = 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 SigningData
maybeSigningData <- case Maybe SigningData
signingData of
        Maybe SigningData
Nothing -> Ptr SigningData -> IO (Ptr SigningData)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr SigningData
forall a. Ptr a
nullPtr
        Just SigningData
jSigningData -> do
            Ptr SigningData
jSigningData' <- SigningData -> IO (Ptr SigningData)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SigningData
jSigningData
            Ptr SigningData -> IO (Ptr SigningData)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr SigningData
jSigningData'
    Ptr SigningData -> IO ()
poppler_signing_data_free Ptr SigningData
maybeSigningData
    Maybe SigningData -> (SigningData -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe SigningData
signingData SigningData -> 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 SigningDataFreeMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod SigningDataFreeMethodInfo SigningData signature where
    overloadedMethod i = signingDataFree (Just i)

instance O.OverloadedMethodInfo SigningDataFreeMethodInfo SigningData where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Poppler.Structs.SigningData.signingDataFree",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-poppler-0.18.30/docs/GI-Poppler-Structs-SigningData.html#v:signingDataFree"
        })


#endif

-- method SigningData::get_background_color
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "signing_data"
--           , argType =
--               TInterface Name { namespace = "Poppler" , name = "SigningData" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #PopplerSigningData structure containing signing data"
--                 , 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_signing_data_get_background_color" poppler_signing_data_get_background_color :: 
    Ptr SigningData ->                      -- signing_data : TInterface (Name {namespace = "Poppler", name = "SigningData"})
    IO (Ptr Poppler.Color.Color)

-- | Get signature background color.
-- 
-- /Since: 23.07.0/
signingDataGetBackgroundColor ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    SigningData
    -- ^ /@signingData@/: a t'GI.Poppler.Structs.SigningData.SigningData' structure containing signing data
    -> m Poppler.Color.Color
    -- ^ __Returns:__ a t'GI.Poppler.Structs.Color.Color'
signingDataGetBackgroundColor :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
SigningData -> m Color
signingDataGetBackgroundColor SigningData
signingData = 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 SigningData
signingData' <- SigningData -> IO (Ptr SigningData)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SigningData
signingData
    Ptr Color
result <- Ptr SigningData -> IO (Ptr Color)
poppler_signing_data_get_background_color Ptr SigningData
signingData'
    Text -> Ptr Color -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"signingDataGetBackgroundColor" Ptr Color
result
    Color
result' <- ((ManagedPtr Color -> Color) -> Ptr Color -> IO Color
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Color -> Color
Poppler.Color.Color) Ptr Color
result
    SigningData -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SigningData
signingData
    Color -> IO Color
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Color
result'

#if defined(ENABLE_OVERLOADING)
data SigningDataGetBackgroundColorMethodInfo
instance (signature ~ (m Poppler.Color.Color), MonadIO m) => O.OverloadedMethod SigningDataGetBackgroundColorMethodInfo SigningData signature where
    overloadedMethod = signingDataGetBackgroundColor

instance O.OverloadedMethodInfo SigningDataGetBackgroundColorMethodInfo SigningData where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Poppler.Structs.SigningData.signingDataGetBackgroundColor",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-poppler-0.18.30/docs/GI-Poppler-Structs-SigningData.html#v:signingDataGetBackgroundColor"
        })


#endif

-- method SigningData::get_border_color
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "signing_data"
--           , argType =
--               TInterface Name { namespace = "Poppler" , name = "SigningData" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #PopplerSigningData structure containing signing data"
--                 , 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_signing_data_get_border_color" poppler_signing_data_get_border_color :: 
    Ptr SigningData ->                      -- signing_data : TInterface (Name {namespace = "Poppler", name = "SigningData"})
    IO (Ptr Poppler.Color.Color)

-- | Get signature border color.
-- 
-- /Since: 23.07.0/
signingDataGetBorderColor ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    SigningData
    -- ^ /@signingData@/: a t'GI.Poppler.Structs.SigningData.SigningData' structure containing signing data
    -> m Poppler.Color.Color
    -- ^ __Returns:__ a t'GI.Poppler.Structs.Color.Color'
signingDataGetBorderColor :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
SigningData -> m Color
signingDataGetBorderColor SigningData
signingData = 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 SigningData
signingData' <- SigningData -> IO (Ptr SigningData)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SigningData
signingData
    Ptr Color
result <- Ptr SigningData -> IO (Ptr Color)
poppler_signing_data_get_border_color Ptr SigningData
signingData'
    Text -> Ptr Color -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"signingDataGetBorderColor" Ptr Color
result
    Color
result' <- ((ManagedPtr Color -> Color) -> Ptr Color -> IO Color
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Color -> Color
Poppler.Color.Color) Ptr Color
result
    SigningData -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SigningData
signingData
    Color -> IO Color
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Color
result'

#if defined(ENABLE_OVERLOADING)
data SigningDataGetBorderColorMethodInfo
instance (signature ~ (m Poppler.Color.Color), MonadIO m) => O.OverloadedMethod SigningDataGetBorderColorMethodInfo SigningData signature where
    overloadedMethod = signingDataGetBorderColor

instance O.OverloadedMethodInfo SigningDataGetBorderColorMethodInfo SigningData where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Poppler.Structs.SigningData.signingDataGetBorderColor",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-poppler-0.18.30/docs/GI-Poppler-Structs-SigningData.html#v:signingDataGetBorderColor"
        })


#endif

-- method SigningData::get_border_width
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "signing_data"
--           , argType =
--               TInterface Name { namespace = "Poppler" , name = "SigningData" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #PopplerSigningData structure containing signing data"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TDouble)
-- throws : False
-- Skip return : False

foreign import ccall "poppler_signing_data_get_border_width" poppler_signing_data_get_border_width :: 
    Ptr SigningData ->                      -- signing_data : TInterface (Name {namespace = "Poppler", name = "SigningData"})
    IO CDouble

-- | Get signature border width.
-- 
-- /Since: 23.07.0/
signingDataGetBorderWidth ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    SigningData
    -- ^ /@signingData@/: a t'GI.Poppler.Structs.SigningData.SigningData' structure containing signing data
    -> m Double
    -- ^ __Returns:__ border width
signingDataGetBorderWidth :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
SigningData -> m Double
signingDataGetBorderWidth SigningData
signingData = IO Double -> m Double
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ do
    Ptr SigningData
signingData' <- SigningData -> IO (Ptr SigningData)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SigningData
signingData
    CDouble
result <- Ptr SigningData -> IO CDouble
poppler_signing_data_get_border_width Ptr SigningData
signingData'
    let result' :: Double
result' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
result
    SigningData -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SigningData
signingData
    Double -> IO Double
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Double
result'

#if defined(ENABLE_OVERLOADING)
data SigningDataGetBorderWidthMethodInfo
instance (signature ~ (m Double), MonadIO m) => O.OverloadedMethod SigningDataGetBorderWidthMethodInfo SigningData signature where
    overloadedMethod = signingDataGetBorderWidth

instance O.OverloadedMethodInfo SigningDataGetBorderWidthMethodInfo SigningData where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Poppler.Structs.SigningData.signingDataGetBorderWidth",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-poppler-0.18.30/docs/GI-Poppler-Structs-SigningData.html#v:signingDataGetBorderWidth"
        })


#endif

-- method SigningData::get_certificate_info
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "signing_data"
--           , argType =
--               TInterface Name { namespace = "Poppler" , name = "SigningData" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #PopplerSigningData structure containing signing data"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "Poppler" , name = "CertificateInfo" })
-- throws : False
-- Skip return : False

foreign import ccall "poppler_signing_data_get_certificate_info" poppler_signing_data_get_certificate_info :: 
    Ptr SigningData ->                      -- signing_data : TInterface (Name {namespace = "Poppler", name = "SigningData"})
    IO (Ptr Poppler.CertificateInfo.CertificateInfo)

-- | Get certification information.
-- 
-- /Since: 23.07.0/
signingDataGetCertificateInfo ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    SigningData
    -- ^ /@signingData@/: a t'GI.Poppler.Structs.SigningData.SigningData' structure containing signing data
    -> m Poppler.CertificateInfo.CertificateInfo
    -- ^ __Returns:__ a t'GI.Poppler.Structs.CertificateInfo.CertificateInfo'
signingDataGetCertificateInfo :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
SigningData -> m CertificateInfo
signingDataGetCertificateInfo SigningData
signingData = IO CertificateInfo -> m CertificateInfo
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CertificateInfo -> m CertificateInfo)
-> IO CertificateInfo -> m CertificateInfo
forall a b. (a -> b) -> a -> b
$ do
    Ptr SigningData
signingData' <- SigningData -> IO (Ptr SigningData)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SigningData
signingData
    Ptr CertificateInfo
result <- Ptr SigningData -> IO (Ptr CertificateInfo)
poppler_signing_data_get_certificate_info Ptr SigningData
signingData'
    Text -> Ptr CertificateInfo -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"signingDataGetCertificateInfo" Ptr CertificateInfo
result
    CertificateInfo
result' <- ((ManagedPtr CertificateInfo -> CertificateInfo)
-> Ptr CertificateInfo -> IO CertificateInfo
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr CertificateInfo -> CertificateInfo
Poppler.CertificateInfo.CertificateInfo) Ptr CertificateInfo
result
    SigningData -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SigningData
signingData
    CertificateInfo -> IO CertificateInfo
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CertificateInfo
result'

#if defined(ENABLE_OVERLOADING)
data SigningDataGetCertificateInfoMethodInfo
instance (signature ~ (m Poppler.CertificateInfo.CertificateInfo), MonadIO m) => O.OverloadedMethod SigningDataGetCertificateInfoMethodInfo SigningData signature where
    overloadedMethod = signingDataGetCertificateInfo

instance O.OverloadedMethodInfo SigningDataGetCertificateInfoMethodInfo SigningData where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Poppler.Structs.SigningData.signingDataGetCertificateInfo",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-poppler-0.18.30/docs/GI-Poppler-Structs-SigningData.html#v:signingDataGetCertificateInfo"
        })


#endif

-- method SigningData::get_destination_filename
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "signing_data"
--           , argType =
--               TInterface Name { namespace = "Poppler" , name = "SigningData" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #PopplerSigningData structure containing signing data"
--                 , 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_signing_data_get_destination_filename" poppler_signing_data_get_destination_filename :: 
    Ptr SigningData ->                      -- signing_data : TInterface (Name {namespace = "Poppler", name = "SigningData"})
    IO CString

-- | Get destination file name.
-- 
-- /Since: 23.07.0/
signingDataGetDestinationFilename ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    SigningData
    -- ^ /@signingData@/: a t'GI.Poppler.Structs.SigningData.SigningData' structure containing signing data
    -> m T.Text
    -- ^ __Returns:__ destination filename
signingDataGetDestinationFilename :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
SigningData -> m Text
signingDataGetDestinationFilename SigningData
signingData = 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 SigningData
signingData' <- SigningData -> IO (Ptr SigningData)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SigningData
signingData
    CString
result <- Ptr SigningData -> IO CString
poppler_signing_data_get_destination_filename Ptr SigningData
signingData'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"signingDataGetDestinationFilename" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    SigningData -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SigningData
signingData
    Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data SigningDataGetDestinationFilenameMethodInfo
instance (signature ~ (m T.Text), MonadIO m) => O.OverloadedMethod SigningDataGetDestinationFilenameMethodInfo SigningData signature where
    overloadedMethod = signingDataGetDestinationFilename

instance O.OverloadedMethodInfo SigningDataGetDestinationFilenameMethodInfo SigningData where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Poppler.Structs.SigningData.signingDataGetDestinationFilename",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-poppler-0.18.30/docs/GI-Poppler-Structs-SigningData.html#v:signingDataGetDestinationFilename"
        })


#endif

-- method SigningData::get_document_owner_password
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "signing_data"
--           , argType =
--               TInterface Name { namespace = "Poppler" , name = "SigningData" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #PopplerSigningData structure containing signing data"
--                 , 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_signing_data_get_document_owner_password" poppler_signing_data_get_document_owner_password :: 
    Ptr SigningData ->                      -- signing_data : TInterface (Name {namespace = "Poppler", name = "SigningData"})
    IO CString

-- | Get document owner password.
-- 
-- /Since: 23.07.0/
signingDataGetDocumentOwnerPassword ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    SigningData
    -- ^ /@signingData@/: a t'GI.Poppler.Structs.SigningData.SigningData' structure containing signing data
    -> m T.Text
    -- ^ __Returns:__ document owner password (for encrypted files)
signingDataGetDocumentOwnerPassword :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
SigningData -> m Text
signingDataGetDocumentOwnerPassword SigningData
signingData = 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 SigningData
signingData' <- SigningData -> IO (Ptr SigningData)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SigningData
signingData
    CString
result <- Ptr SigningData -> IO CString
poppler_signing_data_get_document_owner_password Ptr SigningData
signingData'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"signingDataGetDocumentOwnerPassword" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    SigningData -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SigningData
signingData
    Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data SigningDataGetDocumentOwnerPasswordMethodInfo
instance (signature ~ (m T.Text), MonadIO m) => O.OverloadedMethod SigningDataGetDocumentOwnerPasswordMethodInfo SigningData signature where
    overloadedMethod = signingDataGetDocumentOwnerPassword

instance O.OverloadedMethodInfo SigningDataGetDocumentOwnerPasswordMethodInfo SigningData where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Poppler.Structs.SigningData.signingDataGetDocumentOwnerPassword",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-poppler-0.18.30/docs/GI-Poppler-Structs-SigningData.html#v:signingDataGetDocumentOwnerPassword"
        })


#endif

-- method SigningData::get_document_user_password
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "signing_data"
--           , argType =
--               TInterface Name { namespace = "Poppler" , name = "SigningData" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #PopplerSigningData structure containing signing data"
--                 , 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_signing_data_get_document_user_password" poppler_signing_data_get_document_user_password :: 
    Ptr SigningData ->                      -- signing_data : TInterface (Name {namespace = "Poppler", name = "SigningData"})
    IO CString

-- | Get document user password.
-- 
-- /Since: 23.07.0/
signingDataGetDocumentUserPassword ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    SigningData
    -- ^ /@signingData@/: a t'GI.Poppler.Structs.SigningData.SigningData' structure containing signing data
    -> m T.Text
    -- ^ __Returns:__ document user password (for encrypted files)
signingDataGetDocumentUserPassword :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
SigningData -> m Text
signingDataGetDocumentUserPassword SigningData
signingData = 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 SigningData
signingData' <- SigningData -> IO (Ptr SigningData)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SigningData
signingData
    CString
result <- Ptr SigningData -> IO CString
poppler_signing_data_get_document_user_password Ptr SigningData
signingData'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"signingDataGetDocumentUserPassword" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    SigningData -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SigningData
signingData
    Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data SigningDataGetDocumentUserPasswordMethodInfo
instance (signature ~ (m T.Text), MonadIO m) => O.OverloadedMethod SigningDataGetDocumentUserPasswordMethodInfo SigningData signature where
    overloadedMethod = signingDataGetDocumentUserPassword

instance O.OverloadedMethodInfo SigningDataGetDocumentUserPasswordMethodInfo SigningData where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Poppler.Structs.SigningData.signingDataGetDocumentUserPassword",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-poppler-0.18.30/docs/GI-Poppler-Structs-SigningData.html#v:signingDataGetDocumentUserPassword"
        })


#endif

-- method SigningData::get_field_partial_name
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "signing_data"
--           , argType =
--               TInterface Name { namespace = "Poppler" , name = "SigningData" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #PopplerSigningData structure containing signing data"
--                 , 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_signing_data_get_field_partial_name" poppler_signing_data_get_field_partial_name :: 
    Ptr SigningData ->                      -- signing_data : TInterface (Name {namespace = "Poppler", name = "SigningData"})
    IO CString

-- | Get field partial name.
-- 
-- /Since: 23.07.0/
signingDataGetFieldPartialName ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    SigningData
    -- ^ /@signingData@/: a t'GI.Poppler.Structs.SigningData.SigningData' structure containing signing data
    -> m T.Text
    -- ^ __Returns:__ field partial name
signingDataGetFieldPartialName :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
SigningData -> m Text
signingDataGetFieldPartialName SigningData
signingData = 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 SigningData
signingData' <- SigningData -> IO (Ptr SigningData)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SigningData
signingData
    CString
result <- Ptr SigningData -> IO CString
poppler_signing_data_get_field_partial_name Ptr SigningData
signingData'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"signingDataGetFieldPartialName" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    SigningData -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SigningData
signingData
    Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data SigningDataGetFieldPartialNameMethodInfo
instance (signature ~ (m T.Text), MonadIO m) => O.OverloadedMethod SigningDataGetFieldPartialNameMethodInfo SigningData signature where
    overloadedMethod = signingDataGetFieldPartialName

instance O.OverloadedMethodInfo SigningDataGetFieldPartialNameMethodInfo SigningData where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Poppler.Structs.SigningData.signingDataGetFieldPartialName",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-poppler-0.18.30/docs/GI-Poppler-Structs-SigningData.html#v:signingDataGetFieldPartialName"
        })


#endif

-- method SigningData::get_font_color
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "signing_data"
--           , argType =
--               TInterface Name { namespace = "Poppler" , name = "SigningData" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #PopplerSigningData structure containing signing data"
--                 , 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_signing_data_get_font_color" poppler_signing_data_get_font_color :: 
    Ptr SigningData ->                      -- signing_data : TInterface (Name {namespace = "Poppler", name = "SigningData"})
    IO (Ptr Poppler.Color.Color)

-- | Get signature font color.
-- 
-- /Since: 23.07.0/
signingDataGetFontColor ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    SigningData
    -- ^ /@signingData@/: a t'GI.Poppler.Structs.SigningData.SigningData' structure containing signing data
    -> m Poppler.Color.Color
    -- ^ __Returns:__ a t'GI.Poppler.Structs.Color.Color'
signingDataGetFontColor :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
SigningData -> m Color
signingDataGetFontColor SigningData
signingData = 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 SigningData
signingData' <- SigningData -> IO (Ptr SigningData)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SigningData
signingData
    Ptr Color
result <- Ptr SigningData -> IO (Ptr Color)
poppler_signing_data_get_font_color Ptr SigningData
signingData'
    Text -> Ptr Color -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"signingDataGetFontColor" Ptr Color
result
    Color
result' <- ((ManagedPtr Color -> Color) -> Ptr Color -> IO Color
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Color -> Color
Poppler.Color.Color) Ptr Color
result
    SigningData -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SigningData
signingData
    Color -> IO Color
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Color
result'

#if defined(ENABLE_OVERLOADING)
data SigningDataGetFontColorMethodInfo
instance (signature ~ (m Poppler.Color.Color), MonadIO m) => O.OverloadedMethod SigningDataGetFontColorMethodInfo SigningData signature where
    overloadedMethod = signingDataGetFontColor

instance O.OverloadedMethodInfo SigningDataGetFontColorMethodInfo SigningData where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Poppler.Structs.SigningData.signingDataGetFontColor",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-poppler-0.18.30/docs/GI-Poppler-Structs-SigningData.html#v:signingDataGetFontColor"
        })


#endif

-- method SigningData::get_font_size
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "signing_data"
--           , argType =
--               TInterface Name { namespace = "Poppler" , name = "SigningData" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #PopplerSigningData structure containing signing data"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TDouble)
-- throws : False
-- Skip return : False

foreign import ccall "poppler_signing_data_get_font_size" poppler_signing_data_get_font_size :: 
    Ptr SigningData ->                      -- signing_data : TInterface (Name {namespace = "Poppler", name = "SigningData"})
    IO CDouble

-- | Get signature font size.
-- 
-- /Since: 23.07.0/
signingDataGetFontSize ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    SigningData
    -- ^ /@signingData@/: a t'GI.Poppler.Structs.SigningData.SigningData' structure containing signing data
    -> m Double
    -- ^ __Returns:__ font size
signingDataGetFontSize :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
SigningData -> m Double
signingDataGetFontSize SigningData
signingData = IO Double -> m Double
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ do
    Ptr SigningData
signingData' <- SigningData -> IO (Ptr SigningData)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SigningData
signingData
    CDouble
result <- Ptr SigningData -> IO CDouble
poppler_signing_data_get_font_size Ptr SigningData
signingData'
    let result' :: Double
result' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
result
    SigningData -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SigningData
signingData
    Double -> IO Double
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Double
result'

#if defined(ENABLE_OVERLOADING)
data SigningDataGetFontSizeMethodInfo
instance (signature ~ (m Double), MonadIO m) => O.OverloadedMethod SigningDataGetFontSizeMethodInfo SigningData signature where
    overloadedMethod = signingDataGetFontSize

instance O.OverloadedMethodInfo SigningDataGetFontSizeMethodInfo SigningData where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Poppler.Structs.SigningData.signingDataGetFontSize",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-poppler-0.18.30/docs/GI-Poppler-Structs-SigningData.html#v:signingDataGetFontSize"
        })


#endif

-- method SigningData::get_image_path
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "signing_data"
--           , argType =
--               TInterface Name { namespace = "Poppler" , name = "SigningData" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #PopplerSigningData structure containing signing data"
--                 , 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_signing_data_get_image_path" poppler_signing_data_get_image_path :: 
    Ptr SigningData ->                      -- signing_data : TInterface (Name {namespace = "Poppler", name = "SigningData"})
    IO CString

-- | Get image path.
-- 
-- /Since: 23.07.0/
signingDataGetImagePath ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    SigningData
    -- ^ /@signingData@/: a t'GI.Poppler.Structs.SigningData.SigningData' structure containing signing data
    -> m T.Text
    -- ^ __Returns:__ image path
signingDataGetImagePath :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
SigningData -> m Text
signingDataGetImagePath SigningData
signingData = 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 SigningData
signingData' <- SigningData -> IO (Ptr SigningData)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SigningData
signingData
    CString
result <- Ptr SigningData -> IO CString
poppler_signing_data_get_image_path Ptr SigningData
signingData'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"signingDataGetImagePath" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    SigningData -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SigningData
signingData
    Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data SigningDataGetImagePathMethodInfo
instance (signature ~ (m T.Text), MonadIO m) => O.OverloadedMethod SigningDataGetImagePathMethodInfo SigningData signature where
    overloadedMethod = signingDataGetImagePath

instance O.OverloadedMethodInfo SigningDataGetImagePathMethodInfo SigningData where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Poppler.Structs.SigningData.signingDataGetImagePath",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-poppler-0.18.30/docs/GI-Poppler-Structs-SigningData.html#v:signingDataGetImagePath"
        })


#endif

-- method SigningData::get_left_font_size
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "signing_data"
--           , argType =
--               TInterface Name { namespace = "Poppler" , name = "SigningData" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #PopplerSigningData structure containing signing data"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TDouble)
-- throws : False
-- Skip return : False

foreign import ccall "poppler_signing_data_get_left_font_size" poppler_signing_data_get_left_font_size :: 
    Ptr SigningData ->                      -- signing_data : TInterface (Name {namespace = "Poppler", name = "SigningData"})
    IO CDouble

-- | Get signature left font size.
-- 
-- /Since: 23.07.0/
signingDataGetLeftFontSize ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    SigningData
    -- ^ /@signingData@/: a t'GI.Poppler.Structs.SigningData.SigningData' structure containing signing data
    -> m Double
    -- ^ __Returns:__ left font size
signingDataGetLeftFontSize :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
SigningData -> m Double
signingDataGetLeftFontSize SigningData
signingData = IO Double -> m Double
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ do
    Ptr SigningData
signingData' <- SigningData -> IO (Ptr SigningData)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SigningData
signingData
    CDouble
result <- Ptr SigningData -> IO CDouble
poppler_signing_data_get_left_font_size Ptr SigningData
signingData'
    let result' :: Double
result' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
result
    SigningData -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SigningData
signingData
    Double -> IO Double
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Double
result'

#if defined(ENABLE_OVERLOADING)
data SigningDataGetLeftFontSizeMethodInfo
instance (signature ~ (m Double), MonadIO m) => O.OverloadedMethod SigningDataGetLeftFontSizeMethodInfo SigningData signature where
    overloadedMethod = signingDataGetLeftFontSize

instance O.OverloadedMethodInfo SigningDataGetLeftFontSizeMethodInfo SigningData where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Poppler.Structs.SigningData.signingDataGetLeftFontSize",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-poppler-0.18.30/docs/GI-Poppler-Structs-SigningData.html#v:signingDataGetLeftFontSize"
        })


#endif

-- method SigningData::get_location
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "signing_data"
--           , argType =
--               TInterface Name { namespace = "Poppler" , name = "SigningData" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #PopplerSigningData structure containing signing data"
--                 , 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_signing_data_get_location" poppler_signing_data_get_location :: 
    Ptr SigningData ->                      -- signing_data : TInterface (Name {namespace = "Poppler", name = "SigningData"})
    IO CString

-- | Get location.
-- 
-- /Since: 23.07.0/
signingDataGetLocation ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    SigningData
    -- ^ /@signingData@/: a t'GI.Poppler.Structs.SigningData.SigningData' structure containing signing data
    -> m T.Text
    -- ^ __Returns:__ location
signingDataGetLocation :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
SigningData -> m Text
signingDataGetLocation SigningData
signingData = 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 SigningData
signingData' <- SigningData -> IO (Ptr SigningData)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SigningData
signingData
    CString
result <- Ptr SigningData -> IO CString
poppler_signing_data_get_location Ptr SigningData
signingData'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"signingDataGetLocation" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    SigningData -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SigningData
signingData
    Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data SigningDataGetLocationMethodInfo
instance (signature ~ (m T.Text), MonadIO m) => O.OverloadedMethod SigningDataGetLocationMethodInfo SigningData signature where
    overloadedMethod = signingDataGetLocation

instance O.OverloadedMethodInfo SigningDataGetLocationMethodInfo SigningData where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Poppler.Structs.SigningData.signingDataGetLocation",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-poppler-0.18.30/docs/GI-Poppler-Structs-SigningData.html#v:signingDataGetLocation"
        })


#endif

-- method SigningData::get_page
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "signing_data"
--           , argType =
--               TInterface Name { namespace = "Poppler" , name = "SigningData" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #PopplerSigningData structure containing signing data"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TInt)
-- throws : False
-- Skip return : False

foreign import ccall "poppler_signing_data_get_page" poppler_signing_data_get_page :: 
    Ptr SigningData ->                      -- signing_data : TInterface (Name {namespace = "Poppler", name = "SigningData"})
    IO Int32

-- | Get page.
-- 
-- /Since: 23.07.0/
signingDataGetPage ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    SigningData
    -- ^ /@signingData@/: a t'GI.Poppler.Structs.SigningData.SigningData' structure containing signing data
    -> m Int32
    -- ^ __Returns:__ page number
signingDataGetPage :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
SigningData -> m Int32
signingDataGetPage SigningData
signingData = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr SigningData
signingData' <- SigningData -> IO (Ptr SigningData)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SigningData
signingData
    Int32
result <- Ptr SigningData -> IO Int32
poppler_signing_data_get_page Ptr SigningData
signingData'
    SigningData -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SigningData
signingData
    Int32 -> IO Int32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data SigningDataGetPageMethodInfo
instance (signature ~ (m Int32), MonadIO m) => O.OverloadedMethod SigningDataGetPageMethodInfo SigningData signature where
    overloadedMethod = signingDataGetPage

instance O.OverloadedMethodInfo SigningDataGetPageMethodInfo SigningData where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Poppler.Structs.SigningData.signingDataGetPage",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-poppler-0.18.30/docs/GI-Poppler-Structs-SigningData.html#v:signingDataGetPage"
        })


#endif

-- method SigningData::get_password
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "signing_data"
--           , argType =
--               TInterface Name { namespace = "Poppler" , name = "SigningData" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #PopplerSigningData structure containing signing data"
--                 , 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_signing_data_get_password" poppler_signing_data_get_password :: 
    Ptr SigningData ->                      -- signing_data : TInterface (Name {namespace = "Poppler", name = "SigningData"})
    IO CString

-- | Get signing key password.
-- 
-- /Since: 23.07.0/
signingDataGetPassword ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    SigningData
    -- ^ /@signingData@/: a t'GI.Poppler.Structs.SigningData.SigningData' structure containing signing data
    -> m T.Text
    -- ^ __Returns:__ password
signingDataGetPassword :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
SigningData -> m Text
signingDataGetPassword SigningData
signingData = 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 SigningData
signingData' <- SigningData -> IO (Ptr SigningData)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SigningData
signingData
    CString
result <- Ptr SigningData -> IO CString
poppler_signing_data_get_password Ptr SigningData
signingData'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"signingDataGetPassword" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    SigningData -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SigningData
signingData
    Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data SigningDataGetPasswordMethodInfo
instance (signature ~ (m T.Text), MonadIO m) => O.OverloadedMethod SigningDataGetPasswordMethodInfo SigningData signature where
    overloadedMethod = signingDataGetPassword

instance O.OverloadedMethodInfo SigningDataGetPasswordMethodInfo SigningData where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Poppler.Structs.SigningData.signingDataGetPassword",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-poppler-0.18.30/docs/GI-Poppler-Structs-SigningData.html#v:signingDataGetPassword"
        })


#endif

-- method SigningData::get_reason
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "signing_data"
--           , argType =
--               TInterface Name { namespace = "Poppler" , name = "SigningData" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #PopplerSigningData structure containing signing data"
--                 , 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_signing_data_get_reason" poppler_signing_data_get_reason :: 
    Ptr SigningData ->                      -- signing_data : TInterface (Name {namespace = "Poppler", name = "SigningData"})
    IO CString

-- | Get reason.
-- 
-- /Since: 23.07.0/
signingDataGetReason ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    SigningData
    -- ^ /@signingData@/: a t'GI.Poppler.Structs.SigningData.SigningData' structure containing signing data
    -> m T.Text
    -- ^ __Returns:__ reason
signingDataGetReason :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
SigningData -> m Text
signingDataGetReason SigningData
signingData = 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 SigningData
signingData' <- SigningData -> IO (Ptr SigningData)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SigningData
signingData
    CString
result <- Ptr SigningData -> IO CString
poppler_signing_data_get_reason Ptr SigningData
signingData'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"signingDataGetReason" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    SigningData -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SigningData
signingData
    Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data SigningDataGetReasonMethodInfo
instance (signature ~ (m T.Text), MonadIO m) => O.OverloadedMethod SigningDataGetReasonMethodInfo SigningData signature where
    overloadedMethod = signingDataGetReason

instance O.OverloadedMethodInfo SigningDataGetReasonMethodInfo SigningData where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Poppler.Structs.SigningData.signingDataGetReason",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-poppler-0.18.30/docs/GI-Poppler-Structs-SigningData.html#v:signingDataGetReason"
        })


#endif

-- method SigningData::get_signature_rectangle
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "signing_data"
--           , argType =
--               TInterface Name { namespace = "Poppler" , name = "SigningData" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #PopplerSigningData structure containing signing data"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Poppler" , name = "Rectangle" })
-- throws : False
-- Skip return : False

foreign import ccall "poppler_signing_data_get_signature_rectangle" poppler_signing_data_get_signature_rectangle :: 
    Ptr SigningData ->                      -- signing_data : TInterface (Name {namespace = "Poppler", name = "SigningData"})
    IO (Ptr Poppler.Rectangle.Rectangle)

-- | Get signature rectangle.
-- 
-- /Since: 23.07.0/
signingDataGetSignatureRectangle ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    SigningData
    -- ^ /@signingData@/: a t'GI.Poppler.Structs.SigningData.SigningData' structure containing signing data
    -> m Poppler.Rectangle.Rectangle
    -- ^ __Returns:__ a t'GI.Poppler.Structs.Rectangle.Rectangle'
signingDataGetSignatureRectangle :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
SigningData -> m Rectangle
signingDataGetSignatureRectangle SigningData
signingData = IO Rectangle -> m Rectangle
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Rectangle -> m Rectangle) -> IO Rectangle -> m Rectangle
forall a b. (a -> b) -> a -> b
$ do
    Ptr SigningData
signingData' <- SigningData -> IO (Ptr SigningData)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SigningData
signingData
    Ptr Rectangle
result <- Ptr SigningData -> IO (Ptr Rectangle)
poppler_signing_data_get_signature_rectangle Ptr SigningData
signingData'
    Text -> Ptr Rectangle -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"signingDataGetSignatureRectangle" Ptr Rectangle
result
    Rectangle
result' <- ((ManagedPtr Rectangle -> Rectangle)
-> Ptr Rectangle -> IO Rectangle
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Rectangle -> Rectangle
Poppler.Rectangle.Rectangle) Ptr Rectangle
result
    SigningData -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SigningData
signingData
    Rectangle -> IO Rectangle
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Rectangle
result'

#if defined(ENABLE_OVERLOADING)
data SigningDataGetSignatureRectangleMethodInfo
instance (signature ~ (m Poppler.Rectangle.Rectangle), MonadIO m) => O.OverloadedMethod SigningDataGetSignatureRectangleMethodInfo SigningData signature where
    overloadedMethod = signingDataGetSignatureRectangle

instance O.OverloadedMethodInfo SigningDataGetSignatureRectangleMethodInfo SigningData where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Poppler.Structs.SigningData.signingDataGetSignatureRectangle",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-poppler-0.18.30/docs/GI-Poppler-Structs-SigningData.html#v:signingDataGetSignatureRectangle"
        })


#endif

-- method SigningData::get_signature_text
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "signing_data"
--           , argType =
--               TInterface Name { namespace = "Poppler" , name = "SigningData" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #PopplerSigningData structure containing signing data"
--                 , 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_signing_data_get_signature_text" poppler_signing_data_get_signature_text :: 
    Ptr SigningData ->                      -- signing_data : TInterface (Name {namespace = "Poppler", name = "SigningData"})
    IO CString

-- | Get signature text.
-- 
-- /Since: 23.07.0/
signingDataGetSignatureText ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    SigningData
    -- ^ /@signingData@/: a t'GI.Poppler.Structs.SigningData.SigningData' structure containing signing data
    -> m T.Text
    -- ^ __Returns:__ signature text
signingDataGetSignatureText :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
SigningData -> m Text
signingDataGetSignatureText SigningData
signingData = 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 SigningData
signingData' <- SigningData -> IO (Ptr SigningData)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SigningData
signingData
    CString
result <- Ptr SigningData -> IO CString
poppler_signing_data_get_signature_text Ptr SigningData
signingData'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"signingDataGetSignatureText" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    SigningData -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SigningData
signingData
    Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data SigningDataGetSignatureTextMethodInfo
instance (signature ~ (m T.Text), MonadIO m) => O.OverloadedMethod SigningDataGetSignatureTextMethodInfo SigningData signature where
    overloadedMethod = signingDataGetSignatureText

instance O.OverloadedMethodInfo SigningDataGetSignatureTextMethodInfo SigningData where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Poppler.Structs.SigningData.signingDataGetSignatureText",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-poppler-0.18.30/docs/GI-Poppler-Structs-SigningData.html#v:signingDataGetSignatureText"
        })


#endif

-- method SigningData::get_signature_text_left
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "signing_data"
--           , argType =
--               TInterface Name { namespace = "Poppler" , name = "SigningData" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #PopplerSigningData structure containing signing data"
--                 , 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_signing_data_get_signature_text_left" poppler_signing_data_get_signature_text_left :: 
    Ptr SigningData ->                      -- signing_data : TInterface (Name {namespace = "Poppler", name = "SigningData"})
    IO CString

-- | Get signature text left.
-- 
-- /Since: 23.07.0/
signingDataGetSignatureTextLeft ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    SigningData
    -- ^ /@signingData@/: a t'GI.Poppler.Structs.SigningData.SigningData' structure containing signing data
    -> m T.Text
    -- ^ __Returns:__ signature text left
signingDataGetSignatureTextLeft :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
SigningData -> m Text
signingDataGetSignatureTextLeft SigningData
signingData = 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 SigningData
signingData' <- SigningData -> IO (Ptr SigningData)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SigningData
signingData
    CString
result <- Ptr SigningData -> IO CString
poppler_signing_data_get_signature_text_left Ptr SigningData
signingData'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"signingDataGetSignatureTextLeft" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    SigningData -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SigningData
signingData
    Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data SigningDataGetSignatureTextLeftMethodInfo
instance (signature ~ (m T.Text), MonadIO m) => O.OverloadedMethod SigningDataGetSignatureTextLeftMethodInfo SigningData signature where
    overloadedMethod = signingDataGetSignatureTextLeft

instance O.OverloadedMethodInfo SigningDataGetSignatureTextLeftMethodInfo SigningData where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Poppler.Structs.SigningData.signingDataGetSignatureTextLeft",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-poppler-0.18.30/docs/GI-Poppler-Structs-SigningData.html#v:signingDataGetSignatureTextLeft"
        })


#endif

-- method SigningData::set_background_color
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "signing_data"
--           , argType =
--               TInterface Name { namespace = "Poppler" , name = "SigningData" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #PopplerSigningData structure containing signing data"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "background_color"
--           , argType =
--               TInterface Name { namespace = "Poppler" , name = "Color" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #PopplerColor to be used for signature background"
--                 , 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_signing_data_set_background_color" poppler_signing_data_set_background_color :: 
    Ptr SigningData ->                      -- signing_data : TInterface (Name {namespace = "Poppler", name = "SigningData"})
    Ptr Poppler.Color.Color ->              -- background_color : TInterface (Name {namespace = "Poppler", name = "Color"})
    IO ()

-- | Set signature background color.
-- 
-- /Since: 23.07.0/
signingDataSetBackgroundColor ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    SigningData
    -- ^ /@signingData@/: a t'GI.Poppler.Structs.SigningData.SigningData' structure containing signing data
    -> Poppler.Color.Color
    -- ^ /@backgroundColor@/: a t'GI.Poppler.Structs.Color.Color' to be used for signature background
    -> m ()
signingDataSetBackgroundColor :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
SigningData -> Color -> m ()
signingDataSetBackgroundColor SigningData
signingData Color
backgroundColor = 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 SigningData
signingData' <- SigningData -> IO (Ptr SigningData)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SigningData
signingData
    Ptr Color
backgroundColor' <- Color -> IO (Ptr Color)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Color
backgroundColor
    Ptr SigningData -> Ptr Color -> IO ()
poppler_signing_data_set_background_color Ptr SigningData
signingData' Ptr Color
backgroundColor'
    SigningData -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SigningData
signingData
    Color -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Color
backgroundColor
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data SigningDataSetBackgroundColorMethodInfo
instance (signature ~ (Poppler.Color.Color -> m ()), MonadIO m) => O.OverloadedMethod SigningDataSetBackgroundColorMethodInfo SigningData signature where
    overloadedMethod = signingDataSetBackgroundColor

instance O.OverloadedMethodInfo SigningDataSetBackgroundColorMethodInfo SigningData where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Poppler.Structs.SigningData.signingDataSetBackgroundColor",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-poppler-0.18.30/docs/GI-Poppler-Structs-SigningData.html#v:signingDataSetBackgroundColor"
        })


#endif

-- method SigningData::set_border_color
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "signing_data"
--           , argType =
--               TInterface Name { namespace = "Poppler" , name = "SigningData" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #PopplerSigningData structure containing signing data"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "border_color"
--           , argType =
--               TInterface Name { namespace = "Poppler" , name = "Color" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #PopplerColor to be used for signature border"
--                 , 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_signing_data_set_border_color" poppler_signing_data_set_border_color :: 
    Ptr SigningData ->                      -- signing_data : TInterface (Name {namespace = "Poppler", name = "SigningData"})
    Ptr Poppler.Color.Color ->              -- border_color : TInterface (Name {namespace = "Poppler", name = "Color"})
    IO ()

-- | Set signature border color.
-- 
-- /Since: 23.07.0/
signingDataSetBorderColor ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    SigningData
    -- ^ /@signingData@/: a t'GI.Poppler.Structs.SigningData.SigningData' structure containing signing data
    -> Poppler.Color.Color
    -- ^ /@borderColor@/: a t'GI.Poppler.Structs.Color.Color' to be used for signature border
    -> m ()
signingDataSetBorderColor :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
SigningData -> Color -> m ()
signingDataSetBorderColor SigningData
signingData Color
borderColor = 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 SigningData
signingData' <- SigningData -> IO (Ptr SigningData)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SigningData
signingData
    Ptr Color
borderColor' <- Color -> IO (Ptr Color)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Color
borderColor
    Ptr SigningData -> Ptr Color -> IO ()
poppler_signing_data_set_border_color Ptr SigningData
signingData' Ptr Color
borderColor'
    SigningData -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SigningData
signingData
    Color -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Color
borderColor
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data SigningDataSetBorderColorMethodInfo
instance (signature ~ (Poppler.Color.Color -> m ()), MonadIO m) => O.OverloadedMethod SigningDataSetBorderColorMethodInfo SigningData signature where
    overloadedMethod = signingDataSetBorderColor

instance O.OverloadedMethodInfo SigningDataSetBorderColorMethodInfo SigningData where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Poppler.Structs.SigningData.signingDataSetBorderColor",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-poppler-0.18.30/docs/GI-Poppler-Structs-SigningData.html#v:signingDataSetBorderColor"
        })


#endif

-- method SigningData::set_border_width
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "signing_data"
--           , argType =
--               TInterface Name { namespace = "Poppler" , name = "SigningData" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #PopplerSigningData structure containing signing data"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "border_width"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "border width" , 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_signing_data_set_border_width" poppler_signing_data_set_border_width :: 
    Ptr SigningData ->                      -- signing_data : TInterface (Name {namespace = "Poppler", name = "SigningData"})
    CDouble ->                              -- border_width : TBasicType TDouble
    IO ()

-- | Set signature border width.
-- 
-- /Since: 23.07.0/
signingDataSetBorderWidth ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    SigningData
    -- ^ /@signingData@/: a t'GI.Poppler.Structs.SigningData.SigningData' structure containing signing data
    -> Double
    -- ^ /@borderWidth@/: border width
    -> m ()
signingDataSetBorderWidth :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
SigningData -> Double -> m ()
signingDataSetBorderWidth SigningData
signingData Double
borderWidth = 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 SigningData
signingData' <- SigningData -> IO (Ptr SigningData)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SigningData
signingData
    let borderWidth' :: CDouble
borderWidth' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
borderWidth
    Ptr SigningData -> CDouble -> IO ()
poppler_signing_data_set_border_width Ptr SigningData
signingData' CDouble
borderWidth'
    SigningData -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SigningData
signingData
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data SigningDataSetBorderWidthMethodInfo
instance (signature ~ (Double -> m ()), MonadIO m) => O.OverloadedMethod SigningDataSetBorderWidthMethodInfo SigningData signature where
    overloadedMethod = signingDataSetBorderWidth

instance O.OverloadedMethodInfo SigningDataSetBorderWidthMethodInfo SigningData where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Poppler.Structs.SigningData.signingDataSetBorderWidth",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-poppler-0.18.30/docs/GI-Poppler-Structs-SigningData.html#v:signingDataSetBorderWidth"
        })


#endif

-- method SigningData::set_certificate_info
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "signing_data"
--           , argType =
--               TInterface Name { namespace = "Poppler" , name = "SigningData" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #PopplerSigningData structure containing signing data"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "certificate_info"
--           , argType =
--               TInterface
--                 Name { namespace = "Poppler" , name = "CertificateInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #PopplerCertificateInfo"
--                 , 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_signing_data_set_certificate_info" poppler_signing_data_set_certificate_info :: 
    Ptr SigningData ->                      -- signing_data : TInterface (Name {namespace = "Poppler", name = "SigningData"})
    Ptr Poppler.CertificateInfo.CertificateInfo -> -- certificate_info : TInterface (Name {namespace = "Poppler", name = "CertificateInfo"})
    IO ()

-- | Set certification information.
-- 
-- /Since: 23.07.0/
signingDataSetCertificateInfo ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    SigningData
    -- ^ /@signingData@/: a t'GI.Poppler.Structs.SigningData.SigningData' structure containing signing data
    -> Poppler.CertificateInfo.CertificateInfo
    -- ^ /@certificateInfo@/: a t'GI.Poppler.Structs.CertificateInfo.CertificateInfo'
    -> m ()
signingDataSetCertificateInfo :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
SigningData -> CertificateInfo -> m ()
signingDataSetCertificateInfo SigningData
signingData CertificateInfo
certificateInfo = 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 SigningData
signingData' <- SigningData -> IO (Ptr SigningData)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SigningData
signingData
    Ptr CertificateInfo
certificateInfo' <- CertificateInfo -> IO (Ptr CertificateInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr CertificateInfo
certificateInfo
    Ptr SigningData -> Ptr CertificateInfo -> IO ()
poppler_signing_data_set_certificate_info Ptr SigningData
signingData' Ptr CertificateInfo
certificateInfo'
    SigningData -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SigningData
signingData
    CertificateInfo -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr CertificateInfo
certificateInfo
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data SigningDataSetCertificateInfoMethodInfo
instance (signature ~ (Poppler.CertificateInfo.CertificateInfo -> m ()), MonadIO m) => O.OverloadedMethod SigningDataSetCertificateInfoMethodInfo SigningData signature where
    overloadedMethod = signingDataSetCertificateInfo

instance O.OverloadedMethodInfo SigningDataSetCertificateInfoMethodInfo SigningData where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Poppler.Structs.SigningData.signingDataSetCertificateInfo",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-poppler-0.18.30/docs/GI-Poppler-Structs-SigningData.html#v:signingDataSetCertificateInfo"
        })


#endif

-- method SigningData::set_destination_filename
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "signing_data"
--           , argType =
--               TInterface Name { namespace = "Poppler" , name = "SigningData" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #PopplerSigningData structure containing signing data"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "filename"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "destination filename"
--                 , 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_signing_data_set_destination_filename" poppler_signing_data_set_destination_filename :: 
    Ptr SigningData ->                      -- signing_data : TInterface (Name {namespace = "Poppler", name = "SigningData"})
    CString ->                              -- filename : TBasicType TUTF8
    IO ()

-- | Set destination file name.
-- 
-- /Since: 23.07.0/
signingDataSetDestinationFilename ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    SigningData
    -- ^ /@signingData@/: a t'GI.Poppler.Structs.SigningData.SigningData' structure containing signing data
    -> T.Text
    -- ^ /@filename@/: destination filename
    -> m ()
signingDataSetDestinationFilename :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
SigningData -> Text -> m ()
signingDataSetDestinationFilename SigningData
signingData Text
filename = 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 SigningData
signingData' <- SigningData -> IO (Ptr SigningData)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SigningData
signingData
    CString
filename' <- Text -> IO CString
textToCString Text
filename
    Ptr SigningData -> CString -> IO ()
poppler_signing_data_set_destination_filename Ptr SigningData
signingData' CString
filename'
    SigningData -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SigningData
signingData
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
filename'
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data SigningDataSetDestinationFilenameMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m) => O.OverloadedMethod SigningDataSetDestinationFilenameMethodInfo SigningData signature where
    overloadedMethod = signingDataSetDestinationFilename

instance O.OverloadedMethodInfo SigningDataSetDestinationFilenameMethodInfo SigningData where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Poppler.Structs.SigningData.signingDataSetDestinationFilename",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-poppler-0.18.30/docs/GI-Poppler-Structs-SigningData.html#v:signingDataSetDestinationFilename"
        })


#endif

-- method SigningData::set_document_owner_password
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "signing_data"
--           , argType =
--               TInterface Name { namespace = "Poppler" , name = "SigningData" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #PopplerSigningData structure containing signing data"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "document_owner_password"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "document owner password"
--                 , 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_signing_data_set_document_owner_password" poppler_signing_data_set_document_owner_password :: 
    Ptr SigningData ->                      -- signing_data : TInterface (Name {namespace = "Poppler", name = "SigningData"})
    CString ->                              -- document_owner_password : TBasicType TUTF8
    IO ()

-- | Set document owner password (for encrypted files).
-- 
-- /Since: 23.07.0/
signingDataSetDocumentOwnerPassword ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    SigningData
    -- ^ /@signingData@/: a t'GI.Poppler.Structs.SigningData.SigningData' structure containing signing data
    -> T.Text
    -- ^ /@documentOwnerPassword@/: document owner password
    -> m ()
signingDataSetDocumentOwnerPassword :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
SigningData -> Text -> m ()
signingDataSetDocumentOwnerPassword SigningData
signingData Text
documentOwnerPassword = 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 SigningData
signingData' <- SigningData -> IO (Ptr SigningData)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SigningData
signingData
    CString
documentOwnerPassword' <- Text -> IO CString
textToCString Text
documentOwnerPassword
    Ptr SigningData -> CString -> IO ()
poppler_signing_data_set_document_owner_password Ptr SigningData
signingData' CString
documentOwnerPassword'
    SigningData -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SigningData
signingData
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
documentOwnerPassword'
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data SigningDataSetDocumentOwnerPasswordMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m) => O.OverloadedMethod SigningDataSetDocumentOwnerPasswordMethodInfo SigningData signature where
    overloadedMethod = signingDataSetDocumentOwnerPassword

instance O.OverloadedMethodInfo SigningDataSetDocumentOwnerPasswordMethodInfo SigningData where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Poppler.Structs.SigningData.signingDataSetDocumentOwnerPassword",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-poppler-0.18.30/docs/GI-Poppler-Structs-SigningData.html#v:signingDataSetDocumentOwnerPassword"
        })


#endif

-- method SigningData::set_document_user_password
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "signing_data"
--           , argType =
--               TInterface Name { namespace = "Poppler" , name = "SigningData" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #PopplerSigningData structure containing signing data"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "document_user_password"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "document user password"
--                 , 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_signing_data_set_document_user_password" poppler_signing_data_set_document_user_password :: 
    Ptr SigningData ->                      -- signing_data : TInterface (Name {namespace = "Poppler", name = "SigningData"})
    CString ->                              -- document_user_password : TBasicType TUTF8
    IO ()

-- | Set document user password (for encrypted files).
-- 
-- /Since: 23.07.0/
signingDataSetDocumentUserPassword ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    SigningData
    -- ^ /@signingData@/: a t'GI.Poppler.Structs.SigningData.SigningData' structure containing signing data
    -> T.Text
    -- ^ /@documentUserPassword@/: document user password
    -> m ()
signingDataSetDocumentUserPassword :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
SigningData -> Text -> m ()
signingDataSetDocumentUserPassword SigningData
signingData Text
documentUserPassword = 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 SigningData
signingData' <- SigningData -> IO (Ptr SigningData)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SigningData
signingData
    CString
documentUserPassword' <- Text -> IO CString
textToCString Text
documentUserPassword
    Ptr SigningData -> CString -> IO ()
poppler_signing_data_set_document_user_password Ptr SigningData
signingData' CString
documentUserPassword'
    SigningData -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SigningData
signingData
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
documentUserPassword'
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data SigningDataSetDocumentUserPasswordMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m) => O.OverloadedMethod SigningDataSetDocumentUserPasswordMethodInfo SigningData signature where
    overloadedMethod = signingDataSetDocumentUserPassword

instance O.OverloadedMethodInfo SigningDataSetDocumentUserPasswordMethodInfo SigningData where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Poppler.Structs.SigningData.signingDataSetDocumentUserPassword",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-poppler-0.18.30/docs/GI-Poppler-Structs-SigningData.html#v:signingDataSetDocumentUserPassword"
        })


#endif

-- method SigningData::set_field_partial_name
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "signing_data"
--           , argType =
--               TInterface Name { namespace = "Poppler" , name = "SigningData" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #PopplerSigningData structure containing signing data"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "field_partial_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a field partial name"
--                 , 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_signing_data_set_field_partial_name" poppler_signing_data_set_field_partial_name :: 
    Ptr SigningData ->                      -- signing_data : TInterface (Name {namespace = "Poppler", name = "SigningData"})
    CString ->                              -- field_partial_name : TBasicType TUTF8
    IO ()

-- | Set field partial name (existing field id or a new one) where signature is placed.
-- 
-- /Since: 23.07.0/
signingDataSetFieldPartialName ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    SigningData
    -- ^ /@signingData@/: a t'GI.Poppler.Structs.SigningData.SigningData' structure containing signing data
    -> T.Text
    -- ^ /@fieldPartialName@/: a field partial name
    -> m ()
signingDataSetFieldPartialName :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
SigningData -> Text -> m ()
signingDataSetFieldPartialName SigningData
signingData Text
fieldPartialName = 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 SigningData
signingData' <- SigningData -> IO (Ptr SigningData)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SigningData
signingData
    CString
fieldPartialName' <- Text -> IO CString
textToCString Text
fieldPartialName
    Ptr SigningData -> CString -> IO ()
poppler_signing_data_set_field_partial_name Ptr SigningData
signingData' CString
fieldPartialName'
    SigningData -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SigningData
signingData
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
fieldPartialName'
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data SigningDataSetFieldPartialNameMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m) => O.OverloadedMethod SigningDataSetFieldPartialNameMethodInfo SigningData signature where
    overloadedMethod = signingDataSetFieldPartialName

instance O.OverloadedMethodInfo SigningDataSetFieldPartialNameMethodInfo SigningData where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Poppler.Structs.SigningData.signingDataSetFieldPartialName",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-poppler-0.18.30/docs/GI-Poppler-Structs-SigningData.html#v:signingDataSetFieldPartialName"
        })


#endif

-- method SigningData::set_font_color
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "signing_data"
--           , argType =
--               TInterface Name { namespace = "Poppler" , name = "SigningData" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #PopplerSigningData structure containing signing data"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "font_color"
--           , argType =
--               TInterface Name { namespace = "Poppler" , name = "Color" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #PopplerColor to be used as signature font color"
--                 , 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_signing_data_set_font_color" poppler_signing_data_set_font_color :: 
    Ptr SigningData ->                      -- signing_data : TInterface (Name {namespace = "Poppler", name = "SigningData"})
    Ptr Poppler.Color.Color ->              -- font_color : TInterface (Name {namespace = "Poppler", name = "Color"})
    IO ()

-- | Set signature font color.
-- 
-- /Since: 23.07.0/
signingDataSetFontColor ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    SigningData
    -- ^ /@signingData@/: a t'GI.Poppler.Structs.SigningData.SigningData' structure containing signing data
    -> Poppler.Color.Color
    -- ^ /@fontColor@/: a t'GI.Poppler.Structs.Color.Color' to be used as signature font color
    -> m ()
signingDataSetFontColor :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
SigningData -> Color -> m ()
signingDataSetFontColor SigningData
signingData Color
fontColor = 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 SigningData
signingData' <- SigningData -> IO (Ptr SigningData)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SigningData
signingData
    Ptr Color
fontColor' <- Color -> IO (Ptr Color)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Color
fontColor
    Ptr SigningData -> Ptr Color -> IO ()
poppler_signing_data_set_font_color Ptr SigningData
signingData' Ptr Color
fontColor'
    SigningData -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SigningData
signingData
    Color -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Color
fontColor
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data SigningDataSetFontColorMethodInfo
instance (signature ~ (Poppler.Color.Color -> m ()), MonadIO m) => O.OverloadedMethod SigningDataSetFontColorMethodInfo SigningData signature where
    overloadedMethod = signingDataSetFontColor

instance O.OverloadedMethodInfo SigningDataSetFontColorMethodInfo SigningData where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Poppler.Structs.SigningData.signingDataSetFontColor",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-poppler-0.18.30/docs/GI-Poppler-Structs-SigningData.html#v:signingDataSetFontColor"
        })


#endif

-- method SigningData::set_font_size
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "signing_data"
--           , argType =
--               TInterface Name { namespace = "Poppler" , name = "SigningData" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #PopplerSigningData structure containing signing data"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "font_size"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "signature font size"
--                 , 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_signing_data_set_font_size" poppler_signing_data_set_font_size :: 
    Ptr SigningData ->                      -- signing_data : TInterface (Name {namespace = "Poppler", name = "SigningData"})
    CDouble ->                              -- font_size : TBasicType TDouble
    IO ()

-- | Set signature font size (>0).
-- 
-- /Since: 23.07.0/
signingDataSetFontSize ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    SigningData
    -- ^ /@signingData@/: a t'GI.Poppler.Structs.SigningData.SigningData' structure containing signing data
    -> Double
    -- ^ /@fontSize@/: signature font size
    -> m ()
signingDataSetFontSize :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
SigningData -> Double -> m ()
signingDataSetFontSize SigningData
signingData Double
fontSize = 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 SigningData
signingData' <- SigningData -> IO (Ptr SigningData)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SigningData
signingData
    let fontSize' :: CDouble
fontSize' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
fontSize
    Ptr SigningData -> CDouble -> IO ()
poppler_signing_data_set_font_size Ptr SigningData
signingData' CDouble
fontSize'
    SigningData -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SigningData
signingData
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data SigningDataSetFontSizeMethodInfo
instance (signature ~ (Double -> m ()), MonadIO m) => O.OverloadedMethod SigningDataSetFontSizeMethodInfo SigningData signature where
    overloadedMethod = signingDataSetFontSize

instance O.OverloadedMethodInfo SigningDataSetFontSizeMethodInfo SigningData where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Poppler.Structs.SigningData.signingDataSetFontSize",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-poppler-0.18.30/docs/GI-Poppler-Structs-SigningData.html#v:signingDataSetFontSize"
        })


#endif

-- method SigningData::set_image_path
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "signing_data"
--           , argType =
--               TInterface Name { namespace = "Poppler" , name = "SigningData" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #PopplerSigningData structure containing signing data"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "image_path"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "signature image path"
--                 , 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_signing_data_set_image_path" poppler_signing_data_set_image_path :: 
    Ptr SigningData ->                      -- signing_data : TInterface (Name {namespace = "Poppler", name = "SigningData"})
    CString ->                              -- image_path : TBasicType TUTF8
    IO ()

-- | Set signature background (watermark) image path.
-- 
-- /Since: 23.07.0/
signingDataSetImagePath ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    SigningData
    -- ^ /@signingData@/: a t'GI.Poppler.Structs.SigningData.SigningData' structure containing signing data
    -> T.Text
    -- ^ /@imagePath@/: signature image path
    -> m ()
signingDataSetImagePath :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
SigningData -> Text -> m ()
signingDataSetImagePath SigningData
signingData Text
imagePath = 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 SigningData
signingData' <- SigningData -> IO (Ptr SigningData)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SigningData
signingData
    CString
imagePath' <- Text -> IO CString
textToCString Text
imagePath
    Ptr SigningData -> CString -> IO ()
poppler_signing_data_set_image_path Ptr SigningData
signingData' CString
imagePath'
    SigningData -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SigningData
signingData
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
imagePath'
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data SigningDataSetImagePathMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m) => O.OverloadedMethod SigningDataSetImagePathMethodInfo SigningData signature where
    overloadedMethod = signingDataSetImagePath

instance O.OverloadedMethodInfo SigningDataSetImagePathMethodInfo SigningData where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Poppler.Structs.SigningData.signingDataSetImagePath",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-poppler-0.18.30/docs/GI-Poppler-Structs-SigningData.html#v:signingDataSetImagePath"
        })


#endif

-- method SigningData::set_left_font_size
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "signing_data"
--           , argType =
--               TInterface Name { namespace = "Poppler" , name = "SigningData" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #PopplerSigningData structure containing signing data"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "font_size"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "signature font size"
--                 , 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_signing_data_set_left_font_size" poppler_signing_data_set_left_font_size :: 
    Ptr SigningData ->                      -- signing_data : TInterface (Name {namespace = "Poppler", name = "SigningData"})
    CDouble ->                              -- font_size : TBasicType TDouble
    IO ()

-- | Set signature left font size (> 0).
-- 
-- /Since: 23.07.0/
signingDataSetLeftFontSize ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    SigningData
    -- ^ /@signingData@/: a t'GI.Poppler.Structs.SigningData.SigningData' structure containing signing data
    -> Double
    -- ^ /@fontSize@/: signature font size
    -> m ()
signingDataSetLeftFontSize :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
SigningData -> Double -> m ()
signingDataSetLeftFontSize SigningData
signingData Double
fontSize = 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 SigningData
signingData' <- SigningData -> IO (Ptr SigningData)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SigningData
signingData
    let fontSize' :: CDouble
fontSize' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
fontSize
    Ptr SigningData -> CDouble -> IO ()
poppler_signing_data_set_left_font_size Ptr SigningData
signingData' CDouble
fontSize'
    SigningData -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SigningData
signingData
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data SigningDataSetLeftFontSizeMethodInfo
instance (signature ~ (Double -> m ()), MonadIO m) => O.OverloadedMethod SigningDataSetLeftFontSizeMethodInfo SigningData signature where
    overloadedMethod = signingDataSetLeftFontSize

instance O.OverloadedMethodInfo SigningDataSetLeftFontSizeMethodInfo SigningData where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Poppler.Structs.SigningData.signingDataSetLeftFontSize",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-poppler-0.18.30/docs/GI-Poppler-Structs-SigningData.html#v:signingDataSetLeftFontSize"
        })


#endif

-- method SigningData::set_location
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "signing_data"
--           , argType =
--               TInterface Name { namespace = "Poppler" , name = "SigningData" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #PopplerSigningData structure containing signing data"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "location"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a location" , 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_signing_data_set_location" poppler_signing_data_set_location :: 
    Ptr SigningData ->                      -- signing_data : TInterface (Name {namespace = "Poppler", name = "SigningData"})
    CString ->                              -- location : TBasicType TUTF8
    IO ()

-- | Set signature location (e.g. \"At my desk\").
-- 
-- /Since: 23.07.0/
signingDataSetLocation ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    SigningData
    -- ^ /@signingData@/: a t'GI.Poppler.Structs.SigningData.SigningData' structure containing signing data
    -> T.Text
    -- ^ /@location@/: a location
    -> m ()
signingDataSetLocation :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
SigningData -> Text -> m ()
signingDataSetLocation SigningData
signingData Text
location = 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 SigningData
signingData' <- SigningData -> IO (Ptr SigningData)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SigningData
signingData
    CString
location' <- Text -> IO CString
textToCString Text
location
    Ptr SigningData -> CString -> IO ()
poppler_signing_data_set_location Ptr SigningData
signingData' CString
location'
    SigningData -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SigningData
signingData
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
location'
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data SigningDataSetLocationMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m) => O.OverloadedMethod SigningDataSetLocationMethodInfo SigningData signature where
    overloadedMethod = signingDataSetLocation

instance O.OverloadedMethodInfo SigningDataSetLocationMethodInfo SigningData where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Poppler.Structs.SigningData.signingDataSetLocation",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-poppler-0.18.30/docs/GI-Poppler-Structs-SigningData.html#v:signingDataSetLocation"
        })


#endif

-- method SigningData::set_page
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "signing_data"
--           , argType =
--               TInterface Name { namespace = "Poppler" , name = "SigningData" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #PopplerSigningData structure containing signing data"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "page"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a page number" , 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_signing_data_set_page" poppler_signing_data_set_page :: 
    Ptr SigningData ->                      -- signing_data : TInterface (Name {namespace = "Poppler", name = "SigningData"})
    Int32 ->                                -- page : TBasicType TInt
    IO ()

-- | Set page (>=0).
-- 
-- /Since: 23.07.0/
signingDataSetPage ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    SigningData
    -- ^ /@signingData@/: a t'GI.Poppler.Structs.SigningData.SigningData' structure containing signing data
    -> Int32
    -- ^ /@page@/: a page number
    -> m ()
signingDataSetPage :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
SigningData -> Int32 -> m ()
signingDataSetPage SigningData
signingData Int32
page = 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 SigningData
signingData' <- SigningData -> IO (Ptr SigningData)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SigningData
signingData
    Ptr SigningData -> Int32 -> IO ()
poppler_signing_data_set_page Ptr SigningData
signingData' Int32
page
    SigningData -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SigningData
signingData
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data SigningDataSetPageMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m) => O.OverloadedMethod SigningDataSetPageMethodInfo SigningData signature where
    overloadedMethod = signingDataSetPage

instance O.OverloadedMethodInfo SigningDataSetPageMethodInfo SigningData where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Poppler.Structs.SigningData.signingDataSetPage",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-poppler-0.18.30/docs/GI-Poppler-Structs-SigningData.html#v:signingDataSetPage"
        })


#endif

-- method SigningData::set_password
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "signing_data"
--           , argType =
--               TInterface Name { namespace = "Poppler" , name = "SigningData" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #PopplerSigningData structure containing signing data"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "password"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a password" , 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_signing_data_set_password" poppler_signing_data_set_password :: 
    Ptr SigningData ->                      -- signing_data : TInterface (Name {namespace = "Poppler", name = "SigningData"})
    CString ->                              -- password : TBasicType TUTF8
    IO ()

-- | Set password for the signing key.
-- 
-- /Since: 23.07.0/
signingDataSetPassword ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    SigningData
    -- ^ /@signingData@/: a t'GI.Poppler.Structs.SigningData.SigningData' structure containing signing data
    -> T.Text
    -- ^ /@password@/: a password
    -> m ()
signingDataSetPassword :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
SigningData -> Text -> m ()
signingDataSetPassword SigningData
signingData Text
password = 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 SigningData
signingData' <- SigningData -> IO (Ptr SigningData)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SigningData
signingData
    CString
password' <- Text -> IO CString
textToCString Text
password
    Ptr SigningData -> CString -> IO ()
poppler_signing_data_set_password Ptr SigningData
signingData' CString
password'
    SigningData -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SigningData
signingData
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
password'
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data SigningDataSetPasswordMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m) => O.OverloadedMethod SigningDataSetPasswordMethodInfo SigningData signature where
    overloadedMethod = signingDataSetPassword

instance O.OverloadedMethodInfo SigningDataSetPasswordMethodInfo SigningData where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Poppler.Structs.SigningData.signingDataSetPassword",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-poppler-0.18.30/docs/GI-Poppler-Structs-SigningData.html#v:signingDataSetPassword"
        })


#endif

-- method SigningData::set_reason
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "signing_data"
--           , argType =
--               TInterface Name { namespace = "Poppler" , name = "SigningData" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #PopplerSigningData structure containing signing data"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "reason"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a reason" , 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_signing_data_set_reason" poppler_signing_data_set_reason :: 
    Ptr SigningData ->                      -- signing_data : TInterface (Name {namespace = "Poppler", name = "SigningData"})
    CString ->                              -- reason : TBasicType TUTF8
    IO ()

-- | Set reason for signature (e.g. I\'m approver).
-- 
-- /Since: 23.07.0/
signingDataSetReason ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    SigningData
    -- ^ /@signingData@/: a t'GI.Poppler.Structs.SigningData.SigningData' structure containing signing data
    -> T.Text
    -- ^ /@reason@/: a reason
    -> m ()
signingDataSetReason :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
SigningData -> Text -> m ()
signingDataSetReason SigningData
signingData Text
reason = 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 SigningData
signingData' <- SigningData -> IO (Ptr SigningData)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SigningData
signingData
    CString
reason' <- Text -> IO CString
textToCString Text
reason
    Ptr SigningData -> CString -> IO ()
poppler_signing_data_set_reason Ptr SigningData
signingData' CString
reason'
    SigningData -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SigningData
signingData
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
reason'
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data SigningDataSetReasonMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m) => O.OverloadedMethod SigningDataSetReasonMethodInfo SigningData signature where
    overloadedMethod = signingDataSetReason

instance O.OverloadedMethodInfo SigningDataSetReasonMethodInfo SigningData where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Poppler.Structs.SigningData.signingDataSetReason",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-poppler-0.18.30/docs/GI-Poppler-Structs-SigningData.html#v:signingDataSetReason"
        })


#endif

-- method SigningData::set_signature_rectangle
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "signing_data"
--           , argType =
--               TInterface Name { namespace = "Poppler" , name = "SigningData" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #PopplerSigningData structure containing signing data"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "signature_rect"
--           , argType =
--               TInterface Name { namespace = "Poppler" , name = "Rectangle" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #PopplerRectangle where signature should be shown"
--                 , 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_signing_data_set_signature_rectangle" poppler_signing_data_set_signature_rectangle :: 
    Ptr SigningData ->                      -- signing_data : TInterface (Name {namespace = "Poppler", name = "SigningData"})
    Ptr Poppler.Rectangle.Rectangle ->      -- signature_rect : TInterface (Name {namespace = "Poppler", name = "Rectangle"})
    IO ()

-- | Set signature rectangle.
-- 
-- /Since: 23.07.0/
signingDataSetSignatureRectangle ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    SigningData
    -- ^ /@signingData@/: a t'GI.Poppler.Structs.SigningData.SigningData' structure containing signing data
    -> Poppler.Rectangle.Rectangle
    -- ^ /@signatureRect@/: a t'GI.Poppler.Structs.Rectangle.Rectangle' where signature should be shown
    -> m ()
signingDataSetSignatureRectangle :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
SigningData -> Rectangle -> m ()
signingDataSetSignatureRectangle SigningData
signingData Rectangle
signatureRect = 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 SigningData
signingData' <- SigningData -> IO (Ptr SigningData)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SigningData
signingData
    Ptr Rectangle
signatureRect' <- Rectangle -> IO (Ptr Rectangle)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rectangle
signatureRect
    Ptr SigningData -> Ptr Rectangle -> IO ()
poppler_signing_data_set_signature_rectangle Ptr SigningData
signingData' Ptr Rectangle
signatureRect'
    SigningData -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SigningData
signingData
    Rectangle -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rectangle
signatureRect
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data SigningDataSetSignatureRectangleMethodInfo
instance (signature ~ (Poppler.Rectangle.Rectangle -> m ()), MonadIO m) => O.OverloadedMethod SigningDataSetSignatureRectangleMethodInfo SigningData signature where
    overloadedMethod = signingDataSetSignatureRectangle

instance O.OverloadedMethodInfo SigningDataSetSignatureRectangleMethodInfo SigningData where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Poppler.Structs.SigningData.signingDataSetSignatureRectangle",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-poppler-0.18.30/docs/GI-Poppler-Structs-SigningData.html#v:signingDataSetSignatureRectangle"
        })


#endif

-- method SigningData::set_signature_text
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "signing_data"
--           , argType =
--               TInterface Name { namespace = "Poppler" , name = "SigningData" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #PopplerSigningData structure containing signing data"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "signature_text"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "text to show as main signature"
--                 , 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_signing_data_set_signature_text" poppler_signing_data_set_signature_text :: 
    Ptr SigningData ->                      -- signing_data : TInterface (Name {namespace = "Poppler", name = "SigningData"})
    CString ->                              -- signature_text : TBasicType TUTF8
    IO ()

-- | Set signature text.
-- 
-- /Since: 23.07.0/
signingDataSetSignatureText ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    SigningData
    -- ^ /@signingData@/: a t'GI.Poppler.Structs.SigningData.SigningData' structure containing signing data
    -> T.Text
    -- ^ /@signatureText@/: text to show as main signature
    -> m ()
signingDataSetSignatureText :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
SigningData -> Text -> m ()
signingDataSetSignatureText SigningData
signingData Text
signatureText = 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 SigningData
signingData' <- SigningData -> IO (Ptr SigningData)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SigningData
signingData
    CString
signatureText' <- Text -> IO CString
textToCString Text
signatureText
    Ptr SigningData -> CString -> IO ()
poppler_signing_data_set_signature_text Ptr SigningData
signingData' CString
signatureText'
    SigningData -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SigningData
signingData
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
signatureText'
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data SigningDataSetSignatureTextMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m) => O.OverloadedMethod SigningDataSetSignatureTextMethodInfo SigningData signature where
    overloadedMethod = signingDataSetSignatureText

instance O.OverloadedMethodInfo SigningDataSetSignatureTextMethodInfo SigningData where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Poppler.Structs.SigningData.signingDataSetSignatureText",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-poppler-0.18.30/docs/GI-Poppler-Structs-SigningData.html#v:signingDataSetSignatureText"
        })


#endif

-- method SigningData::set_signature_text_left
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "signing_data"
--           , argType =
--               TInterface Name { namespace = "Poppler" , name = "SigningData" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #PopplerSigningData structure containing signing data"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "signature_text_left"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "text to show as small left signature"
--                 , 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_signing_data_set_signature_text_left" poppler_signing_data_set_signature_text_left :: 
    Ptr SigningData ->                      -- signing_data : TInterface (Name {namespace = "Poppler", name = "SigningData"})
    CString ->                              -- signature_text_left : TBasicType TUTF8
    IO ()

-- | Set small signature text on the left hand.
-- 
-- /Since: 23.07.0/
signingDataSetSignatureTextLeft ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    SigningData
    -- ^ /@signingData@/: a t'GI.Poppler.Structs.SigningData.SigningData' structure containing signing data
    -> T.Text
    -- ^ /@signatureTextLeft@/: text to show as small left signature
    -> m ()
signingDataSetSignatureTextLeft :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
SigningData -> Text -> m ()
signingDataSetSignatureTextLeft SigningData
signingData Text
signatureTextLeft = 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 SigningData
signingData' <- SigningData -> IO (Ptr SigningData)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SigningData
signingData
    CString
signatureTextLeft' <- Text -> IO CString
textToCString Text
signatureTextLeft
    Ptr SigningData -> CString -> IO ()
poppler_signing_data_set_signature_text_left Ptr SigningData
signingData' CString
signatureTextLeft'
    SigningData -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SigningData
signingData
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
signatureTextLeft'
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data SigningDataSetSignatureTextLeftMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m) => O.OverloadedMethod SigningDataSetSignatureTextLeftMethodInfo SigningData signature where
    overloadedMethod = signingDataSetSignatureTextLeft

instance O.OverloadedMethodInfo SigningDataSetSignatureTextLeftMethodInfo SigningData where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Poppler.Structs.SigningData.signingDataSetSignatureTextLeft",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-poppler-0.18.30/docs/GI-Poppler-Structs-SigningData.html#v:signingDataSetSignatureTextLeft"
        })


#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveSigningDataMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveSigningDataMethod "copy" o = SigningDataCopyMethodInfo
    ResolveSigningDataMethod "free" o = SigningDataFreeMethodInfo
    ResolveSigningDataMethod "getBackgroundColor" o = SigningDataGetBackgroundColorMethodInfo
    ResolveSigningDataMethod "getBorderColor" o = SigningDataGetBorderColorMethodInfo
    ResolveSigningDataMethod "getBorderWidth" o = SigningDataGetBorderWidthMethodInfo
    ResolveSigningDataMethod "getCertificateInfo" o = SigningDataGetCertificateInfoMethodInfo
    ResolveSigningDataMethod "getDestinationFilename" o = SigningDataGetDestinationFilenameMethodInfo
    ResolveSigningDataMethod "getDocumentOwnerPassword" o = SigningDataGetDocumentOwnerPasswordMethodInfo
    ResolveSigningDataMethod "getDocumentUserPassword" o = SigningDataGetDocumentUserPasswordMethodInfo
    ResolveSigningDataMethod "getFieldPartialName" o = SigningDataGetFieldPartialNameMethodInfo
    ResolveSigningDataMethod "getFontColor" o = SigningDataGetFontColorMethodInfo
    ResolveSigningDataMethod "getFontSize" o = SigningDataGetFontSizeMethodInfo
    ResolveSigningDataMethod "getImagePath" o = SigningDataGetImagePathMethodInfo
    ResolveSigningDataMethod "getLeftFontSize" o = SigningDataGetLeftFontSizeMethodInfo
    ResolveSigningDataMethod "getLocation" o = SigningDataGetLocationMethodInfo
    ResolveSigningDataMethod "getPage" o = SigningDataGetPageMethodInfo
    ResolveSigningDataMethod "getPassword" o = SigningDataGetPasswordMethodInfo
    ResolveSigningDataMethod "getReason" o = SigningDataGetReasonMethodInfo
    ResolveSigningDataMethod "getSignatureRectangle" o = SigningDataGetSignatureRectangleMethodInfo
    ResolveSigningDataMethod "getSignatureText" o = SigningDataGetSignatureTextMethodInfo
    ResolveSigningDataMethod "getSignatureTextLeft" o = SigningDataGetSignatureTextLeftMethodInfo
    ResolveSigningDataMethod "setBackgroundColor" o = SigningDataSetBackgroundColorMethodInfo
    ResolveSigningDataMethod "setBorderColor" o = SigningDataSetBorderColorMethodInfo
    ResolveSigningDataMethod "setBorderWidth" o = SigningDataSetBorderWidthMethodInfo
    ResolveSigningDataMethod "setCertificateInfo" o = SigningDataSetCertificateInfoMethodInfo
    ResolveSigningDataMethod "setDestinationFilename" o = SigningDataSetDestinationFilenameMethodInfo
    ResolveSigningDataMethod "setDocumentOwnerPassword" o = SigningDataSetDocumentOwnerPasswordMethodInfo
    ResolveSigningDataMethod "setDocumentUserPassword" o = SigningDataSetDocumentUserPasswordMethodInfo
    ResolveSigningDataMethod "setFieldPartialName" o = SigningDataSetFieldPartialNameMethodInfo
    ResolveSigningDataMethod "setFontColor" o = SigningDataSetFontColorMethodInfo
    ResolveSigningDataMethod "setFontSize" o = SigningDataSetFontSizeMethodInfo
    ResolveSigningDataMethod "setImagePath" o = SigningDataSetImagePathMethodInfo
    ResolveSigningDataMethod "setLeftFontSize" o = SigningDataSetLeftFontSizeMethodInfo
    ResolveSigningDataMethod "setLocation" o = SigningDataSetLocationMethodInfo
    ResolveSigningDataMethod "setPage" o = SigningDataSetPageMethodInfo
    ResolveSigningDataMethod "setPassword" o = SigningDataSetPasswordMethodInfo
    ResolveSigningDataMethod "setReason" o = SigningDataSetReasonMethodInfo
    ResolveSigningDataMethod "setSignatureRectangle" o = SigningDataSetSignatureRectangleMethodInfo
    ResolveSigningDataMethod "setSignatureText" o = SigningDataSetSignatureTextMethodInfo
    ResolveSigningDataMethod "setSignatureTextLeft" o = SigningDataSetSignatureTextLeftMethodInfo
    ResolveSigningDataMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif