{- |
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.Gio.Objects.FilenameCompleter
    ( 

-- * Exported types
    FilenameCompleter(..)                   ,
    FilenameCompleterK                      ,
    toFilenameCompleter                     ,
    noFilenameCompleter                     ,


 -- * Methods
-- ** filenameCompleterGetCompletionSuffix
    filenameCompleterGetCompletionSuffix    ,


-- ** filenameCompleterGetCompletions
    filenameCompleterGetCompletions         ,


-- ** filenameCompleterNew
    filenameCompleterNew                    ,


-- ** filenameCompleterSetDirsOnly
    filenameCompleterSetDirsOnly            ,




 -- * Signals
-- ** GotCompletionData
    FilenameCompleterGotCompletionDataCallback,
    FilenameCompleterGotCompletionDataCallbackC,
    FilenameCompleterGotCompletionDataSignalInfo,
    afterFilenameCompleterGotCompletionData ,
    filenameCompleterGotCompletionDataCallbackWrapper,
    filenameCompleterGotCompletionDataClosure,
    mkFilenameCompleterGotCompletionDataCallback,
    noFilenameCompleterGotCompletionDataCallback,
    onFilenameCompleterGotCompletionData    ,




    ) 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.Gio.Types
import GI.Gio.Callbacks
import qualified GI.GObject as GObject

newtype FilenameCompleter = FilenameCompleter (ForeignPtr FilenameCompleter)
foreign import ccall "g_filename_completer_get_type"
    c_g_filename_completer_get_type :: IO GType

type instance ParentTypes FilenameCompleter = FilenameCompleterParentTypes
type FilenameCompleterParentTypes = '[GObject.Object]

instance GObject FilenameCompleter where
    gobjectIsInitiallyUnowned _ = False
    gobjectType _ = c_g_filename_completer_get_type
    

class GObject o => FilenameCompleterK o
instance (GObject o, IsDescendantOf FilenameCompleter o) => FilenameCompleterK o

toFilenameCompleter :: FilenameCompleterK o => o -> IO FilenameCompleter
toFilenameCompleter = unsafeCastTo FilenameCompleter

noFilenameCompleter :: Maybe FilenameCompleter
noFilenameCompleter = Nothing

-- signal FilenameCompleter::got-completion-data
type FilenameCompleterGotCompletionDataCallback =
    IO ()

noFilenameCompleterGotCompletionDataCallback :: Maybe FilenameCompleterGotCompletionDataCallback
noFilenameCompleterGotCompletionDataCallback = Nothing

type FilenameCompleterGotCompletionDataCallbackC =
    Ptr () ->                               -- object
    Ptr () ->                               -- user_data
    IO ()

foreign import ccall "wrapper"
    mkFilenameCompleterGotCompletionDataCallback :: FilenameCompleterGotCompletionDataCallbackC -> IO (FunPtr FilenameCompleterGotCompletionDataCallbackC)

filenameCompleterGotCompletionDataClosure :: FilenameCompleterGotCompletionDataCallback -> IO Closure
filenameCompleterGotCompletionDataClosure cb = newCClosure =<< mkFilenameCompleterGotCompletionDataCallback wrapped
    where wrapped = filenameCompleterGotCompletionDataCallbackWrapper cb

filenameCompleterGotCompletionDataCallbackWrapper ::
    FilenameCompleterGotCompletionDataCallback ->
    Ptr () ->
    Ptr () ->
    IO ()
filenameCompleterGotCompletionDataCallbackWrapper _cb _ _ = do
    _cb 

onFilenameCompleterGotCompletionData :: (GObject a, MonadIO m) => a -> FilenameCompleterGotCompletionDataCallback -> m SignalHandlerId
onFilenameCompleterGotCompletionData obj cb = liftIO $ connectFilenameCompleterGotCompletionData obj cb SignalConnectBefore
afterFilenameCompleterGotCompletionData :: (GObject a, MonadIO m) => a -> FilenameCompleterGotCompletionDataCallback -> m SignalHandlerId
afterFilenameCompleterGotCompletionData obj cb = connectFilenameCompleterGotCompletionData obj cb SignalConnectAfter

connectFilenameCompleterGotCompletionData :: (GObject a, MonadIO m) =>
                                             a -> FilenameCompleterGotCompletionDataCallback -> SignalConnectMode -> m SignalHandlerId
connectFilenameCompleterGotCompletionData obj cb after = liftIO $ do
    cb' <- mkFilenameCompleterGotCompletionDataCallback (filenameCompleterGotCompletionDataCallbackWrapper cb)
    connectSignalFunPtr obj "got-completion-data" cb' after

type instance AttributeList FilenameCompleter = FilenameCompleterAttributeList
type FilenameCompleterAttributeList = ('[ ] :: [(Symbol, *)])

data FilenameCompleterGotCompletionDataSignalInfo
instance SignalInfo FilenameCompleterGotCompletionDataSignalInfo where
    type HaskellCallbackType FilenameCompleterGotCompletionDataSignalInfo = FilenameCompleterGotCompletionDataCallback
    connectSignal _ = connectFilenameCompleterGotCompletionData

type instance SignalList FilenameCompleter = FilenameCompleterSignalList
type FilenameCompleterSignalList = ('[ '("got-completion-data", FilenameCompleterGotCompletionDataSignalInfo), '("notify", GObject.ObjectNotifySignalInfo), '("notify::[property]", GObjectNotifySignalInfo)] :: [(Symbol, *)])

-- method FilenameCompleter::new
-- method type : Constructor
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TInterface "Gio" "FilenameCompleter"
-- throws : False
-- Skip return : False

foreign import ccall "g_filename_completer_new" g_filename_completer_new :: 
    IO (Ptr FilenameCompleter)


filenameCompleterNew ::
    (MonadIO m) =>
    m FilenameCompleter
filenameCompleterNew  = liftIO $ do
    result <- g_filename_completer_new
    checkUnexpectedReturnNULL "g_filename_completer_new" result
    result' <- (wrapObject FilenameCompleter) result
    return result'

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

foreign import ccall "g_filename_completer_get_completion_suffix" g_filename_completer_get_completion_suffix :: 
    Ptr FilenameCompleter ->                -- _obj : TInterface "Gio" "FilenameCompleter"
    CString ->                              -- initial_text : TBasicType TUTF8
    IO CString


filenameCompleterGetCompletionSuffix ::
    (MonadIO m, FilenameCompleterK a) =>
    a ->                                    -- _obj
    T.Text ->                               -- initial_text
    m T.Text
filenameCompleterGetCompletionSuffix _obj initial_text = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    initial_text' <- textToCString initial_text
    result <- g_filename_completer_get_completion_suffix _obj' initial_text'
    checkUnexpectedReturnNULL "g_filename_completer_get_completion_suffix" result
    result' <- cstringToText result
    freeMem result
    touchManagedPtr _obj
    freeMem initial_text'
    return result'

-- method FilenameCompleter::get_completions
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gio" "FilenameCompleter", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "initial_text", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gio" "FilenameCompleter", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "initial_text", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TCArray True (-1) (-1) (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "g_filename_completer_get_completions" g_filename_completer_get_completions :: 
    Ptr FilenameCompleter ->                -- _obj : TInterface "Gio" "FilenameCompleter"
    CString ->                              -- initial_text : TBasicType TUTF8
    IO (Ptr CString)


filenameCompleterGetCompletions ::
    (MonadIO m, FilenameCompleterK a) =>
    a ->                                    -- _obj
    T.Text ->                               -- initial_text
    m [T.Text]
filenameCompleterGetCompletions _obj initial_text = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    initial_text' <- textToCString initial_text
    result <- g_filename_completer_get_completions _obj' initial_text'
    checkUnexpectedReturnNULL "g_filename_completer_get_completions" result
    result' <- unpackZeroTerminatedUTF8CArray result
    mapZeroTerminatedCArray freeMem result
    freeMem result
    touchManagedPtr _obj
    freeMem initial_text'
    return result'

-- method FilenameCompleter::set_dirs_only
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gio" "FilenameCompleter", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "dirs_only", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gio" "FilenameCompleter", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "dirs_only", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_filename_completer_set_dirs_only" g_filename_completer_set_dirs_only :: 
    Ptr FilenameCompleter ->                -- _obj : TInterface "Gio" "FilenameCompleter"
    CInt ->                                 -- dirs_only : TBasicType TBoolean
    IO ()


filenameCompleterSetDirsOnly ::
    (MonadIO m, FilenameCompleterK a) =>
    a ->                                    -- _obj
    Bool ->                                 -- dirs_only
    m ()
filenameCompleterSetDirsOnly _obj dirs_only = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let dirs_only' = (fromIntegral . fromEnum) dirs_only
    g_filename_completer_set_dirs_only _obj' dirs_only'
    touchManagedPtr _obj
    return ()