module GI.Poppler.Objects.AnnotFreeText
(
AnnotFreeText(..) ,
AnnotFreeTextK ,
toAnnotFreeText ,
noAnnotFreeText ,
annotFreeTextGetCalloutLine ,
annotFreeTextGetQuadding ,
) where
import Prelude ()
import Data.GI.Base.ShortPrelude
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import GI.Poppler.Types
import GI.Poppler.Callbacks
import qualified GI.GObject as GObject
newtype AnnotFreeText = AnnotFreeText (ForeignPtr AnnotFreeText)
foreign import ccall "poppler_annot_free_text_get_type"
c_poppler_annot_free_text_get_type :: IO GType
type instance ParentTypes AnnotFreeText = AnnotFreeTextParentTypes
type AnnotFreeTextParentTypes = '[AnnotMarkup, Annot, GObject.Object]
instance GObject AnnotFreeText where
gobjectIsInitiallyUnowned _ = False
gobjectType _ = c_poppler_annot_free_text_get_type
class GObject o => AnnotFreeTextK o
instance (GObject o, IsDescendantOf AnnotFreeText o) => AnnotFreeTextK o
toAnnotFreeText :: AnnotFreeTextK o => o -> IO AnnotFreeText
toAnnotFreeText = unsafeCastTo AnnotFreeText
noAnnotFreeText :: Maybe AnnotFreeText
noAnnotFreeText = Nothing
type instance AttributeList AnnotFreeText = AnnotFreeTextAttributeList
type AnnotFreeTextAttributeList = ('[ ] :: [(Symbol, *)])
type instance SignalList AnnotFreeText = AnnotFreeTextSignalList
type AnnotFreeTextSignalList = ('[ '("notify", GObject.ObjectNotifySignalInfo), '("notify::[property]", GObjectNotifySignalInfo)] :: [(Symbol, *)])
foreign import ccall "poppler_annot_free_text_get_callout_line" poppler_annot_free_text_get_callout_line ::
Ptr AnnotFreeText ->
IO (Ptr AnnotCalloutLine)
annotFreeTextGetCalloutLine ::
(MonadIO m, AnnotFreeTextK a) =>
a ->
m AnnotCalloutLine
annotFreeTextGetCalloutLine _obj = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
result <- poppler_annot_free_text_get_callout_line _obj'
checkUnexpectedReturnNULL "poppler_annot_free_text_get_callout_line" result
result' <- (wrapBoxed AnnotCalloutLine) result
touchManagedPtr _obj
return result'
foreign import ccall "poppler_annot_free_text_get_quadding" poppler_annot_free_text_get_quadding ::
Ptr AnnotFreeText ->
IO CUInt
annotFreeTextGetQuadding ::
(MonadIO m, AnnotFreeTextK a) =>
a ->
m AnnotFreeTextQuadding
annotFreeTextGetQuadding _obj = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
result <- poppler_annot_free_text_get_quadding _obj'
let result' = (toEnum . fromIntegral) result
touchManagedPtr _obj
return result'