module Graphics.UI.Gtk.Recent.RecentChooser (
RecentChooser,
RecentChooserClass,
castToRecentChooser,
toRecentChooser,
RecentChooserError(..),
RecentSortType(..),
recentChooserSetSortFunc,
recentChooserSetCurrentURI,
recentChooserGetCurrentURI,
recentChooserGetCurrentItem,
recentChooserSelectURI,
recentChooserUnselectURI,
recentChooserSelectAll,
recentChooserUnselectAll,
recentChooserGetItems,
recentChooserGetURIs,
recentChooserAddFilter,
recentChooserRemoveFilter,
recentChooserListFilters,
recentChooserShowPrivate,
recentChooserShowTips,
recentChooserShowIcons,
recentChooserShowNotFound,
recentChooserSelectMultiple,
recentChooserLocalOnly,
recentChooserLimit,
recentChooserSortType,
recentChooserFilter,
recentChooserSelectionChanged,
recentChooserItemActivated,
) where
import Control.Monad (liftM)
import System.Glib.FFI
import System.Glib.UTFString
import System.Glib.Attributes
import System.Glib.Properties
import System.Glib.GList
import System.Glib.GError (checkGError)
import Graphics.UI.Gtk.Abstract.Object (makeNewObject)
import Graphics.UI.Gtk.Recent.RecentInfo (RecentInfo, mkRecentInfo)
import Graphics.UI.Gtk.Types
import Graphics.UI.Gtk.Signals
data RecentChooserError = RecentChooserErrorNotFound
| RecentChooserErrorInvalidUri
deriving (Enum,Bounded,Eq,Show)
data RecentSortType = RecentSortNone
| RecentSortMru
| RecentSortLru
| RecentSortCustom
deriving (Bounded,Eq,Show)
instance Enum RecentSortType where
fromEnum RecentSortNone = 0
fromEnum RecentSortMru = 1
fromEnum RecentSortLru = 2
fromEnum RecentSortCustom = 3
toEnum 0 = RecentSortNone
toEnum 1 = RecentSortMru
toEnum 2 = RecentSortLru
toEnum 3 = RecentSortCustom
toEnum unmatched = error ("RecentSortType.toEnum: Cannot match " ++ show unmatched)
succ RecentSortNone = RecentSortMru
succ RecentSortMru = RecentSortLru
succ RecentSortLru = RecentSortCustom
succ _ = undefined
pred RecentSortMru = RecentSortNone
pred RecentSortLru = RecentSortMru
pred RecentSortCustom = RecentSortLru
pred _ = undefined
enumFromTo x y | fromEnum x == fromEnum y = [ y ]
| otherwise = x : enumFromTo (succ x) y
enumFrom x = enumFromTo x RecentSortCustom
enumFromThen _ _ = error "Enum RecentSortType: enumFromThen not implemented"
enumFromThenTo _ _ _ = error "Enum RecentSortType: enumFromThenTo not implemented"
recentChooserSetSortFunc :: RecentChooserClass self => self
-> (Maybe (RecentInfo -> IO Int))
-> IO ()
recentChooserSetSortFunc self Nothing =
(\(RecentChooser arg1) arg2 arg3 arg4 -> withForeignPtr arg1 $ \argPtr1 ->gtk_recent_chooser_set_sort_func argPtr1 arg2 arg3 arg4)
(toRecentChooser self) nullFunPtr nullPtr nullFunPtr
recentChooserSetSortFunc self (Just func) = do
fPtr <- mkRecentSortFunc $ \_ infoPtr _ -> do
info <- mkRecentInfo infoPtr
liftM fromIntegral (func info)
(\(RecentChooser arg1) arg2 arg3 arg4 -> withForeignPtr arg1 $ \argPtr1 ->gtk_recent_chooser_set_sort_func argPtr1 arg2 arg3 arg4)
(toRecentChooser self)
fPtr
(castFunPtrToPtr fPtr)
destroyFunPtr
type RecentSortFunc = FunPtr (((Ptr RecentInfo) -> ((Ptr RecentInfo) -> ((Ptr ()) -> (IO CInt)))))
foreign import ccall "wrapper" mkRecentSortFunc ::
(Ptr RecentInfo -> Ptr RecentInfo -> Ptr () -> IO (CInt))
-> IO RecentSortFunc
recentChooserSetCurrentURI :: (RecentChooserClass self, GlibString string) => self
-> string
-> IO Bool
recentChooserSetCurrentURI self uri =
checkGError ( \errorPtr ->
liftM toBool $
withUTFString uri $ \uriPtr ->
(\(RecentChooser arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->gtk_recent_chooser_set_current_uri argPtr1 arg2 arg3)
(toRecentChooser self)
uriPtr
errorPtr)
(\_ -> return False)
recentChooserGetCurrentURI :: (RecentChooserClass self, GlibString string) => self
-> IO string
recentChooserGetCurrentURI self =
(\(RecentChooser arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_recent_chooser_get_current_uri argPtr1)
(toRecentChooser self)
>>= readUTFString
recentChooserGetCurrentItem :: RecentChooserClass self => self
-> IO RecentInfo
recentChooserGetCurrentItem self = do
info <- (\(RecentChooser arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_recent_chooser_get_current_item argPtr1) (toRecentChooser self)
mkRecentInfo info
recentChooserSelectURI :: (RecentChooserClass self, GlibString string) => self
-> string
-> IO Bool
recentChooserSelectURI self uri =
checkGError ( \errorPtr ->
liftM toBool $
withUTFString uri $ \uriPtr ->
(\(RecentChooser arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->gtk_recent_chooser_select_uri argPtr1 arg2 arg3)
(toRecentChooser self)
uriPtr
errorPtr)
(\_ -> return False)
recentChooserUnselectURI :: (RecentChooserClass self, GlibString string) => self
-> string
-> IO ()
recentChooserUnselectURI self uri =
withUTFString uri $ \uriPtr ->
(\(RecentChooser arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_recent_chooser_unselect_uri argPtr1 arg2)
(toRecentChooser self)
uriPtr
recentChooserSelectAll :: RecentChooserClass self => self -> IO ()
recentChooserSelectAll self =
(\(RecentChooser arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_recent_chooser_select_all argPtr1)
(toRecentChooser self)
recentChooserUnselectAll :: RecentChooserClass self => self -> IO ()
recentChooserUnselectAll self =
(\(RecentChooser arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_recent_chooser_unselect_all argPtr1)
(toRecentChooser self)
recentChooserGetItems :: RecentChooserClass self => self
-> IO [RecentInfo]
recentChooserGetItems self = do
glist <- (\(RecentChooser arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_recent_chooser_get_items argPtr1) (toRecentChooser self)
list <- fromGList glist
mapM mkRecentInfo list
recentChooserGetURIs :: (RecentChooserClass self, GlibString string) => self
-> IO [string]
recentChooserGetURIs self =
alloca $ \lengthPtr -> do
str <- (\(RecentChooser arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_recent_chooser_get_uris argPtr1 arg2)
(toRecentChooser self)
lengthPtr
length <- peek lengthPtr
mapM peekUTFString =<< peekArray (fromIntegral length) str
recentChooserAddFilter :: (RecentChooserClass self, RecentFilterClass filter) => self
-> filter
-> IO ()
recentChooserAddFilter self filter =
(\(RecentChooser arg1) (RecentFilter arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_recent_chooser_add_filter argPtr1 argPtr2)
(toRecentChooser self)
(toRecentFilter filter)
recentChooserRemoveFilter :: (RecentChooserClass self, RecentFilterClass filter) => self
-> filter
-> IO ()
recentChooserRemoveFilter self filter =
(\(RecentChooser arg1) (RecentFilter arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_recent_chooser_remove_filter argPtr1 argPtr2)
(toRecentChooser self)
(toRecentFilter filter)
recentChooserListFilters :: RecentChooserClass self => self
-> IO [RecentFilter]
recentChooserListFilters self = do
glist <- (\(RecentChooser arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_recent_chooser_list_filters argPtr1)
(toRecentChooser self)
list <- fromGList glist
mapM (\x -> makeNewObject mkRecentFilter (return (castPtr x))) list
recentChooserShowPrivate :: RecentChooserClass self => Attr self Bool
recentChooserShowPrivate = newAttrFromBoolProperty "show-private"
recentChooserShowTips :: RecentChooserClass self => Attr self Bool
recentChooserShowTips = newAttrFromBoolProperty "show-tips"
recentChooserShowIcons :: RecentChooserClass self => Attr self Bool
recentChooserShowIcons = newAttrFromBoolProperty "show-icons"
recentChooserShowNotFound :: RecentChooserClass self => Attr self Bool
recentChooserShowNotFound = newAttrFromBoolProperty "show-not-found"
recentChooserSelectMultiple :: RecentChooserClass self => Attr self Bool
recentChooserSelectMultiple = newAttrFromBoolProperty "select-multiple"
recentChooserLocalOnly :: RecentChooserClass self => Attr self Bool
recentChooserLocalOnly = newAttrFromBoolProperty "local-only"
recentChooserLimit :: RecentChooserClass self => Attr self Int
recentChooserLimit = newAttrFromIntProperty "limit"
recentChooserSortType :: RecentChooserClass self => Attr self RecentSortType
recentChooserSortType = newAttrFromEnumProperty "sort-type"
gtk_recent_sort_type_get_type
recentChooserFilter :: (RecentChooserClass self, RecentFilterClass recentFilter) => ReadWriteAttr self RecentFilter recentFilter
recentChooserFilter = newAttrFromObjectProperty "filter"
gtk_recent_filter_get_type
recentChooserSelectionChanged :: RecentChooserClass self => Signal self (IO ())
recentChooserSelectionChanged = Signal (connect_NONE__NONE "selection_changed")
recentChooserItemActivated :: RecentChooserClass self => Signal self (IO ())
recentChooserItemActivated = Signal (connect_NONE__NONE "item_activated")
foreign import ccall safe "gtk_recent_chooser_set_sort_func"
gtk_recent_chooser_set_sort_func :: ((Ptr RecentChooser) -> ((FunPtr ((Ptr RecentInfo) -> ((Ptr RecentInfo) -> ((Ptr ()) -> (IO CInt))))) -> ((Ptr ()) -> ((FunPtr ((Ptr ()) -> (IO ()))) -> (IO ())))))
foreign import ccall safe "gtk_recent_chooser_set_current_uri"
gtk_recent_chooser_set_current_uri :: ((Ptr RecentChooser) -> ((Ptr CChar) -> ((Ptr (Ptr ())) -> (IO CInt))))
foreign import ccall safe "gtk_recent_chooser_get_current_uri"
gtk_recent_chooser_get_current_uri :: ((Ptr RecentChooser) -> (IO (Ptr CChar)))
foreign import ccall safe "gtk_recent_chooser_get_current_item"
gtk_recent_chooser_get_current_item :: ((Ptr RecentChooser) -> (IO (Ptr RecentInfo)))
foreign import ccall safe "gtk_recent_chooser_select_uri"
gtk_recent_chooser_select_uri :: ((Ptr RecentChooser) -> ((Ptr CChar) -> ((Ptr (Ptr ())) -> (IO CInt))))
foreign import ccall safe "gtk_recent_chooser_unselect_uri"
gtk_recent_chooser_unselect_uri :: ((Ptr RecentChooser) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "gtk_recent_chooser_select_all"
gtk_recent_chooser_select_all :: ((Ptr RecentChooser) -> (IO ()))
foreign import ccall safe "gtk_recent_chooser_unselect_all"
gtk_recent_chooser_unselect_all :: ((Ptr RecentChooser) -> (IO ()))
foreign import ccall safe "gtk_recent_chooser_get_items"
gtk_recent_chooser_get_items :: ((Ptr RecentChooser) -> (IO (Ptr ())))
foreign import ccall safe "gtk_recent_chooser_get_uris"
gtk_recent_chooser_get_uris :: ((Ptr RecentChooser) -> ((Ptr CULong) -> (IO (Ptr (Ptr CChar)))))
foreign import ccall safe "gtk_recent_chooser_add_filter"
gtk_recent_chooser_add_filter :: ((Ptr RecentChooser) -> ((Ptr RecentFilter) -> (IO ())))
foreign import ccall safe "gtk_recent_chooser_remove_filter"
gtk_recent_chooser_remove_filter :: ((Ptr RecentChooser) -> ((Ptr RecentFilter) -> (IO ())))
foreign import ccall safe "gtk_recent_chooser_list_filters"
gtk_recent_chooser_list_filters :: ((Ptr RecentChooser) -> (IO (Ptr ())))
foreign import ccall unsafe "gtk_recent_sort_type_get_type"
gtk_recent_sort_type_get_type :: CULong
foreign import ccall unsafe "gtk_recent_filter_get_type"
gtk_recent_filter_get_type :: CULong