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

 -- * Methods
-- ** getAppName
    getAppName                              ,


-- ** getServerCaps
    getServerCaps                           ,


-- ** getServerInfo
    getServerInfo                           ,


-- ** init
    init                                    ,


-- ** isInitted
    isInitted                               ,


-- ** setAppName
    setAppName                              ,


-- ** uninit
    uninit                                  ,




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

-- function notify_uninit
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "notify_uninit" notify_uninit :: 
    IO ()


uninit ::
    (MonadIO m) =>
    m ()
uninit  = liftIO $ do
    notify_uninit
    return ()


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

foreign import ccall "notify_set_app_name" notify_set_app_name :: 
    CString ->                              -- app_name : TBasicType TUTF8
    IO ()


setAppName ::
    (MonadIO m) =>
    T.Text ->                               -- app_name
    m ()
setAppName app_name = liftIO $ do
    app_name' <- textToCString app_name
    notify_set_app_name app_name'
    freeMem app_name'
    return ()


-- function notify_is_initted
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "notify_is_initted" notify_is_initted :: 
    IO CInt


isInitted ::
    (MonadIO m) =>
    m Bool
isInitted  = liftIO $ do
    result <- notify_is_initted
    let result' = (/= 0) result
    return result'


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

foreign import ccall "notify_init" notify_init :: 
    CString ->                              -- app_name : TBasicType TUTF8
    IO CInt


init ::
    (MonadIO m) =>
    T.Text ->                               -- app_name
    m Bool
init app_name = liftIO $ do
    app_name' <- textToCString app_name
    result <- notify_init app_name'
    let result' = (/= 0) result
    freeMem app_name'
    return result'


-- function notify_get_server_info
-- Args : [Arg {argName = "ret_name", argType = TBasicType TUTF8, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "ret_vendor", argType = TBasicType TUTF8, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "ret_version", argType = TBasicType TUTF8, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "ret_spec_version", argType = TBasicType TUTF8, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}]
-- Lengths : []
-- hInArgs : []
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "notify_get_server_info" notify_get_server_info :: 
    Ptr CString ->                          -- ret_name : TBasicType TUTF8
    Ptr CString ->                          -- ret_vendor : TBasicType TUTF8
    Ptr CString ->                          -- ret_version : TBasicType TUTF8
    Ptr CString ->                          -- ret_spec_version : TBasicType TUTF8
    IO CInt


getServerInfo ::
    (MonadIO m) =>
    m (Bool,T.Text,T.Text,T.Text,T.Text)
getServerInfo  = liftIO $ do
    ret_name <- allocMem :: IO (Ptr CString)
    ret_vendor <- allocMem :: IO (Ptr CString)
    ret_version <- allocMem :: IO (Ptr CString)
    ret_spec_version <- allocMem :: IO (Ptr CString)
    result <- notify_get_server_info ret_name ret_vendor ret_version ret_spec_version
    let result' = (/= 0) result
    ret_name' <- peek ret_name
    ret_name'' <- cstringToText ret_name'
    freeMem ret_name'
    ret_vendor' <- peek ret_vendor
    ret_vendor'' <- cstringToText ret_vendor'
    freeMem ret_vendor'
    ret_version' <- peek ret_version
    ret_version'' <- cstringToText ret_version'
    freeMem ret_version'
    ret_spec_version' <- peek ret_spec_version
    ret_spec_version'' <- cstringToText ret_spec_version'
    freeMem ret_spec_version'
    freeMem ret_name
    freeMem ret_vendor
    freeMem ret_version
    freeMem ret_spec_version
    return (result', ret_name'', ret_vendor'', ret_version'', ret_spec_version'')


-- function notify_get_server_caps
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TGList (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "notify_get_server_caps" notify_get_server_caps :: 
    IO (Ptr (GList CString))


getServerCaps ::
    (MonadIO m) =>
    m [T.Text]
getServerCaps  = liftIO $ do
    result <- notify_get_server_caps
    checkUnexpectedReturnNULL "notify_get_server_caps" result
    result' <- unpackGList result
    result'' <- mapM cstringToText result'
    mapGList freeMem result
    g_list_free result
    return result''


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

foreign import ccall "notify_get_app_name" notify_get_app_name :: 
    IO CString


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