{- |
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.Functions
    ( 

 -- * Methods
-- ** dateParse
    dateParse                               ,


-- ** errorQuark
    errorQuark                              ,


-- ** getBackend
    getBackend                              ,


-- ** getVersion
    getVersion                              ,




    ) 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

-- function poppler_get_version
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "poppler_get_version" poppler_get_version :: 
    IO CString


getVersion ::
    (MonadIO m) =>
    m T.Text
getVersion  = liftIO $ do
    result <- poppler_get_version
    checkUnexpectedReturnNULL "poppler_get_version" result
    result' <- cstringToText result
    return result'


-- function poppler_get_backend
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TInterface "Poppler" "Backend"
-- throws : False
-- Skip return : False

foreign import ccall "poppler_get_backend" poppler_get_backend :: 
    IO CUInt


getBackend ::
    (MonadIO m) =>
    m Backend
getBackend  = liftIO $ do
    result <- poppler_get_backend
    let result' = (toEnum . fromIntegral) result
    return result'


-- function poppler_error_quark
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TBasicType TUInt32
-- throws : False
-- Skip return : False

foreign import ccall "poppler_error_quark" poppler_error_quark :: 
    IO Word32


errorQuark ::
    (MonadIO m) =>
    m Word32
errorQuark  = liftIO $ do
    result <- poppler_error_quark
    return result


-- function poppler_date_parse
-- Args : [Arg {argName = "date", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "timet", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "date", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "timet", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "poppler_date_parse" poppler_date_parse :: 
    CString ->                              -- date : TBasicType TUTF8
    Int64 ->                                -- timet : TBasicType TInt64
    IO CInt


dateParse ::
    (MonadIO m) =>
    T.Text ->                               -- date
    Int64 ->                                -- timet
    m Bool
dateParse date timet = liftIO $ do
    date' <- textToCString date
    result <- poppler_date_parse date' timet
    let result' = (/= 0) result
    freeMem date'
    return result'