{- |
Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
License    : LGPL-2.1
Maintainer : Iñaki García Etxebarria (garetxe@gmail.com)
-}

module GI.Poppler.Structs.ActionMovie
    ( 

-- * Exported types
    ActionMovie(..)                         ,
    noActionMovie                           ,


 -- * Properties
-- ** Movie
    actionMovieReadMovie                    ,


-- ** Operation
    actionMovieReadOperation                ,


-- ** Title
    actionMovieReadTitle                    ,


-- ** Type
    actionMovieReadType                     ,




    ) 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 ActionMovie = ActionMovie (ForeignPtr ActionMovie)
noActionMovie :: Maybe ActionMovie
noActionMovie = Nothing

actionMovieReadType :: ActionMovie -> IO ActionType
actionMovieReadType s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 0) :: IO CUInt
    let val' = (toEnum . fromIntegral) val
    return val'

actionMovieReadTitle :: ActionMovie -> IO T.Text
actionMovieReadTitle s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 8) :: IO CString
    val' <- cstringToText val
    return val'

actionMovieReadOperation :: ActionMovie -> IO ActionMovieOperation
actionMovieReadOperation s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 16) :: IO CUInt
    let val' = (toEnum . fromIntegral) val
    return val'

actionMovieReadMovie :: ActionMovie -> IO Movie
actionMovieReadMovie s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 24) :: IO (Ptr Movie)
    val' <- (newObject Movie) val
    return val'