{- |
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.Gtk.Interfaces.RecentChooser
    ( 

-- * Exported types
    RecentChooser(..)                       ,
    noRecentChooser                         ,
    RecentChooserK                          ,
    toRecentChooser                         ,


 -- * Methods
-- ** recentChooserAddFilter
    recentChooserAddFilter                  ,


-- ** recentChooserGetCurrentItem
    recentChooserGetCurrentItem             ,


-- ** recentChooserGetCurrentUri
    recentChooserGetCurrentUri              ,


-- ** recentChooserGetFilter
    recentChooserGetFilter                  ,


-- ** recentChooserGetItems
    recentChooserGetItems                   ,


-- ** recentChooserGetLimit
    recentChooserGetLimit                   ,


-- ** recentChooserGetLocalOnly
    recentChooserGetLocalOnly               ,


-- ** recentChooserGetSelectMultiple
    recentChooserGetSelectMultiple          ,


-- ** recentChooserGetShowIcons
    recentChooserGetShowIcons               ,


-- ** recentChooserGetShowNotFound
    recentChooserGetShowNotFound            ,


-- ** recentChooserGetShowPrivate
    recentChooserGetShowPrivate             ,


-- ** recentChooserGetShowTips
    recentChooserGetShowTips                ,


-- ** recentChooserGetSortType
    recentChooserGetSortType                ,


-- ** recentChooserGetUris
    recentChooserGetUris                    ,


-- ** recentChooserListFilters
    recentChooserListFilters                ,


-- ** recentChooserRemoveFilter
    recentChooserRemoveFilter               ,


-- ** recentChooserSelectAll
    recentChooserSelectAll                  ,


-- ** recentChooserSelectUri
    recentChooserSelectUri                  ,


-- ** recentChooserSetCurrentUri
    recentChooserSetCurrentUri              ,


-- ** recentChooserSetFilter
    recentChooserSetFilter                  ,


-- ** recentChooserSetLimit
    recentChooserSetLimit                   ,


-- ** recentChooserSetLocalOnly
    recentChooserSetLocalOnly               ,


-- ** recentChooserSetSelectMultiple
    recentChooserSetSelectMultiple          ,


-- ** recentChooserSetShowIcons
    recentChooserSetShowIcons               ,


-- ** recentChooserSetShowNotFound
    recentChooserSetShowNotFound            ,


-- ** recentChooserSetShowPrivate
    recentChooserSetShowPrivate             ,


-- ** recentChooserSetShowTips
    recentChooserSetShowTips                ,


-- ** recentChooserSetSortFunc
    recentChooserSetSortFunc                ,


-- ** recentChooserSetSortType
    recentChooserSetSortType                ,


-- ** recentChooserUnselectAll
    recentChooserUnselectAll                ,


-- ** recentChooserUnselectUri
    recentChooserUnselectUri                ,




 -- * Properties
-- ** Filter
    RecentChooserFilterPropertyInfo         ,
    constructRecentChooserFilter            ,
    getRecentChooserFilter                  ,
    setRecentChooserFilter                  ,


-- ** Limit
    RecentChooserLimitPropertyInfo          ,
    constructRecentChooserLimit             ,
    getRecentChooserLimit                   ,
    setRecentChooserLimit                   ,


-- ** LocalOnly
    RecentChooserLocalOnlyPropertyInfo      ,
    constructRecentChooserLocalOnly         ,
    getRecentChooserLocalOnly               ,
    setRecentChooserLocalOnly               ,


-- ** RecentManager
    RecentChooserRecentManagerPropertyInfo  ,
    constructRecentChooserRecentManager     ,


-- ** SelectMultiple
    RecentChooserSelectMultiplePropertyInfo ,
    constructRecentChooserSelectMultiple    ,
    getRecentChooserSelectMultiple          ,
    setRecentChooserSelectMultiple          ,


-- ** ShowIcons
    RecentChooserShowIconsPropertyInfo      ,
    constructRecentChooserShowIcons         ,
    getRecentChooserShowIcons               ,
    setRecentChooserShowIcons               ,


-- ** ShowNotFound
    RecentChooserShowNotFoundPropertyInfo   ,
    constructRecentChooserShowNotFound      ,
    getRecentChooserShowNotFound            ,
    setRecentChooserShowNotFound            ,


-- ** ShowPrivate
    RecentChooserShowPrivatePropertyInfo    ,
    constructRecentChooserShowPrivate       ,
    getRecentChooserShowPrivate             ,
    setRecentChooserShowPrivate             ,


-- ** ShowTips
    RecentChooserShowTipsPropertyInfo       ,
    constructRecentChooserShowTips          ,
    getRecentChooserShowTips                ,
    setRecentChooserShowTips                ,


-- ** SortType
    RecentChooserSortTypePropertyInfo       ,
    constructRecentChooserSortType          ,
    getRecentChooserSortType                ,
    setRecentChooserSortType                ,




 -- * Signals
-- ** ItemActivated
    RecentChooserItemActivatedCallback      ,
    RecentChooserItemActivatedCallbackC     ,
    RecentChooserItemActivatedSignalInfo    ,
    afterRecentChooserItemActivated         ,
    mkRecentChooserItemActivatedCallback    ,
    noRecentChooserItemActivatedCallback    ,
    onRecentChooserItemActivated            ,
    recentChooserItemActivatedCallbackWrapper,
    recentChooserItemActivatedClosure       ,


-- ** SelectionChanged
    RecentChooserSelectionChangedCallback   ,
    RecentChooserSelectionChangedCallbackC  ,
    RecentChooserSelectionChangedSignalInfo ,
    afterRecentChooserSelectionChanged      ,
    mkRecentChooserSelectionChangedCallback ,
    noRecentChooserSelectionChangedCallback ,
    onRecentChooserSelectionChanged         ,
    recentChooserSelectionChangedCallbackWrapper,
    recentChooserSelectionChangedClosure    ,




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

-- interface RecentChooser 

newtype RecentChooser = RecentChooser (ForeignPtr RecentChooser)
noRecentChooser :: Maybe RecentChooser
noRecentChooser = Nothing

-- signal RecentChooser::item-activated
type RecentChooserItemActivatedCallback =
    IO ()

noRecentChooserItemActivatedCallback :: Maybe RecentChooserItemActivatedCallback
noRecentChooserItemActivatedCallback = Nothing

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

foreign import ccall "wrapper"
    mkRecentChooserItemActivatedCallback :: RecentChooserItemActivatedCallbackC -> IO (FunPtr RecentChooserItemActivatedCallbackC)

recentChooserItemActivatedClosure :: RecentChooserItemActivatedCallback -> IO Closure
recentChooserItemActivatedClosure cb = newCClosure =<< mkRecentChooserItemActivatedCallback wrapped
    where wrapped = recentChooserItemActivatedCallbackWrapper cb

recentChooserItemActivatedCallbackWrapper ::
    RecentChooserItemActivatedCallback ->
    Ptr () ->
    Ptr () ->
    IO ()
recentChooserItemActivatedCallbackWrapper _cb _ _ = do
    _cb 

onRecentChooserItemActivated :: (GObject a, MonadIO m) => a -> RecentChooserItemActivatedCallback -> m SignalHandlerId
onRecentChooserItemActivated obj cb = liftIO $ connectRecentChooserItemActivated obj cb SignalConnectBefore
afterRecentChooserItemActivated :: (GObject a, MonadIO m) => a -> RecentChooserItemActivatedCallback -> m SignalHandlerId
afterRecentChooserItemActivated obj cb = connectRecentChooserItemActivated obj cb SignalConnectAfter

connectRecentChooserItemActivated :: (GObject a, MonadIO m) =>
                                     a -> RecentChooserItemActivatedCallback -> SignalConnectMode -> m SignalHandlerId
connectRecentChooserItemActivated obj cb after = liftIO $ do
    cb' <- mkRecentChooserItemActivatedCallback (recentChooserItemActivatedCallbackWrapper cb)
    connectSignalFunPtr obj "item-activated" cb' after

-- signal RecentChooser::selection-changed
type RecentChooserSelectionChangedCallback =
    IO ()

noRecentChooserSelectionChangedCallback :: Maybe RecentChooserSelectionChangedCallback
noRecentChooserSelectionChangedCallback = Nothing

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

foreign import ccall "wrapper"
    mkRecentChooserSelectionChangedCallback :: RecentChooserSelectionChangedCallbackC -> IO (FunPtr RecentChooserSelectionChangedCallbackC)

recentChooserSelectionChangedClosure :: RecentChooserSelectionChangedCallback -> IO Closure
recentChooserSelectionChangedClosure cb = newCClosure =<< mkRecentChooserSelectionChangedCallback wrapped
    where wrapped = recentChooserSelectionChangedCallbackWrapper cb

recentChooserSelectionChangedCallbackWrapper ::
    RecentChooserSelectionChangedCallback ->
    Ptr () ->
    Ptr () ->
    IO ()
recentChooserSelectionChangedCallbackWrapper _cb _ _ = do
    _cb 

onRecentChooserSelectionChanged :: (GObject a, MonadIO m) => a -> RecentChooserSelectionChangedCallback -> m SignalHandlerId
onRecentChooserSelectionChanged obj cb = liftIO $ connectRecentChooserSelectionChanged obj cb SignalConnectBefore
afterRecentChooserSelectionChanged :: (GObject a, MonadIO m) => a -> RecentChooserSelectionChangedCallback -> m SignalHandlerId
afterRecentChooserSelectionChanged obj cb = connectRecentChooserSelectionChanged obj cb SignalConnectAfter

connectRecentChooserSelectionChanged :: (GObject a, MonadIO m) =>
                                        a -> RecentChooserSelectionChangedCallback -> SignalConnectMode -> m SignalHandlerId
connectRecentChooserSelectionChanged obj cb after = liftIO $ do
    cb' <- mkRecentChooserSelectionChangedCallback (recentChooserSelectionChangedCallbackWrapper cb)
    connectSignalFunPtr obj "selection-changed" cb' after

-- VVV Prop "filter"
   -- Type: TInterface "Gtk" "RecentFilter"
   -- Flags: [PropertyReadable,PropertyWritable]

getRecentChooserFilter :: (MonadIO m, RecentChooserK o) => o -> m RecentFilter
getRecentChooserFilter obj = liftIO $ getObjectPropertyObject obj "filter" RecentFilter

setRecentChooserFilter :: (MonadIO m, RecentChooserK o, RecentFilterK a) => o -> a -> m ()
setRecentChooserFilter obj val = liftIO $ setObjectPropertyObject obj "filter" val

constructRecentChooserFilter :: (RecentFilterK a) => a -> IO ([Char], GValue)
constructRecentChooserFilter val = constructObjectPropertyObject "filter" val

data RecentChooserFilterPropertyInfo
instance AttrInfo RecentChooserFilterPropertyInfo where
    type AttrAllowedOps RecentChooserFilterPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint RecentChooserFilterPropertyInfo = RecentFilterK
    type AttrBaseTypeConstraint RecentChooserFilterPropertyInfo = RecentChooserK
    type AttrGetType RecentChooserFilterPropertyInfo = RecentFilter
    type AttrLabel RecentChooserFilterPropertyInfo = "RecentChooser::filter"
    attrGet _ = getRecentChooserFilter
    attrSet _ = setRecentChooserFilter
    attrConstruct _ = constructRecentChooserFilter

-- VVV Prop "limit"
   -- Type: TBasicType TInt32
   -- Flags: [PropertyReadable,PropertyWritable]

getRecentChooserLimit :: (MonadIO m, RecentChooserK o) => o -> m Int32
getRecentChooserLimit obj = liftIO $ getObjectPropertyCInt obj "limit"

setRecentChooserLimit :: (MonadIO m, RecentChooserK o) => o -> Int32 -> m ()
setRecentChooserLimit obj val = liftIO $ setObjectPropertyCInt obj "limit" val

constructRecentChooserLimit :: Int32 -> IO ([Char], GValue)
constructRecentChooserLimit val = constructObjectPropertyCInt "limit" val

data RecentChooserLimitPropertyInfo
instance AttrInfo RecentChooserLimitPropertyInfo where
    type AttrAllowedOps RecentChooserLimitPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint RecentChooserLimitPropertyInfo = (~) Int32
    type AttrBaseTypeConstraint RecentChooserLimitPropertyInfo = RecentChooserK
    type AttrGetType RecentChooserLimitPropertyInfo = Int32
    type AttrLabel RecentChooserLimitPropertyInfo = "RecentChooser::limit"
    attrGet _ = getRecentChooserLimit
    attrSet _ = setRecentChooserLimit
    attrConstruct _ = constructRecentChooserLimit

-- VVV Prop "local-only"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]

getRecentChooserLocalOnly :: (MonadIO m, RecentChooserK o) => o -> m Bool
getRecentChooserLocalOnly obj = liftIO $ getObjectPropertyBool obj "local-only"

setRecentChooserLocalOnly :: (MonadIO m, RecentChooserK o) => o -> Bool -> m ()
setRecentChooserLocalOnly obj val = liftIO $ setObjectPropertyBool obj "local-only" val

constructRecentChooserLocalOnly :: Bool -> IO ([Char], GValue)
constructRecentChooserLocalOnly val = constructObjectPropertyBool "local-only" val

data RecentChooserLocalOnlyPropertyInfo
instance AttrInfo RecentChooserLocalOnlyPropertyInfo where
    type AttrAllowedOps RecentChooserLocalOnlyPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint RecentChooserLocalOnlyPropertyInfo = (~) Bool
    type AttrBaseTypeConstraint RecentChooserLocalOnlyPropertyInfo = RecentChooserK
    type AttrGetType RecentChooserLocalOnlyPropertyInfo = Bool
    type AttrLabel RecentChooserLocalOnlyPropertyInfo = "RecentChooser::local-only"
    attrGet _ = getRecentChooserLocalOnly
    attrSet _ = setRecentChooserLocalOnly
    attrConstruct _ = constructRecentChooserLocalOnly

-- VVV Prop "recent-manager"
   -- Type: TInterface "Gtk" "RecentManager"
   -- Flags: [PropertyWritable,PropertyConstructOnly]

constructRecentChooserRecentManager :: (RecentManagerK a) => a -> IO ([Char], GValue)
constructRecentChooserRecentManager val = constructObjectPropertyObject "recent-manager" val

data RecentChooserRecentManagerPropertyInfo
instance AttrInfo RecentChooserRecentManagerPropertyInfo where
    type AttrAllowedOps RecentChooserRecentManagerPropertyInfo = '[ 'AttrConstruct]
    type AttrSetTypeConstraint RecentChooserRecentManagerPropertyInfo = RecentManagerK
    type AttrBaseTypeConstraint RecentChooserRecentManagerPropertyInfo = RecentChooserK
    type AttrGetType RecentChooserRecentManagerPropertyInfo = ()
    type AttrLabel RecentChooserRecentManagerPropertyInfo = "RecentChooser::recent-manager"
    attrGet _ = undefined
    attrSet _ = undefined
    attrConstruct _ = constructRecentChooserRecentManager

-- VVV Prop "select-multiple"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]

getRecentChooserSelectMultiple :: (MonadIO m, RecentChooserK o) => o -> m Bool
getRecentChooserSelectMultiple obj = liftIO $ getObjectPropertyBool obj "select-multiple"

setRecentChooserSelectMultiple :: (MonadIO m, RecentChooserK o) => o -> Bool -> m ()
setRecentChooserSelectMultiple obj val = liftIO $ setObjectPropertyBool obj "select-multiple" val

constructRecentChooserSelectMultiple :: Bool -> IO ([Char], GValue)
constructRecentChooserSelectMultiple val = constructObjectPropertyBool "select-multiple" val

data RecentChooserSelectMultiplePropertyInfo
instance AttrInfo RecentChooserSelectMultiplePropertyInfo where
    type AttrAllowedOps RecentChooserSelectMultiplePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint RecentChooserSelectMultiplePropertyInfo = (~) Bool
    type AttrBaseTypeConstraint RecentChooserSelectMultiplePropertyInfo = RecentChooserK
    type AttrGetType RecentChooserSelectMultiplePropertyInfo = Bool
    type AttrLabel RecentChooserSelectMultiplePropertyInfo = "RecentChooser::select-multiple"
    attrGet _ = getRecentChooserSelectMultiple
    attrSet _ = setRecentChooserSelectMultiple
    attrConstruct _ = constructRecentChooserSelectMultiple

-- VVV Prop "show-icons"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]

getRecentChooserShowIcons :: (MonadIO m, RecentChooserK o) => o -> m Bool
getRecentChooserShowIcons obj = liftIO $ getObjectPropertyBool obj "show-icons"

setRecentChooserShowIcons :: (MonadIO m, RecentChooserK o) => o -> Bool -> m ()
setRecentChooserShowIcons obj val = liftIO $ setObjectPropertyBool obj "show-icons" val

constructRecentChooserShowIcons :: Bool -> IO ([Char], GValue)
constructRecentChooserShowIcons val = constructObjectPropertyBool "show-icons" val

data RecentChooserShowIconsPropertyInfo
instance AttrInfo RecentChooserShowIconsPropertyInfo where
    type AttrAllowedOps RecentChooserShowIconsPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint RecentChooserShowIconsPropertyInfo = (~) Bool
    type AttrBaseTypeConstraint RecentChooserShowIconsPropertyInfo = RecentChooserK
    type AttrGetType RecentChooserShowIconsPropertyInfo = Bool
    type AttrLabel RecentChooserShowIconsPropertyInfo = "RecentChooser::show-icons"
    attrGet _ = getRecentChooserShowIcons
    attrSet _ = setRecentChooserShowIcons
    attrConstruct _ = constructRecentChooserShowIcons

-- VVV Prop "show-not-found"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]

getRecentChooserShowNotFound :: (MonadIO m, RecentChooserK o) => o -> m Bool
getRecentChooserShowNotFound obj = liftIO $ getObjectPropertyBool obj "show-not-found"

setRecentChooserShowNotFound :: (MonadIO m, RecentChooserK o) => o -> Bool -> m ()
setRecentChooserShowNotFound obj val = liftIO $ setObjectPropertyBool obj "show-not-found" val

constructRecentChooserShowNotFound :: Bool -> IO ([Char], GValue)
constructRecentChooserShowNotFound val = constructObjectPropertyBool "show-not-found" val

data RecentChooserShowNotFoundPropertyInfo
instance AttrInfo RecentChooserShowNotFoundPropertyInfo where
    type AttrAllowedOps RecentChooserShowNotFoundPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint RecentChooserShowNotFoundPropertyInfo = (~) Bool
    type AttrBaseTypeConstraint RecentChooserShowNotFoundPropertyInfo = RecentChooserK
    type AttrGetType RecentChooserShowNotFoundPropertyInfo = Bool
    type AttrLabel RecentChooserShowNotFoundPropertyInfo = "RecentChooser::show-not-found"
    attrGet _ = getRecentChooserShowNotFound
    attrSet _ = setRecentChooserShowNotFound
    attrConstruct _ = constructRecentChooserShowNotFound

-- VVV Prop "show-private"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]

getRecentChooserShowPrivate :: (MonadIO m, RecentChooserK o) => o -> m Bool
getRecentChooserShowPrivate obj = liftIO $ getObjectPropertyBool obj "show-private"

setRecentChooserShowPrivate :: (MonadIO m, RecentChooserK o) => o -> Bool -> m ()
setRecentChooserShowPrivate obj val = liftIO $ setObjectPropertyBool obj "show-private" val

constructRecentChooserShowPrivate :: Bool -> IO ([Char], GValue)
constructRecentChooserShowPrivate val = constructObjectPropertyBool "show-private" val

data RecentChooserShowPrivatePropertyInfo
instance AttrInfo RecentChooserShowPrivatePropertyInfo where
    type AttrAllowedOps RecentChooserShowPrivatePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint RecentChooserShowPrivatePropertyInfo = (~) Bool
    type AttrBaseTypeConstraint RecentChooserShowPrivatePropertyInfo = RecentChooserK
    type AttrGetType RecentChooserShowPrivatePropertyInfo = Bool
    type AttrLabel RecentChooserShowPrivatePropertyInfo = "RecentChooser::show-private"
    attrGet _ = getRecentChooserShowPrivate
    attrSet _ = setRecentChooserShowPrivate
    attrConstruct _ = constructRecentChooserShowPrivate

-- VVV Prop "show-tips"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]

getRecentChooserShowTips :: (MonadIO m, RecentChooserK o) => o -> m Bool
getRecentChooserShowTips obj = liftIO $ getObjectPropertyBool obj "show-tips"

setRecentChooserShowTips :: (MonadIO m, RecentChooserK o) => o -> Bool -> m ()
setRecentChooserShowTips obj val = liftIO $ setObjectPropertyBool obj "show-tips" val

constructRecentChooserShowTips :: Bool -> IO ([Char], GValue)
constructRecentChooserShowTips val = constructObjectPropertyBool "show-tips" val

data RecentChooserShowTipsPropertyInfo
instance AttrInfo RecentChooserShowTipsPropertyInfo where
    type AttrAllowedOps RecentChooserShowTipsPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint RecentChooserShowTipsPropertyInfo = (~) Bool
    type AttrBaseTypeConstraint RecentChooserShowTipsPropertyInfo = RecentChooserK
    type AttrGetType RecentChooserShowTipsPropertyInfo = Bool
    type AttrLabel RecentChooserShowTipsPropertyInfo = "RecentChooser::show-tips"
    attrGet _ = getRecentChooserShowTips
    attrSet _ = setRecentChooserShowTips
    attrConstruct _ = constructRecentChooserShowTips

-- VVV Prop "sort-type"
   -- Type: TInterface "Gtk" "RecentSortType"
   -- Flags: [PropertyReadable,PropertyWritable]

getRecentChooserSortType :: (MonadIO m, RecentChooserK o) => o -> m RecentSortType
getRecentChooserSortType obj = liftIO $ getObjectPropertyEnum obj "sort-type"

setRecentChooserSortType :: (MonadIO m, RecentChooserK o) => o -> RecentSortType -> m ()
setRecentChooserSortType obj val = liftIO $ setObjectPropertyEnum obj "sort-type" val

constructRecentChooserSortType :: RecentSortType -> IO ([Char], GValue)
constructRecentChooserSortType val = constructObjectPropertyEnum "sort-type" val

data RecentChooserSortTypePropertyInfo
instance AttrInfo RecentChooserSortTypePropertyInfo where
    type AttrAllowedOps RecentChooserSortTypePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint RecentChooserSortTypePropertyInfo = (~) RecentSortType
    type AttrBaseTypeConstraint RecentChooserSortTypePropertyInfo = RecentChooserK
    type AttrGetType RecentChooserSortTypePropertyInfo = RecentSortType
    type AttrLabel RecentChooserSortTypePropertyInfo = "RecentChooser::sort-type"
    attrGet _ = getRecentChooserSortType
    attrSet _ = setRecentChooserSortType
    attrConstruct _ = constructRecentChooserSortType

type instance AttributeList RecentChooser = RecentChooserAttributeList
type RecentChooserAttributeList = ('[ '("filter", RecentChooserFilterPropertyInfo), '("limit", RecentChooserLimitPropertyInfo), '("local-only", RecentChooserLocalOnlyPropertyInfo), '("recent-manager", RecentChooserRecentManagerPropertyInfo), '("select-multiple", RecentChooserSelectMultiplePropertyInfo), '("show-icons", RecentChooserShowIconsPropertyInfo), '("show-not-found", RecentChooserShowNotFoundPropertyInfo), '("show-private", RecentChooserShowPrivatePropertyInfo), '("show-tips", RecentChooserShowTipsPropertyInfo), '("sort-type", RecentChooserSortTypePropertyInfo)] :: [(Symbol, *)])

data RecentChooserItemActivatedSignalInfo
instance SignalInfo RecentChooserItemActivatedSignalInfo where
    type HaskellCallbackType RecentChooserItemActivatedSignalInfo = RecentChooserItemActivatedCallback
    connectSignal _ = connectRecentChooserItemActivated

data RecentChooserSelectionChangedSignalInfo
instance SignalInfo RecentChooserSelectionChangedSignalInfo where
    type HaskellCallbackType RecentChooserSelectionChangedSignalInfo = RecentChooserSelectionChangedCallback
    connectSignal _ = connectRecentChooserSelectionChanged

type instance SignalList RecentChooser = RecentChooserSignalList
type RecentChooserSignalList = ('[ '("item-activated", RecentChooserItemActivatedSignalInfo), '("notify", GObject.ObjectNotifySignalInfo), '("selection-changed", RecentChooserSelectionChangedSignalInfo), '("notify::[property]", GObjectNotifySignalInfo)] :: [(Symbol, *)])

foreign import ccall "gtk_recent_chooser_get_type"
    c_gtk_recent_chooser_get_type :: IO GType

type instance ParentTypes RecentChooser = RecentChooserParentTypes
type RecentChooserParentTypes = '[GObject.Object]

instance GObject RecentChooser where
    gobjectIsInitiallyUnowned _ = False
    gobjectType _ = c_gtk_recent_chooser_get_type
    

class GObject o => RecentChooserK o
instance (GObject o, IsDescendantOf RecentChooser o) => RecentChooserK o

toRecentChooser :: RecentChooserK o => o -> IO RecentChooser
toRecentChooser = unsafeCastTo RecentChooser

-- method RecentChooser::add_filter
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "RecentChooser", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "filter", argType = TInterface "Gtk" "RecentFilter", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "RecentChooser", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "filter", argType = TInterface "Gtk" "RecentFilter", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_recent_chooser_add_filter" gtk_recent_chooser_add_filter :: 
    Ptr RecentChooser ->                    -- _obj : TInterface "Gtk" "RecentChooser"
    Ptr RecentFilter ->                     -- filter : TInterface "Gtk" "RecentFilter"
    IO ()


recentChooserAddFilter ::
    (MonadIO m, RecentChooserK a, RecentFilterK b) =>
    a ->                                    -- _obj
    b ->                                    -- filter
    m ()
recentChooserAddFilter _obj filter = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let filter' = unsafeManagedPtrCastPtr filter
    gtk_recent_chooser_add_filter _obj' filter'
    touchManagedPtr _obj
    touchManagedPtr filter
    return ()

-- method RecentChooser::get_current_item
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "RecentChooser", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "RecentChooser", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Gtk" "RecentInfo"
-- throws : False
-- Skip return : False

foreign import ccall "gtk_recent_chooser_get_current_item" gtk_recent_chooser_get_current_item :: 
    Ptr RecentChooser ->                    -- _obj : TInterface "Gtk" "RecentChooser"
    IO (Ptr RecentInfo)


recentChooserGetCurrentItem ::
    (MonadIO m, RecentChooserK a) =>
    a ->                                    -- _obj
    m RecentInfo
recentChooserGetCurrentItem _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_recent_chooser_get_current_item _obj'
    checkUnexpectedReturnNULL "gtk_recent_chooser_get_current_item" result
    result' <- (wrapBoxed RecentInfo) result
    touchManagedPtr _obj
    return result'

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

foreign import ccall "gtk_recent_chooser_get_current_uri" gtk_recent_chooser_get_current_uri :: 
    Ptr RecentChooser ->                    -- _obj : TInterface "Gtk" "RecentChooser"
    IO CString


recentChooserGetCurrentUri ::
    (MonadIO m, RecentChooserK a) =>
    a ->                                    -- _obj
    m T.Text
recentChooserGetCurrentUri _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_recent_chooser_get_current_uri _obj'
    checkUnexpectedReturnNULL "gtk_recent_chooser_get_current_uri" result
    result' <- cstringToText result
    freeMem result
    touchManagedPtr _obj
    return result'

-- method RecentChooser::get_filter
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "RecentChooser", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "RecentChooser", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Gtk" "RecentFilter"
-- throws : False
-- Skip return : False

foreign import ccall "gtk_recent_chooser_get_filter" gtk_recent_chooser_get_filter :: 
    Ptr RecentChooser ->                    -- _obj : TInterface "Gtk" "RecentChooser"
    IO (Ptr RecentFilter)


recentChooserGetFilter ::
    (MonadIO m, RecentChooserK a) =>
    a ->                                    -- _obj
    m RecentFilter
recentChooserGetFilter _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_recent_chooser_get_filter _obj'
    checkUnexpectedReturnNULL "gtk_recent_chooser_get_filter" result
    result' <- (newObject RecentFilter) result
    touchManagedPtr _obj
    return result'

-- method RecentChooser::get_items
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "RecentChooser", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "RecentChooser", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TGList (TInterface "Gtk" "RecentInfo")
-- throws : False
-- Skip return : False

foreign import ccall "gtk_recent_chooser_get_items" gtk_recent_chooser_get_items :: 
    Ptr RecentChooser ->                    -- _obj : TInterface "Gtk" "RecentChooser"
    IO (Ptr (GList (Ptr RecentInfo)))


recentChooserGetItems ::
    (MonadIO m, RecentChooserK a) =>
    a ->                                    -- _obj
    m [RecentInfo]
recentChooserGetItems _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_recent_chooser_get_items _obj'
    checkUnexpectedReturnNULL "gtk_recent_chooser_get_items" result
    result' <- unpackGList result
    result'' <- mapM (wrapBoxed RecentInfo) result'
    g_list_free result
    touchManagedPtr _obj
    return result''

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

foreign import ccall "gtk_recent_chooser_get_limit" gtk_recent_chooser_get_limit :: 
    Ptr RecentChooser ->                    -- _obj : TInterface "Gtk" "RecentChooser"
    IO Int32


recentChooserGetLimit ::
    (MonadIO m, RecentChooserK a) =>
    a ->                                    -- _obj
    m Int32
recentChooserGetLimit _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_recent_chooser_get_limit _obj'
    touchManagedPtr _obj
    return result

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

foreign import ccall "gtk_recent_chooser_get_local_only" gtk_recent_chooser_get_local_only :: 
    Ptr RecentChooser ->                    -- _obj : TInterface "Gtk" "RecentChooser"
    IO CInt


recentChooserGetLocalOnly ::
    (MonadIO m, RecentChooserK a) =>
    a ->                                    -- _obj
    m Bool
recentChooserGetLocalOnly _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_recent_chooser_get_local_only _obj'
    let result' = (/= 0) result
    touchManagedPtr _obj
    return result'

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

foreign import ccall "gtk_recent_chooser_get_select_multiple" gtk_recent_chooser_get_select_multiple :: 
    Ptr RecentChooser ->                    -- _obj : TInterface "Gtk" "RecentChooser"
    IO CInt


recentChooserGetSelectMultiple ::
    (MonadIO m, RecentChooserK a) =>
    a ->                                    -- _obj
    m Bool
recentChooserGetSelectMultiple _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_recent_chooser_get_select_multiple _obj'
    let result' = (/= 0) result
    touchManagedPtr _obj
    return result'

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

foreign import ccall "gtk_recent_chooser_get_show_icons" gtk_recent_chooser_get_show_icons :: 
    Ptr RecentChooser ->                    -- _obj : TInterface "Gtk" "RecentChooser"
    IO CInt


recentChooserGetShowIcons ::
    (MonadIO m, RecentChooserK a) =>
    a ->                                    -- _obj
    m Bool
recentChooserGetShowIcons _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_recent_chooser_get_show_icons _obj'
    let result' = (/= 0) result
    touchManagedPtr _obj
    return result'

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

foreign import ccall "gtk_recent_chooser_get_show_not_found" gtk_recent_chooser_get_show_not_found :: 
    Ptr RecentChooser ->                    -- _obj : TInterface "Gtk" "RecentChooser"
    IO CInt


recentChooserGetShowNotFound ::
    (MonadIO m, RecentChooserK a) =>
    a ->                                    -- _obj
    m Bool
recentChooserGetShowNotFound _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_recent_chooser_get_show_not_found _obj'
    let result' = (/= 0) result
    touchManagedPtr _obj
    return result'

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

foreign import ccall "gtk_recent_chooser_get_show_private" gtk_recent_chooser_get_show_private :: 
    Ptr RecentChooser ->                    -- _obj : TInterface "Gtk" "RecentChooser"
    IO CInt


recentChooserGetShowPrivate ::
    (MonadIO m, RecentChooserK a) =>
    a ->                                    -- _obj
    m Bool
recentChooserGetShowPrivate _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_recent_chooser_get_show_private _obj'
    let result' = (/= 0) result
    touchManagedPtr _obj
    return result'

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

foreign import ccall "gtk_recent_chooser_get_show_tips" gtk_recent_chooser_get_show_tips :: 
    Ptr RecentChooser ->                    -- _obj : TInterface "Gtk" "RecentChooser"
    IO CInt


recentChooserGetShowTips ::
    (MonadIO m, RecentChooserK a) =>
    a ->                                    -- _obj
    m Bool
recentChooserGetShowTips _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_recent_chooser_get_show_tips _obj'
    let result' = (/= 0) result
    touchManagedPtr _obj
    return result'

-- method RecentChooser::get_sort_type
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "RecentChooser", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "RecentChooser", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Gtk" "RecentSortType"
-- throws : False
-- Skip return : False

foreign import ccall "gtk_recent_chooser_get_sort_type" gtk_recent_chooser_get_sort_type :: 
    Ptr RecentChooser ->                    -- _obj : TInterface "Gtk" "RecentChooser"
    IO CUInt


recentChooserGetSortType ::
    (MonadIO m, RecentChooserK a) =>
    a ->                                    -- _obj
    m RecentSortType
recentChooserGetSortType _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_recent_chooser_get_sort_type _obj'
    let result' = (toEnum . fromIntegral) result
    touchManagedPtr _obj
    return result'

-- method RecentChooser::get_uris
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "RecentChooser", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "length", argType = TBasicType TUInt64, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "RecentChooser", 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 "gtk_recent_chooser_get_uris" gtk_recent_chooser_get_uris :: 
    Ptr RecentChooser ->                    -- _obj : TInterface "Gtk" "RecentChooser"
    Ptr Word64 ->                           -- length : TBasicType TUInt64
    IO (Ptr CString)


recentChooserGetUris ::
    (MonadIO m, RecentChooserK a) =>
    a ->                                    -- _obj
    m ([T.Text],Word64)
recentChooserGetUris _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    length_ <- allocMem :: IO (Ptr Word64)
    result <- gtk_recent_chooser_get_uris _obj' length_
    checkUnexpectedReturnNULL "gtk_recent_chooser_get_uris" result
    result' <- unpackZeroTerminatedUTF8CArray result
    mapZeroTerminatedCArray freeMem result
    freeMem result
    length_' <- peek length_
    touchManagedPtr _obj
    freeMem length_
    return (result', length_')

-- method RecentChooser::list_filters
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "RecentChooser", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "RecentChooser", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TGSList (TInterface "Gtk" "RecentFilter")
-- throws : False
-- Skip return : False

foreign import ccall "gtk_recent_chooser_list_filters" gtk_recent_chooser_list_filters :: 
    Ptr RecentChooser ->                    -- _obj : TInterface "Gtk" "RecentChooser"
    IO (Ptr (GSList (Ptr RecentFilter)))


recentChooserListFilters ::
    (MonadIO m, RecentChooserK a) =>
    a ->                                    -- _obj
    m [RecentFilter]
recentChooserListFilters _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_recent_chooser_list_filters _obj'
    checkUnexpectedReturnNULL "gtk_recent_chooser_list_filters" result
    result' <- unpackGSList result
    result'' <- mapM (newObject RecentFilter) result'
    g_slist_free result
    touchManagedPtr _obj
    return result''

-- method RecentChooser::remove_filter
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "RecentChooser", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "filter", argType = TInterface "Gtk" "RecentFilter", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "RecentChooser", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "filter", argType = TInterface "Gtk" "RecentFilter", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_recent_chooser_remove_filter" gtk_recent_chooser_remove_filter :: 
    Ptr RecentChooser ->                    -- _obj : TInterface "Gtk" "RecentChooser"
    Ptr RecentFilter ->                     -- filter : TInterface "Gtk" "RecentFilter"
    IO ()


recentChooserRemoveFilter ::
    (MonadIO m, RecentChooserK a, RecentFilterK b) =>
    a ->                                    -- _obj
    b ->                                    -- filter
    m ()
recentChooserRemoveFilter _obj filter = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let filter' = unsafeManagedPtrCastPtr filter
    gtk_recent_chooser_remove_filter _obj' filter'
    touchManagedPtr _obj
    touchManagedPtr filter
    return ()

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

foreign import ccall "gtk_recent_chooser_select_all" gtk_recent_chooser_select_all :: 
    Ptr RecentChooser ->                    -- _obj : TInterface "Gtk" "RecentChooser"
    IO ()


recentChooserSelectAll ::
    (MonadIO m, RecentChooserK a) =>
    a ->                                    -- _obj
    m ()
recentChooserSelectAll _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    gtk_recent_chooser_select_all _obj'
    touchManagedPtr _obj
    return ()

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

foreign import ccall "gtk_recent_chooser_select_uri" gtk_recent_chooser_select_uri :: 
    Ptr RecentChooser ->                    -- _obj : TInterface "Gtk" "RecentChooser"
    CString ->                              -- uri : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO CInt


recentChooserSelectUri ::
    (MonadIO m, RecentChooserK a) =>
    a ->                                    -- _obj
    T.Text ->                               -- uri
    m ()
recentChooserSelectUri _obj uri = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    uri' <- textToCString uri
    onException (do
        _ <- propagateGError $ gtk_recent_chooser_select_uri _obj' uri'
        touchManagedPtr _obj
        freeMem uri'
        return ()
     ) (do
        freeMem uri'
     )

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

foreign import ccall "gtk_recent_chooser_set_current_uri" gtk_recent_chooser_set_current_uri :: 
    Ptr RecentChooser ->                    -- _obj : TInterface "Gtk" "RecentChooser"
    CString ->                              -- uri : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO CInt


recentChooserSetCurrentUri ::
    (MonadIO m, RecentChooserK a) =>
    a ->                                    -- _obj
    T.Text ->                               -- uri
    m ()
recentChooserSetCurrentUri _obj uri = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    uri' <- textToCString uri
    onException (do
        _ <- propagateGError $ gtk_recent_chooser_set_current_uri _obj' uri'
        touchManagedPtr _obj
        freeMem uri'
        return ()
     ) (do
        freeMem uri'
     )

-- method RecentChooser::set_filter
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "RecentChooser", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "filter", argType = TInterface "Gtk" "RecentFilter", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "RecentChooser", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "filter", argType = TInterface "Gtk" "RecentFilter", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_recent_chooser_set_filter" gtk_recent_chooser_set_filter :: 
    Ptr RecentChooser ->                    -- _obj : TInterface "Gtk" "RecentChooser"
    Ptr RecentFilter ->                     -- filter : TInterface "Gtk" "RecentFilter"
    IO ()


recentChooserSetFilter ::
    (MonadIO m, RecentChooserK a, RecentFilterK b) =>
    a ->                                    -- _obj
    Maybe (b) ->                            -- filter
    m ()
recentChooserSetFilter _obj filter = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    maybeFilter <- case filter of
        Nothing -> return nullPtr
        Just jFilter -> do
            let jFilter' = unsafeManagedPtrCastPtr jFilter
            return jFilter'
    gtk_recent_chooser_set_filter _obj' maybeFilter
    touchManagedPtr _obj
    whenJust filter touchManagedPtr
    return ()

-- method RecentChooser::set_limit
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "RecentChooser", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "limit", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "RecentChooser", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "limit", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_recent_chooser_set_limit" gtk_recent_chooser_set_limit :: 
    Ptr RecentChooser ->                    -- _obj : TInterface "Gtk" "RecentChooser"
    Int32 ->                                -- limit : TBasicType TInt32
    IO ()


recentChooserSetLimit ::
    (MonadIO m, RecentChooserK a) =>
    a ->                                    -- _obj
    Int32 ->                                -- limit
    m ()
recentChooserSetLimit _obj limit = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    gtk_recent_chooser_set_limit _obj' limit
    touchManagedPtr _obj
    return ()

-- method RecentChooser::set_local_only
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "RecentChooser", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "local_only", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "RecentChooser", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "local_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 "gtk_recent_chooser_set_local_only" gtk_recent_chooser_set_local_only :: 
    Ptr RecentChooser ->                    -- _obj : TInterface "Gtk" "RecentChooser"
    CInt ->                                 -- local_only : TBasicType TBoolean
    IO ()


recentChooserSetLocalOnly ::
    (MonadIO m, RecentChooserK a) =>
    a ->                                    -- _obj
    Bool ->                                 -- local_only
    m ()
recentChooserSetLocalOnly _obj local_only = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let local_only' = (fromIntegral . fromEnum) local_only
    gtk_recent_chooser_set_local_only _obj' local_only'
    touchManagedPtr _obj
    return ()

-- method RecentChooser::set_select_multiple
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "RecentChooser", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "select_multiple", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "RecentChooser", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "select_multiple", 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 "gtk_recent_chooser_set_select_multiple" gtk_recent_chooser_set_select_multiple :: 
    Ptr RecentChooser ->                    -- _obj : TInterface "Gtk" "RecentChooser"
    CInt ->                                 -- select_multiple : TBasicType TBoolean
    IO ()


recentChooserSetSelectMultiple ::
    (MonadIO m, RecentChooserK a) =>
    a ->                                    -- _obj
    Bool ->                                 -- select_multiple
    m ()
recentChooserSetSelectMultiple _obj select_multiple = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let select_multiple' = (fromIntegral . fromEnum) select_multiple
    gtk_recent_chooser_set_select_multiple _obj' select_multiple'
    touchManagedPtr _obj
    return ()

-- method RecentChooser::set_show_icons
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "RecentChooser", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "show_icons", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "RecentChooser", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "show_icons", 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 "gtk_recent_chooser_set_show_icons" gtk_recent_chooser_set_show_icons :: 
    Ptr RecentChooser ->                    -- _obj : TInterface "Gtk" "RecentChooser"
    CInt ->                                 -- show_icons : TBasicType TBoolean
    IO ()


recentChooserSetShowIcons ::
    (MonadIO m, RecentChooserK a) =>
    a ->                                    -- _obj
    Bool ->                                 -- show_icons
    m ()
recentChooserSetShowIcons _obj show_icons = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let show_icons' = (fromIntegral . fromEnum) show_icons
    gtk_recent_chooser_set_show_icons _obj' show_icons'
    touchManagedPtr _obj
    return ()

-- method RecentChooser::set_show_not_found
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "RecentChooser", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "show_not_found", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "RecentChooser", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "show_not_found", 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 "gtk_recent_chooser_set_show_not_found" gtk_recent_chooser_set_show_not_found :: 
    Ptr RecentChooser ->                    -- _obj : TInterface "Gtk" "RecentChooser"
    CInt ->                                 -- show_not_found : TBasicType TBoolean
    IO ()


recentChooserSetShowNotFound ::
    (MonadIO m, RecentChooserK a) =>
    a ->                                    -- _obj
    Bool ->                                 -- show_not_found
    m ()
recentChooserSetShowNotFound _obj show_not_found = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let show_not_found' = (fromIntegral . fromEnum) show_not_found
    gtk_recent_chooser_set_show_not_found _obj' show_not_found'
    touchManagedPtr _obj
    return ()

-- method RecentChooser::set_show_private
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "RecentChooser", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "show_private", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "RecentChooser", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "show_private", 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 "gtk_recent_chooser_set_show_private" gtk_recent_chooser_set_show_private :: 
    Ptr RecentChooser ->                    -- _obj : TInterface "Gtk" "RecentChooser"
    CInt ->                                 -- show_private : TBasicType TBoolean
    IO ()


recentChooserSetShowPrivate ::
    (MonadIO m, RecentChooserK a) =>
    a ->                                    -- _obj
    Bool ->                                 -- show_private
    m ()
recentChooserSetShowPrivate _obj show_private = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let show_private' = (fromIntegral . fromEnum) show_private
    gtk_recent_chooser_set_show_private _obj' show_private'
    touchManagedPtr _obj
    return ()

-- method RecentChooser::set_show_tips
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "RecentChooser", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "show_tips", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "RecentChooser", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "show_tips", 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 "gtk_recent_chooser_set_show_tips" gtk_recent_chooser_set_show_tips :: 
    Ptr RecentChooser ->                    -- _obj : TInterface "Gtk" "RecentChooser"
    CInt ->                                 -- show_tips : TBasicType TBoolean
    IO ()


recentChooserSetShowTips ::
    (MonadIO m, RecentChooserK a) =>
    a ->                                    -- _obj
    Bool ->                                 -- show_tips
    m ()
recentChooserSetShowTips _obj show_tips = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let show_tips' = (fromIntegral . fromEnum) show_tips
    gtk_recent_chooser_set_show_tips _obj' show_tips'
    touchManagedPtr _obj
    return ()

-- method RecentChooser::set_sort_func
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "RecentChooser", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "sort_func", argType = TInterface "Gtk" "RecentSortFunc", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeNotified, argClosure = 2, argDestroy = 3, transfer = TransferNothing},Arg {argName = "sort_data", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "data_destroy", argType = TInterface "GLib" "DestroyNotify", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeAsync, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "RecentChooser", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "sort_func", argType = TInterface "Gtk" "RecentSortFunc", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeNotified, argClosure = 2, argDestroy = 3, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_recent_chooser_set_sort_func" gtk_recent_chooser_set_sort_func :: 
    Ptr RecentChooser ->                    -- _obj : TInterface "Gtk" "RecentChooser"
    FunPtr RecentSortFuncC ->               -- sort_func : TInterface "Gtk" "RecentSortFunc"
    Ptr () ->                               -- sort_data : TBasicType TVoid
    FunPtr GLib.DestroyNotifyC ->           -- data_destroy : TInterface "GLib" "DestroyNotify"
    IO ()


recentChooserSetSortFunc ::
    (MonadIO m, RecentChooserK a) =>
    a ->                                    -- _obj
    RecentSortFunc ->                       -- sort_func
    m ()
recentChooserSetSortFunc _obj sort_func = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    sort_func' <- mkRecentSortFunc (recentSortFuncWrapper Nothing sort_func)
    let sort_data = castFunPtrToPtr sort_func'
    let data_destroy = safeFreeFunPtrPtr
    gtk_recent_chooser_set_sort_func _obj' sort_func' sort_data data_destroy
    touchManagedPtr _obj
    return ()

-- method RecentChooser::set_sort_type
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "RecentChooser", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "sort_type", argType = TInterface "Gtk" "RecentSortType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "RecentChooser", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "sort_type", argType = TInterface "Gtk" "RecentSortType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_recent_chooser_set_sort_type" gtk_recent_chooser_set_sort_type :: 
    Ptr RecentChooser ->                    -- _obj : TInterface "Gtk" "RecentChooser"
    CUInt ->                                -- sort_type : TInterface "Gtk" "RecentSortType"
    IO ()


recentChooserSetSortType ::
    (MonadIO m, RecentChooserK a) =>
    a ->                                    -- _obj
    RecentSortType ->                       -- sort_type
    m ()
recentChooserSetSortType _obj sort_type = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let sort_type' = (fromIntegral . fromEnum) sort_type
    gtk_recent_chooser_set_sort_type _obj' sort_type'
    touchManagedPtr _obj
    return ()

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

foreign import ccall "gtk_recent_chooser_unselect_all" gtk_recent_chooser_unselect_all :: 
    Ptr RecentChooser ->                    -- _obj : TInterface "Gtk" "RecentChooser"
    IO ()


recentChooserUnselectAll ::
    (MonadIO m, RecentChooserK a) =>
    a ->                                    -- _obj
    m ()
recentChooserUnselectAll _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    gtk_recent_chooser_unselect_all _obj'
    touchManagedPtr _obj
    return ()

-- method RecentChooser::unselect_uri
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "RecentChooser", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "uri", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "RecentChooser", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "uri", 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 "gtk_recent_chooser_unselect_uri" gtk_recent_chooser_unselect_uri :: 
    Ptr RecentChooser ->                    -- _obj : TInterface "Gtk" "RecentChooser"
    CString ->                              -- uri : TBasicType TUTF8
    IO ()


recentChooserUnselectUri ::
    (MonadIO m, RecentChooserK a) =>
    a ->                                    -- _obj
    T.Text ->                               -- uri
    m ()
recentChooserUnselectUri _obj uri = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    uri' <- textToCString uri
    gtk_recent_chooser_unselect_uri _obj' uri'
    touchManagedPtr _obj
    freeMem uri'
    return ()