module GI.Poppler.Structs.ActionGotoRemote
(
ActionGotoRemote(..) ,
noActionGotoRemote ,
actionGotoRemoteReadDest ,
actionGotoRemoteReadFileName ,
actionGotoRemoteReadTitle ,
actionGotoRemoteReadType ,
) 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 ActionGotoRemote = ActionGotoRemote (ForeignPtr ActionGotoRemote)
noActionGotoRemote :: Maybe ActionGotoRemote
noActionGotoRemote = Nothing
actionGotoRemoteReadType :: ActionGotoRemote -> IO ActionType
actionGotoRemoteReadType s = withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 0) :: IO CUInt
let val' = (toEnum . fromIntegral) val
return val'
actionGotoRemoteReadTitle :: ActionGotoRemote -> IO T.Text
actionGotoRemoteReadTitle s = withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 8) :: IO CString
val' <- cstringToText val
return val'
actionGotoRemoteReadFileName :: ActionGotoRemote -> IO T.Text
actionGotoRemoteReadFileName s = withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 16) :: IO CString
val' <- cstringToText val
return val'
actionGotoRemoteReadDest :: ActionGotoRemote -> IO Dest
actionGotoRemoteReadDest s = withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 24) :: IO (Ptr Dest)
val' <- (newBoxed Dest) val
return val'