module Graphics.UI.Gtk.Recent.RecentInfo (
RecentInfo,
mkRecentInfo,
recentInfoExists,
recentInfoGetAdded,
recentInfoGetAge,
recentInfoGetApplicationInfo,
recentInfoGetApplications,
recentInfoGetDescription,
recentInfoGetDisplayName,
recentInfoGetGroups,
recentInfoGetIcon,
recentInfoGetMimeType,
recentInfoGetModified,
recentInfoGetPrivateHint,
recentInfoGetShortName,
recentInfoGetURI,
recentInfoGetURIDisplay,
recentInfoGetVisited,
recentInfoHasApplication,
recentInfoHasGroup,
recentInfoIsLocal,
recentInfoLastApplication,
recentInfoMatch,
) where
import Control.Monad (liftM)
import System.Glib.FFI
import System.Glib.UTFString
import Graphics.UI.Gtk.Types
newtype RecentInfo = RecentInfo (ForeignPtr (RecentInfo))
mkRecentInfo :: Ptr RecentInfo -> IO RecentInfo
mkRecentInfo rPtr = do
info <- newForeignPtr rPtr gtk_recent_info_unref
return (RecentInfo info)
foreign import ccall unsafe ">k_recent_info_unref"
gtk_recent_info_unref :: FinalizerPtr RecentInfo
recentInfoExists :: RecentInfo
-> IO Bool
recentInfoExists self =
liftM toBool $
(\(RecentInfo arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_recent_info_exists argPtr1)
self
recentInfoGetAdded :: RecentInfo
-> IO Int
recentInfoGetAdded self =
liftM fromIntegral $
(\(RecentInfo arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_recent_info_get_added argPtr1)
self
recentInfoGetAge :: RecentInfo
-> IO Int
recentInfoGetAge self =
liftM fromIntegral $
(\(RecentInfo arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_recent_info_get_age argPtr1)
self
recentInfoGetApplicationInfo :: GlibString string => RecentInfo
-> string
-> IO (Maybe ([string], Int, Int))
recentInfoGetApplicationInfo self appName =
alloca $ \countPtr ->
alloca $ \timePtr ->
allocaArray 0 $ \execPtr ->
withUTFString appName $ \appNamePtr -> do
success <- liftM toBool $
(\(RecentInfo arg1) arg2 arg3 arg4 arg5 -> withForeignPtr arg1 $ \argPtr1 ->gtk_recent_info_get_application_info argPtr1 arg2 arg3 arg4 arg5)
self
appNamePtr
execPtr
countPtr
timePtr
if success
then do
exec <- mapM peekUTFString =<< peekArray 0 execPtr
count <- peek countPtr
time <- peek timePtr
return (Just (exec, fromIntegral count, fromIntegral time))
else return Nothing
recentInfoGetApplications :: GlibString string => RecentInfo -> IO [string]
recentInfoGetApplications self =
alloca $ \lengthPtr -> do
str <- (\(RecentInfo arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_recent_info_get_applications argPtr1 arg2) self lengthPtr
length <- peek lengthPtr
mapM peekUTFString =<< peekArray (fromIntegral length) str
recentInfoGetDescription :: GlibString string => RecentInfo
-> IO string
recentInfoGetDescription self =
(\(RecentInfo arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_recent_info_get_description argPtr1)
self
>>= peekUTFString
recentInfoGetDisplayName :: GlibString string => RecentInfo
-> IO string
recentInfoGetDisplayName self =
(\(RecentInfo arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_recent_info_get_display_name argPtr1)
self
>>= peekUTFString
recentInfoGetGroups :: GlibString string => RecentInfo -> IO [string]
recentInfoGetGroups self =
alloca $ \lengthPtr -> do
str <- (\(RecentInfo arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_recent_info_get_groups argPtr1 arg2) self lengthPtr
length <- peek lengthPtr
mapM peekUTFString =<< peekArray (fromIntegral length) str
recentInfoGetIcon :: RecentInfo
-> Int
-> IO (Maybe Pixbuf)
recentInfoGetIcon self size =
maybeNull (makeNewGObject mkPixbuf) $
(\(RecentInfo arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_recent_info_get_icon argPtr1 arg2)
self
(fromIntegral size)
recentInfoGetMimeType :: GlibString string => RecentInfo
-> IO string
recentInfoGetMimeType self =
(\(RecentInfo arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_recent_info_get_mime_type argPtr1)
self
>>= peekUTFString
recentInfoGetModified :: RecentInfo
-> IO Int
recentInfoGetModified self =
liftM fromIntegral $
(\(RecentInfo arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_recent_info_get_modified argPtr1)
self
recentInfoGetPrivateHint :: RecentInfo
-> IO Bool
recentInfoGetPrivateHint self =
liftM toBool $
(\(RecentInfo arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_recent_info_get_private_hint argPtr1)
self
recentInfoGetShortName :: GlibString string => RecentInfo
-> IO string
recentInfoGetShortName self =
(\(RecentInfo arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_recent_info_get_short_name argPtr1)
self
>>= readUTFString
recentInfoGetURI :: GlibString string => RecentInfo
-> IO string
recentInfoGetURI self =
(\(RecentInfo arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_recent_info_get_uri argPtr1)
self
>>= peekUTFString
recentInfoGetURIDisplay :: GlibString string => RecentInfo -> IO string
recentInfoGetURIDisplay self =
(\(RecentInfo arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_recent_info_get_uri_display argPtr1)
self
>>= readUTFString
recentInfoGetVisited :: RecentInfo
-> IO Int
recentInfoGetVisited self =
liftM fromIntegral $
(\(RecentInfo arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_recent_info_get_visited argPtr1)
self
recentInfoHasApplication :: GlibString string => RecentInfo
-> string
-> IO Bool
recentInfoHasApplication self appName =
liftM toBool $
withUTFString appName $ \appNamePtr ->
(\(RecentInfo arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_recent_info_has_application argPtr1 arg2)
self
appNamePtr
recentInfoHasGroup :: GlibString string => RecentInfo
-> string
-> IO Bool
recentInfoHasGroup self groupName =
liftM toBool $
withUTFString groupName $ \groupNamePtr ->
(\(RecentInfo arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_recent_info_has_group argPtr1 arg2)
self
groupNamePtr
recentInfoIsLocal :: RecentInfo
-> IO Bool
recentInfoIsLocal self =
liftM toBool $
(\(RecentInfo arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_recent_info_is_local argPtr1)
self
recentInfoLastApplication :: GlibString string => RecentInfo
-> IO string
recentInfoLastApplication self =
(\(RecentInfo arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_recent_info_last_application argPtr1)
self
>>= readUTFString
recentInfoMatch :: RecentInfo -> RecentInfo
-> IO Bool
recentInfoMatch self infoB =
liftM toBool $
(\(RecentInfo arg1) (RecentInfo arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_recent_info_match argPtr1 argPtr2)
self
infoB
foreign import ccall safe "gtk_recent_info_exists"
gtk_recent_info_exists :: ((Ptr RecentInfo) -> (IO CInt))
foreign import ccall safe "gtk_recent_info_get_added"
gtk_recent_info_get_added :: ((Ptr RecentInfo) -> (IO CLong))
foreign import ccall safe "gtk_recent_info_get_age"
gtk_recent_info_get_age :: ((Ptr RecentInfo) -> (IO CInt))
foreign import ccall safe "gtk_recent_info_get_application_info"
gtk_recent_info_get_application_info :: ((Ptr RecentInfo) -> ((Ptr CChar) -> ((Ptr (Ptr CChar)) -> ((Ptr CUInt) -> ((Ptr CLong) -> (IO CInt))))))
foreign import ccall safe "gtk_recent_info_get_applications"
gtk_recent_info_get_applications :: ((Ptr RecentInfo) -> ((Ptr CULong) -> (IO (Ptr (Ptr CChar)))))
foreign import ccall safe "gtk_recent_info_get_description"
gtk_recent_info_get_description :: ((Ptr RecentInfo) -> (IO (Ptr CChar)))
foreign import ccall safe "gtk_recent_info_get_display_name"
gtk_recent_info_get_display_name :: ((Ptr RecentInfo) -> (IO (Ptr CChar)))
foreign import ccall safe "gtk_recent_info_get_groups"
gtk_recent_info_get_groups :: ((Ptr RecentInfo) -> ((Ptr CULong) -> (IO (Ptr (Ptr CChar)))))
foreign import ccall safe "gtk_recent_info_get_icon"
gtk_recent_info_get_icon :: ((Ptr RecentInfo) -> (CInt -> (IO (Ptr Pixbuf))))
foreign import ccall safe "gtk_recent_info_get_mime_type"
gtk_recent_info_get_mime_type :: ((Ptr RecentInfo) -> (IO (Ptr CChar)))
foreign import ccall safe "gtk_recent_info_get_modified"
gtk_recent_info_get_modified :: ((Ptr RecentInfo) -> (IO CLong))
foreign import ccall safe "gtk_recent_info_get_private_hint"
gtk_recent_info_get_private_hint :: ((Ptr RecentInfo) -> (IO CInt))
foreign import ccall safe "gtk_recent_info_get_short_name"
gtk_recent_info_get_short_name :: ((Ptr RecentInfo) -> (IO (Ptr CChar)))
foreign import ccall safe "gtk_recent_info_get_uri"
gtk_recent_info_get_uri :: ((Ptr RecentInfo) -> (IO (Ptr CChar)))
foreign import ccall safe "gtk_recent_info_get_uri_display"
gtk_recent_info_get_uri_display :: ((Ptr RecentInfo) -> (IO (Ptr CChar)))
foreign import ccall safe "gtk_recent_info_get_visited"
gtk_recent_info_get_visited :: ((Ptr RecentInfo) -> (IO CLong))
foreign import ccall safe "gtk_recent_info_has_application"
gtk_recent_info_has_application :: ((Ptr RecentInfo) -> ((Ptr CChar) -> (IO CInt)))
foreign import ccall safe "gtk_recent_info_has_group"
gtk_recent_info_has_group :: ((Ptr RecentInfo) -> ((Ptr CChar) -> (IO CInt)))
foreign import ccall safe "gtk_recent_info_is_local"
gtk_recent_info_is_local :: ((Ptr RecentInfo) -> (IO CInt))
foreign import ccall safe "gtk_recent_info_last_application"
gtk_recent_info_last_application :: ((Ptr RecentInfo) -> (IO (Ptr CChar)))
foreign import ccall safe "gtk_recent_info_match"
gtk_recent_info_match :: ((Ptr RecentInfo) -> ((Ptr RecentInfo) -> (IO CInt)))