module GI.Gtk.Interfaces.RecentChooser
(
RecentChooser(..) ,
noRecentChooser ,
RecentChooserK ,
toRecentChooser ,
recentChooserAddFilter ,
recentChooserGetCurrentItem ,
recentChooserGetCurrentUri ,
recentChooserGetFilter ,
recentChooserGetItems ,
recentChooserGetLimit ,
recentChooserGetLocalOnly ,
recentChooserGetSelectMultiple ,
recentChooserGetShowIcons ,
recentChooserGetShowNotFound ,
recentChooserGetShowPrivate ,
recentChooserGetShowTips ,
recentChooserGetSortType ,
recentChooserGetUris ,
recentChooserListFilters ,
recentChooserRemoveFilter ,
recentChooserSelectAll ,
recentChooserSelectUri ,
recentChooserSetCurrentUri ,
recentChooserSetFilter ,
recentChooserSetLimit ,
recentChooserSetLocalOnly ,
recentChooserSetSelectMultiple ,
recentChooserSetShowIcons ,
recentChooserSetShowNotFound ,
recentChooserSetShowPrivate ,
recentChooserSetShowTips ,
recentChooserSetSortFunc ,
recentChooserSetSortType ,
recentChooserUnselectAll ,
recentChooserUnselectUri ,
RecentChooserFilterPropertyInfo ,
constructRecentChooserFilter ,
getRecentChooserFilter ,
setRecentChooserFilter ,
RecentChooserLimitPropertyInfo ,
constructRecentChooserLimit ,
getRecentChooserLimit ,
setRecentChooserLimit ,
RecentChooserLocalOnlyPropertyInfo ,
constructRecentChooserLocalOnly ,
getRecentChooserLocalOnly ,
setRecentChooserLocalOnly ,
RecentChooserRecentManagerPropertyInfo ,
constructRecentChooserRecentManager ,
RecentChooserSelectMultiplePropertyInfo ,
constructRecentChooserSelectMultiple ,
getRecentChooserSelectMultiple ,
setRecentChooserSelectMultiple ,
RecentChooserShowIconsPropertyInfo ,
constructRecentChooserShowIcons ,
getRecentChooserShowIcons ,
setRecentChooserShowIcons ,
RecentChooserShowNotFoundPropertyInfo ,
constructRecentChooserShowNotFound ,
getRecentChooserShowNotFound ,
setRecentChooserShowNotFound ,
RecentChooserShowPrivatePropertyInfo ,
constructRecentChooserShowPrivate ,
getRecentChooserShowPrivate ,
setRecentChooserShowPrivate ,
RecentChooserShowTipsPropertyInfo ,
constructRecentChooserShowTips ,
getRecentChooserShowTips ,
setRecentChooserShowTips ,
RecentChooserSortTypePropertyInfo ,
constructRecentChooserSortType ,
getRecentChooserSortType ,
setRecentChooserSortType ,
RecentChooserItemActivatedCallback ,
RecentChooserItemActivatedCallbackC ,
RecentChooserItemActivatedSignalInfo ,
afterRecentChooserItemActivated ,
mkRecentChooserItemActivatedCallback ,
noRecentChooserItemActivatedCallback ,
onRecentChooserItemActivated ,
recentChooserItemActivatedCallbackWrapper,
recentChooserItemActivatedClosure ,
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
newtype RecentChooser = RecentChooser (ForeignPtr RecentChooser)
noRecentChooser :: Maybe RecentChooser
noRecentChooser = Nothing
type RecentChooserItemActivatedCallback =
IO ()
noRecentChooserItemActivatedCallback :: Maybe RecentChooserItemActivatedCallback
noRecentChooserItemActivatedCallback = Nothing
type RecentChooserItemActivatedCallbackC =
Ptr () ->
Ptr () ->
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
type RecentChooserSelectionChangedCallback =
IO ()
noRecentChooserSelectionChangedCallback :: Maybe RecentChooserSelectionChangedCallback
noRecentChooserSelectionChangedCallback = Nothing
type RecentChooserSelectionChangedCallbackC =
Ptr () ->
Ptr () ->
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
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
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
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
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
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
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
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
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
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
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
foreign import ccall "gtk_recent_chooser_add_filter" gtk_recent_chooser_add_filter ::
Ptr RecentChooser ->
Ptr RecentFilter ->
IO ()
recentChooserAddFilter ::
(MonadIO m, RecentChooserK a, RecentFilterK b) =>
a ->
b ->
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 ()
foreign import ccall "gtk_recent_chooser_get_current_item" gtk_recent_chooser_get_current_item ::
Ptr RecentChooser ->
IO (Ptr RecentInfo)
recentChooserGetCurrentItem ::
(MonadIO m, RecentChooserK a) =>
a ->
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'
foreign import ccall "gtk_recent_chooser_get_current_uri" gtk_recent_chooser_get_current_uri ::
Ptr RecentChooser ->
IO CString
recentChooserGetCurrentUri ::
(MonadIO m, RecentChooserK a) =>
a ->
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'
foreign import ccall "gtk_recent_chooser_get_filter" gtk_recent_chooser_get_filter ::
Ptr RecentChooser ->
IO (Ptr RecentFilter)
recentChooserGetFilter ::
(MonadIO m, RecentChooserK a) =>
a ->
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'
foreign import ccall "gtk_recent_chooser_get_items" gtk_recent_chooser_get_items ::
Ptr RecentChooser ->
IO (Ptr (GList (Ptr RecentInfo)))
recentChooserGetItems ::
(MonadIO m, RecentChooserK a) =>
a ->
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''
foreign import ccall "gtk_recent_chooser_get_limit" gtk_recent_chooser_get_limit ::
Ptr RecentChooser ->
IO Int32
recentChooserGetLimit ::
(MonadIO m, RecentChooserK a) =>
a ->
m Int32
recentChooserGetLimit _obj = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
result <- gtk_recent_chooser_get_limit _obj'
touchManagedPtr _obj
return result
foreign import ccall "gtk_recent_chooser_get_local_only" gtk_recent_chooser_get_local_only ::
Ptr RecentChooser ->
IO CInt
recentChooserGetLocalOnly ::
(MonadIO m, RecentChooserK a) =>
a ->
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'
foreign import ccall "gtk_recent_chooser_get_select_multiple" gtk_recent_chooser_get_select_multiple ::
Ptr RecentChooser ->
IO CInt
recentChooserGetSelectMultiple ::
(MonadIO m, RecentChooserK a) =>
a ->
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'
foreign import ccall "gtk_recent_chooser_get_show_icons" gtk_recent_chooser_get_show_icons ::
Ptr RecentChooser ->
IO CInt
recentChooserGetShowIcons ::
(MonadIO m, RecentChooserK a) =>
a ->
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'
foreign import ccall "gtk_recent_chooser_get_show_not_found" gtk_recent_chooser_get_show_not_found ::
Ptr RecentChooser ->
IO CInt
recentChooserGetShowNotFound ::
(MonadIO m, RecentChooserK a) =>
a ->
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'
foreign import ccall "gtk_recent_chooser_get_show_private" gtk_recent_chooser_get_show_private ::
Ptr RecentChooser ->
IO CInt
recentChooserGetShowPrivate ::
(MonadIO m, RecentChooserK a) =>
a ->
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'
foreign import ccall "gtk_recent_chooser_get_show_tips" gtk_recent_chooser_get_show_tips ::
Ptr RecentChooser ->
IO CInt
recentChooserGetShowTips ::
(MonadIO m, RecentChooserK a) =>
a ->
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'
foreign import ccall "gtk_recent_chooser_get_sort_type" gtk_recent_chooser_get_sort_type ::
Ptr RecentChooser ->
IO CUInt
recentChooserGetSortType ::
(MonadIO m, RecentChooserK a) =>
a ->
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'
foreign import ccall "gtk_recent_chooser_get_uris" gtk_recent_chooser_get_uris ::
Ptr RecentChooser ->
Ptr Word64 ->
IO (Ptr CString)
recentChooserGetUris ::
(MonadIO m, RecentChooserK a) =>
a ->
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_')
foreign import ccall "gtk_recent_chooser_list_filters" gtk_recent_chooser_list_filters ::
Ptr RecentChooser ->
IO (Ptr (GSList (Ptr RecentFilter)))
recentChooserListFilters ::
(MonadIO m, RecentChooserK a) =>
a ->
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''
foreign import ccall "gtk_recent_chooser_remove_filter" gtk_recent_chooser_remove_filter ::
Ptr RecentChooser ->
Ptr RecentFilter ->
IO ()
recentChooserRemoveFilter ::
(MonadIO m, RecentChooserK a, RecentFilterK b) =>
a ->
b ->
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 ()
foreign import ccall "gtk_recent_chooser_select_all" gtk_recent_chooser_select_all ::
Ptr RecentChooser ->
IO ()
recentChooserSelectAll ::
(MonadIO m, RecentChooserK a) =>
a ->
m ()
recentChooserSelectAll _obj = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
gtk_recent_chooser_select_all _obj'
touchManagedPtr _obj
return ()
foreign import ccall "gtk_recent_chooser_select_uri" gtk_recent_chooser_select_uri ::
Ptr RecentChooser ->
CString ->
Ptr (Ptr GError) ->
IO CInt
recentChooserSelectUri ::
(MonadIO m, RecentChooserK a) =>
a ->
T.Text ->
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'
)
foreign import ccall "gtk_recent_chooser_set_current_uri" gtk_recent_chooser_set_current_uri ::
Ptr RecentChooser ->
CString ->
Ptr (Ptr GError) ->
IO CInt
recentChooserSetCurrentUri ::
(MonadIO m, RecentChooserK a) =>
a ->
T.Text ->
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'
)
foreign import ccall "gtk_recent_chooser_set_filter" gtk_recent_chooser_set_filter ::
Ptr RecentChooser ->
Ptr RecentFilter ->
IO ()
recentChooserSetFilter ::
(MonadIO m, RecentChooserK a, RecentFilterK b) =>
a ->
Maybe (b) ->
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 ()
foreign import ccall "gtk_recent_chooser_set_limit" gtk_recent_chooser_set_limit ::
Ptr RecentChooser ->
Int32 ->
IO ()
recentChooserSetLimit ::
(MonadIO m, RecentChooserK a) =>
a ->
Int32 ->
m ()
recentChooserSetLimit _obj limit = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
gtk_recent_chooser_set_limit _obj' limit
touchManagedPtr _obj
return ()
foreign import ccall "gtk_recent_chooser_set_local_only" gtk_recent_chooser_set_local_only ::
Ptr RecentChooser ->
CInt ->
IO ()
recentChooserSetLocalOnly ::
(MonadIO m, RecentChooserK a) =>
a ->
Bool ->
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 ()
foreign import ccall "gtk_recent_chooser_set_select_multiple" gtk_recent_chooser_set_select_multiple ::
Ptr RecentChooser ->
CInt ->
IO ()
recentChooserSetSelectMultiple ::
(MonadIO m, RecentChooserK a) =>
a ->
Bool ->
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 ()
foreign import ccall "gtk_recent_chooser_set_show_icons" gtk_recent_chooser_set_show_icons ::
Ptr RecentChooser ->
CInt ->
IO ()
recentChooserSetShowIcons ::
(MonadIO m, RecentChooserK a) =>
a ->
Bool ->
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 ()
foreign import ccall "gtk_recent_chooser_set_show_not_found" gtk_recent_chooser_set_show_not_found ::
Ptr RecentChooser ->
CInt ->
IO ()
recentChooserSetShowNotFound ::
(MonadIO m, RecentChooserK a) =>
a ->
Bool ->
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 ()
foreign import ccall "gtk_recent_chooser_set_show_private" gtk_recent_chooser_set_show_private ::
Ptr RecentChooser ->
CInt ->
IO ()
recentChooserSetShowPrivate ::
(MonadIO m, RecentChooserK a) =>
a ->
Bool ->
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 ()
foreign import ccall "gtk_recent_chooser_set_show_tips" gtk_recent_chooser_set_show_tips ::
Ptr RecentChooser ->
CInt ->
IO ()
recentChooserSetShowTips ::
(MonadIO m, RecentChooserK a) =>
a ->
Bool ->
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 ()
foreign import ccall "gtk_recent_chooser_set_sort_func" gtk_recent_chooser_set_sort_func ::
Ptr RecentChooser ->
FunPtr RecentSortFuncC ->
Ptr () ->
FunPtr GLib.DestroyNotifyC ->
IO ()
recentChooserSetSortFunc ::
(MonadIO m, RecentChooserK a) =>
a ->
RecentSortFunc ->
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 ()
foreign import ccall "gtk_recent_chooser_set_sort_type" gtk_recent_chooser_set_sort_type ::
Ptr RecentChooser ->
CUInt ->
IO ()
recentChooserSetSortType ::
(MonadIO m, RecentChooserK a) =>
a ->
RecentSortType ->
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 ()
foreign import ccall "gtk_recent_chooser_unselect_all" gtk_recent_chooser_unselect_all ::
Ptr RecentChooser ->
IO ()
recentChooserUnselectAll ::
(MonadIO m, RecentChooserK a) =>
a ->
m ()
recentChooserUnselectAll _obj = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
gtk_recent_chooser_unselect_all _obj'
touchManagedPtr _obj
return ()
foreign import ccall "gtk_recent_chooser_unselect_uri" gtk_recent_chooser_unselect_uri ::
Ptr RecentChooser ->
CString ->
IO ()
recentChooserUnselectUri ::
(MonadIO m, RecentChooserK a) =>
a ->
T.Text ->
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 ()