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

Represents a precise time, with seconds and microseconds.
Similar to the struct timeval returned by the gettimeofday()
UNIX system call.

GLib is attempting to unify around the use of 64bit integers to
represent microsecond-precision time. As such, this type will be
removed from a future version of GLib.
-}

module GI.GLib.Structs.TimeVal
    ( 

-- * Exported types
    TimeVal(..)                             ,
    noTimeVal                               ,


 -- * Methods
-- ** timeValAdd
    timeValAdd                              ,


-- ** timeValToIso8601
    timeValToIso8601                        ,




 -- * Properties
-- ** TvSec
    timeValReadTvSec                        ,


-- ** TvUsec
    timeValReadTvUsec                       ,




    ) 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.GLib.Types
import GI.GLib.Callbacks

newtype TimeVal = TimeVal (ForeignPtr TimeVal)
noTimeVal :: Maybe TimeVal
noTimeVal = Nothing

timeValReadTvSec :: TimeVal -> IO Int64
timeValReadTvSec s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 0) :: IO Int64
    return val

timeValReadTvUsec :: TimeVal -> IO Int64
timeValReadTvUsec s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 8) :: IO Int64
    return val

-- method TimeVal::add
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "GLib" "TimeVal", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "microseconds", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "GLib" "TimeVal", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "microseconds", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_time_val_add" g_time_val_add :: 
    Ptr TimeVal ->                          -- _obj : TInterface "GLib" "TimeVal"
    Int64 ->                                -- microseconds : TBasicType TInt64
    IO ()


timeValAdd ::
    (MonadIO m) =>
    TimeVal ->                              -- _obj
    Int64 ->                                -- microseconds
    m ()
timeValAdd _obj microseconds = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    g_time_val_add _obj' microseconds
    touchManagedPtr _obj
    return ()

-- method TimeVal::to_iso8601
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "GLib" "TimeVal", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "GLib" "TimeVal", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_time_val_to_iso8601" g_time_val_to_iso8601 :: 
    Ptr TimeVal ->                          -- _obj : TInterface "GLib" "TimeVal"
    IO CString


timeValToIso8601 ::
    (MonadIO m) =>
    TimeVal ->                              -- _obj
    m T.Text
timeValToIso8601 _obj = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    result <- g_time_val_to_iso8601 _obj'
    checkUnexpectedReturnNULL "g_time_val_to_iso8601" result
    result' <- cstringToText result
    freeMem result
    touchManagedPtr _obj
    return result'