module GI.Poppler.Structs.Dest
(
Dest(..) ,
noDest ,
destCopy ,
destFree ,
destReadBottom ,
destReadChangeLeft ,
destReadChangeTop ,
destReadChangeZoom ,
destReadLeft ,
destReadNamedDest ,
destReadPageNum ,
destReadRight ,
destReadTop ,
destReadType ,
destReadZoom ,
) 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 Dest = Dest (ForeignPtr Dest)
foreign import ccall "poppler_dest_get_type" c_poppler_dest_get_type ::
IO GType
instance BoxedObject Dest where
boxedType _ = c_poppler_dest_get_type
noDest :: Maybe Dest
noDest = Nothing
destReadType :: Dest -> IO DestType
destReadType s = withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 0) :: IO CUInt
let val' = (toEnum . fromIntegral) val
return val'
destReadPageNum :: Dest -> IO Int32
destReadPageNum s = withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 4) :: IO Int32
return val
destReadLeft :: Dest -> IO Double
destReadLeft s = withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 8) :: IO CDouble
let val' = realToFrac val
return val'
destReadBottom :: Dest -> IO Double
destReadBottom s = withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 16) :: IO CDouble
let val' = realToFrac val
return val'
destReadRight :: Dest -> IO Double
destReadRight s = withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 24) :: IO CDouble
let val' = realToFrac val
return val'
destReadTop :: Dest -> IO Double
destReadTop s = withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 32) :: IO CDouble
let val' = realToFrac val
return val'
destReadZoom :: Dest -> IO Double
destReadZoom s = withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 40) :: IO CDouble
let val' = realToFrac val
return val'
destReadNamedDest :: Dest -> IO T.Text
destReadNamedDest s = withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 48) :: IO CString
val' <- cstringToText val
return val'
destReadChangeLeft :: Dest -> IO Word32
destReadChangeLeft s = withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 56) :: IO Word32
return val
destReadChangeTop :: Dest -> IO Word32
destReadChangeTop s = withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 60) :: IO Word32
return val
destReadChangeZoom :: Dest -> IO Word32
destReadChangeZoom s = withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 64) :: IO Word32
return val
foreign import ccall "poppler_dest_copy" poppler_dest_copy ::
Ptr Dest ->
IO (Ptr Dest)
destCopy ::
(MonadIO m) =>
Dest ->
m Dest
destCopy _obj = liftIO $ do
let _obj' = unsafeManagedPtrGetPtr _obj
result <- poppler_dest_copy _obj'
checkUnexpectedReturnNULL "poppler_dest_copy" result
result' <- (wrapBoxed Dest) result
touchManagedPtr _obj
return result'
foreign import ccall "poppler_dest_free" poppler_dest_free ::
Ptr Dest ->
IO ()
destFree ::
(MonadIO m) =>
Dest ->
m ()
destFree _obj = liftIO $ do
let _obj' = unsafeManagedPtrGetPtr _obj
poppler_dest_free _obj'
touchManagedPtr _obj
return ()