module GI.Poppler.Structs.AnnotCalloutLine
(
AnnotCalloutLine(..) ,
noAnnotCalloutLine ,
annotCalloutLineCopy ,
annotCalloutLineFree ,
annotCalloutLineNew ,
annotCalloutLineReadMultiline ,
annotCalloutLineReadX1 ,
annotCalloutLineReadX2 ,
annotCalloutLineReadX3 ,
annotCalloutLineReadY1 ,
annotCalloutLineReadY2 ,
annotCalloutLineReadY3 ,
) 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
newtype AnnotCalloutLine = AnnotCalloutLine (ForeignPtr AnnotCalloutLine)
foreign import ccall "poppler_annot_callout_line_get_type" c_poppler_annot_callout_line_get_type ::
IO GType
instance BoxedObject AnnotCalloutLine where
boxedType _ = c_poppler_annot_callout_line_get_type
noAnnotCalloutLine :: Maybe AnnotCalloutLine
noAnnotCalloutLine = Nothing
annotCalloutLineReadMultiline :: AnnotCalloutLine -> IO Bool
annotCalloutLineReadMultiline s = withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 0) :: IO CInt
let val' = (/= 0) val
return val'
annotCalloutLineReadX1 :: AnnotCalloutLine -> IO Double
annotCalloutLineReadX1 s = withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 8) :: IO CDouble
let val' = realToFrac val
return val'
annotCalloutLineReadY1 :: AnnotCalloutLine -> IO Double
annotCalloutLineReadY1 s = withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 16) :: IO CDouble
let val' = realToFrac val
return val'
annotCalloutLineReadX2 :: AnnotCalloutLine -> IO Double
annotCalloutLineReadX2 s = withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 24) :: IO CDouble
let val' = realToFrac val
return val'
annotCalloutLineReadY2 :: AnnotCalloutLine -> IO Double
annotCalloutLineReadY2 s = withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 32) :: IO CDouble
let val' = realToFrac val
return val'
annotCalloutLineReadX3 :: AnnotCalloutLine -> IO Double
annotCalloutLineReadX3 s = withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 40) :: IO CDouble
let val' = realToFrac val
return val'
annotCalloutLineReadY3 :: AnnotCalloutLine -> IO Double
annotCalloutLineReadY3 s = withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 48) :: IO CDouble
let val' = realToFrac val
return val'
foreign import ccall "poppler_annot_callout_line_new" poppler_annot_callout_line_new ::
IO (Ptr AnnotCalloutLine)
annotCalloutLineNew ::
(MonadIO m) =>
m AnnotCalloutLine
annotCalloutLineNew = liftIO $ do
result <- poppler_annot_callout_line_new
checkUnexpectedReturnNULL "poppler_annot_callout_line_new" result
result' <- (wrapBoxed AnnotCalloutLine) result
return result'
foreign import ccall "poppler_annot_callout_line_copy" poppler_annot_callout_line_copy ::
Ptr AnnotCalloutLine ->
IO (Ptr AnnotCalloutLine)
annotCalloutLineCopy ::
(MonadIO m) =>
AnnotCalloutLine ->
m AnnotCalloutLine
annotCalloutLineCopy _obj = liftIO $ do
let _obj' = unsafeManagedPtrGetPtr _obj
result <- poppler_annot_callout_line_copy _obj'
checkUnexpectedReturnNULL "poppler_annot_callout_line_copy" result
result' <- (wrapBoxed AnnotCalloutLine) result
touchManagedPtr _obj
return result'
foreign import ccall "poppler_annot_callout_line_free" poppler_annot_callout_line_free ::
Ptr AnnotCalloutLine ->
IO ()
annotCalloutLineFree ::
(MonadIO m) =>
AnnotCalloutLine ->
m ()
annotCalloutLineFree _obj = liftIO $ do
let _obj' = unsafeManagedPtrGetPtr _obj
poppler_annot_callout_line_free _obj'
touchManagedPtr _obj
return ()