{-# LINE 2 "./System/GIO/File/AppInfo.chs" #-}
module System.GIO.File.AppInfo (
AppInfo,
AppInfoClass,
AppLaunchContext,
AppLaunchContextClass,
AppInfoCreateFlags (..),
appInfoCreateFromCommandline,
appInfoDup,
appInfoEqual,
appInfoGetId,
appInfoGetName,
appInfoGetDisplayName,
appInfoGetDescription,
appInfoGetExecutable,
appInfoGetCommandline,
appInfoGetIcon,
appInfoLaunch,
appInfoSupportsFiles,
appInfoSupportsUris,
appInfoLaunchUris,
appInfoShouldShow,
appInfoCanDelete,
appInfoDelete,
appInfoResetTypeAssociations,
appInfoSetAsDefaultForType,
appInfoSetAsDefaultForExtension,
appInfoAddSupportsType,
appInfoCanRemoveSupportsType,
appInfoRemoveSupportsType,
appInfoGetAll,
appInfoGetAllForType,
appInfoGetDefaultForType,
appInfoGetDefaultForUriScheme,
appInfoLaunchDefaultForUri,
appLaunchContextGetDisplay,
appLaunchContextGetStartupNotifyId,
appLaunchContextLaunchFailed,
appLaunchContextNew
) where
import Control.Monad
import Data.Maybe (fromMaybe)
import Data.ByteString (ByteString)
import Data.ByteString.Unsafe (unsafePackCStringFinalizer)
import System.GIO.Enums
import System.Glib.FFI
import System.Glib.Flags
import System.Glib.GError
import System.Glib.GList
import System.Glib.GObject
import System.Glib.UTFString
import System.GIO.Types
{-# LINE 112 "./System/GIO/File/AppInfo.chs" #-}
{-# LINE 114 "./System/GIO/File/AppInfo.chs" #-}
appInfoCreateFromCommandline ::
GlibString string
=> string
-> Maybe string
-> [AppInfoCreateFlags]
-> IO AppInfo
appInfoCreateFromCommandline :: forall string.
GlibString string =>
string -> Maybe string -> [AppInfoCreateFlags] -> IO AppInfo
appInfoCreateFromCommandline string
commandline Maybe string
applicationName [AppInfoCreateFlags]
flags =
(ForeignPtr AppInfo -> AppInfo, FinalizerPtr AppInfo)
-> IO (Ptr AppInfo) -> IO AppInfo
forall obj.
GObjectClass obj =>
(ForeignPtr obj -> obj, FinalizerPtr obj) -> IO (Ptr obj) -> IO obj
wrapNewGObject (ForeignPtr AppInfo -> AppInfo, FinalizerPtr AppInfo)
forall {a}. (ForeignPtr AppInfo -> AppInfo, FinalizerPtr a)
mkAppInfo (IO (Ptr AppInfo) -> IO AppInfo) -> IO (Ptr AppInfo) -> IO AppInfo
forall a b. (a -> b) -> a -> b
$
string -> (CString -> IO (Ptr AppInfo)) -> IO (Ptr AppInfo)
forall a. string -> (CString -> IO a) -> IO a
forall s a. GlibString s => s -> (CString -> IO a) -> IO a
withUTFString string
commandline ((CString -> IO (Ptr AppInfo)) -> IO (Ptr AppInfo))
-> (CString -> IO (Ptr AppInfo)) -> IO (Ptr AppInfo)
forall a b. (a -> b) -> a -> b
$ \ CString
commandlinePtr ->
(string -> (CString -> IO (Ptr AppInfo)) -> IO (Ptr AppInfo))
-> Maybe string
-> (CString -> IO (Ptr AppInfo))
-> IO (Ptr AppInfo)
forall a b c.
(a -> (Ptr b -> IO c) -> IO c)
-> Maybe a -> (Ptr b -> IO c) -> IO c
maybeWith string -> (CString -> IO (Ptr AppInfo)) -> IO (Ptr AppInfo)
forall a. string -> (CString -> IO a) -> IO a
forall s a. GlibString s => s -> (CString -> IO a) -> IO a
withUTFString Maybe string
applicationName ((CString -> IO (Ptr AppInfo)) -> IO (Ptr AppInfo))
-> (CString -> IO (Ptr AppInfo)) -> IO (Ptr AppInfo)
forall a b. (a -> b) -> a -> b
$ \ CString
applicationNamePtr ->
(Ptr (Ptr ()) -> IO (Ptr AppInfo)) -> IO (Ptr AppInfo)
forall a. (Ptr (Ptr ()) -> IO a) -> IO a
propagateGError (CString -> CString -> CInt -> Ptr (Ptr ()) -> IO (Ptr AppInfo)
g_app_info_create_from_commandline
{-# LINE 127 "./System/GIO/File/AppInfo.chs" #-}
CString
commandlinePtr
CString
applicationNamePtr
((Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt)
-> ([AppInfoCreateFlags] -> Int) -> [AppInfoCreateFlags] -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [AppInfoCreateFlags] -> Int
forall a. Flags a => [a] -> Int
fromFlags) [AppInfoCreateFlags]
flags))
appInfoDup :: AppInfoClass appinfo => appinfo -> IO AppInfo
appInfoDup :: forall appinfo. AppInfoClass appinfo => appinfo -> IO AppInfo
appInfoDup appinfo
appinfo =
(ForeignPtr AppInfo -> AppInfo, FinalizerPtr AppInfo)
-> IO (Ptr AppInfo) -> IO AppInfo
forall obj.
GObjectClass obj =>
(ForeignPtr obj -> obj, FinalizerPtr obj) -> IO (Ptr obj) -> IO obj
wrapNewGObject (ForeignPtr AppInfo -> AppInfo, FinalizerPtr AppInfo)
forall {a}. (ForeignPtr AppInfo -> AppInfo, FinalizerPtr a)
mkAppInfo (IO (Ptr AppInfo) -> IO AppInfo) -> IO (Ptr AppInfo) -> IO AppInfo
forall a b. (a -> b) -> a -> b
$
(\(AppInfo ForeignPtr AppInfo
arg1) -> ForeignPtr AppInfo
-> (Ptr AppInfo -> IO (Ptr AppInfo)) -> IO (Ptr AppInfo)
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr AppInfo
arg1 ((Ptr AppInfo -> IO (Ptr AppInfo)) -> IO (Ptr AppInfo))
-> (Ptr AppInfo -> IO (Ptr AppInfo)) -> IO (Ptr AppInfo)
forall a b. (a -> b) -> a -> b
$ \Ptr AppInfo
argPtr1 ->Ptr AppInfo -> IO (Ptr AppInfo)
g_app_info_dup Ptr AppInfo
argPtr1) (appinfo -> AppInfo
forall o. AppInfoClass o => o -> AppInfo
toAppInfo appinfo
appinfo)
appInfoEqual :: (AppInfoClass info1, AppInfoClass info2) => info1 -> info2
-> Bool
appInfoEqual :: forall info1 info2.
(AppInfoClass info1, AppInfoClass info2) =>
info1 -> info2 -> Bool
appInfoEqual info1
info1 info2
info2 =
IO Bool -> Bool
forall a. IO a -> a
unsafePerformIO (IO Bool -> Bool) -> IO Bool -> Bool
forall a b. (a -> b) -> a -> b
$ (CInt -> Bool) -> IO CInt -> IO Bool
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM CInt -> Bool
forall a. (Eq a, Num a) => a -> Bool
toBool (IO CInt -> IO Bool) -> IO CInt -> IO Bool
forall a b. (a -> b) -> a -> b
$
(\(AppInfo ForeignPtr AppInfo
arg1) (AppInfo ForeignPtr AppInfo
arg2) -> ForeignPtr AppInfo -> (Ptr AppInfo -> IO CInt) -> IO CInt
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr AppInfo
arg1 ((Ptr AppInfo -> IO CInt) -> IO CInt)
-> (Ptr AppInfo -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \Ptr AppInfo
argPtr1 ->ForeignPtr AppInfo -> (Ptr AppInfo -> IO CInt) -> IO CInt
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr AppInfo
arg2 ((Ptr AppInfo -> IO CInt) -> IO CInt)
-> (Ptr AppInfo -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \Ptr AppInfo
argPtr2 ->Ptr AppInfo -> Ptr AppInfo -> IO CInt
g_app_info_equal Ptr AppInfo
argPtr1 Ptr AppInfo
argPtr2) (info1 -> AppInfo
forall o. AppInfoClass o => o -> AppInfo
toAppInfo info1
info1) (info2 -> AppInfo
forall o. AppInfoClass o => o -> AppInfo
toAppInfo info2
info2)
appInfoGetId :: (AppInfoClass appinfo, GlibString string)
=> appinfo
-> IO (Maybe string)
appInfoGetId :: forall appinfo string.
(AppInfoClass appinfo, GlibString string) =>
appinfo -> IO (Maybe string)
appInfoGetId appinfo
appinfo =
(\(AppInfo ForeignPtr AppInfo
arg1) -> ForeignPtr AppInfo -> (Ptr AppInfo -> IO CString) -> IO CString
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr AppInfo
arg1 ((Ptr AppInfo -> IO CString) -> IO CString)
-> (Ptr AppInfo -> IO CString) -> IO CString
forall a b. (a -> b) -> a -> b
$ \Ptr AppInfo
argPtr1 ->Ptr AppInfo -> IO CString
g_app_info_get_id Ptr AppInfo
argPtr1) (appinfo -> AppInfo
forall o. AppInfoClass o => o -> AppInfo
toAppInfo appinfo
appinfo)
IO CString -> (CString -> IO (Maybe string)) -> IO (Maybe string)
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (CString -> IO string) -> CString -> IO (Maybe string)
forall a b. (Ptr a -> IO b) -> Ptr a -> IO (Maybe b)
maybePeek CString -> IO string
forall s. GlibString s => CString -> IO s
readUTFString
appInfoGetName :: AppInfoClass appinfo => appinfo
-> String
appInfoGetName :: forall appinfo. AppInfoClass appinfo => appinfo -> String
appInfoGetName appinfo
appinfo =
IO String -> String
forall a. IO a -> a
unsafePerformIO (IO String -> String) -> IO String -> String
forall a b. (a -> b) -> a -> b
$
(\(AppInfo ForeignPtr AppInfo
arg1) -> ForeignPtr AppInfo -> (Ptr AppInfo -> IO CString) -> IO CString
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr AppInfo
arg1 ((Ptr AppInfo -> IO CString) -> IO CString)
-> (Ptr AppInfo -> IO CString) -> IO CString
forall a b. (a -> b) -> a -> b
$ \Ptr AppInfo
argPtr1 ->Ptr AppInfo -> IO CString
g_app_info_get_name Ptr AppInfo
argPtr1) (appinfo -> AppInfo
forall o. AppInfoClass o => o -> AppInfo
toAppInfo appinfo
appinfo)
IO CString -> (CString -> IO String) -> IO String
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= CString -> IO String
readCString
appInfoGetDisplayName :: (AppInfoClass appinfo, GlibString string)
=> appinfo
-> string
appInfoGetDisplayName :: forall appinfo string.
(AppInfoClass appinfo, GlibString string) =>
appinfo -> string
appInfoGetDisplayName appinfo
appinfo =
IO string -> string
forall a. IO a -> a
unsafePerformIO (IO string -> string) -> IO string -> string
forall a b. (a -> b) -> a -> b
$
(\(AppInfo ForeignPtr AppInfo
arg1) -> ForeignPtr AppInfo -> (Ptr AppInfo -> IO CString) -> IO CString
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr AppInfo
arg1 ((Ptr AppInfo -> IO CString) -> IO CString)
-> (Ptr AppInfo -> IO CString) -> IO CString
forall a b. (a -> b) -> a -> b
$ \Ptr AppInfo
argPtr1 ->Ptr AppInfo -> IO CString
g_app_info_get_display_name Ptr AppInfo
argPtr1) (appinfo -> AppInfo
forall o. AppInfoClass o => o -> AppInfo
toAppInfo appinfo
appinfo)
IO CString -> (CString -> IO string) -> IO string
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= CString -> IO string
forall s. GlibString s => CString -> IO s
readUTFString
appInfoGetDescription :: (AppInfoClass appinfo, GlibString string)
=> appinfo
-> Maybe string
appInfoGetDescription :: forall appinfo string.
(AppInfoClass appinfo, GlibString string) =>
appinfo -> Maybe string
appInfoGetDescription appinfo
appinfo =
IO (Maybe string) -> Maybe string
forall a. IO a -> a
unsafePerformIO (IO (Maybe string) -> Maybe string)
-> IO (Maybe string) -> Maybe string
forall a b. (a -> b) -> a -> b
$ do
(\(AppInfo ForeignPtr AppInfo
arg1) -> ForeignPtr AppInfo -> (Ptr AppInfo -> IO CString) -> IO CString
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr AppInfo
arg1 ((Ptr AppInfo -> IO CString) -> IO CString)
-> (Ptr AppInfo -> IO CString) -> IO CString
forall a b. (a -> b) -> a -> b
$ \Ptr AppInfo
argPtr1 ->Ptr AppInfo -> IO CString
g_app_info_get_description Ptr AppInfo
argPtr1) (appinfo -> AppInfo
forall o. AppInfoClass o => o -> AppInfo
toAppInfo appinfo
appinfo)
IO CString -> (CString -> IO (Maybe string)) -> IO (Maybe string)
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (CString -> IO string) -> CString -> IO (Maybe string)
forall a b. (Ptr a -> IO b) -> Ptr a -> IO (Maybe b)
maybePeek CString -> IO string
forall s. GlibString s => CString -> IO s
peekUTFString
appInfoGetExecutable :: (AppInfoClass appinfo, GlibString string)
=> appinfo
-> string
appInfoGetExecutable :: forall appinfo string.
(AppInfoClass appinfo, GlibString string) =>
appinfo -> string
appInfoGetExecutable appinfo
appinfo =
IO string -> string
forall a. IO a -> a
unsafePerformIO (IO string -> string) -> IO string -> string
forall a b. (a -> b) -> a -> b
$
(\(AppInfo ForeignPtr AppInfo
arg1) -> ForeignPtr AppInfo -> (Ptr AppInfo -> IO CString) -> IO CString
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr AppInfo
arg1 ((Ptr AppInfo -> IO CString) -> IO CString)
-> (Ptr AppInfo -> IO CString) -> IO CString
forall a b. (a -> b) -> a -> b
$ \Ptr AppInfo
argPtr1 ->Ptr AppInfo -> IO CString
g_app_info_get_executable Ptr AppInfo
argPtr1) (appinfo -> AppInfo
forall o. AppInfoClass o => o -> AppInfo
toAppInfo appinfo
appinfo)
IO CString -> (CString -> IO string) -> IO string
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= CString -> IO string
forall s. GlibString s => CString -> IO s
peekUTFString
appInfoGetCommandline :: AppInfoClass appinfo => appinfo
-> Maybe ByteString
appInfoGetCommandline :: forall appinfo. AppInfoClass appinfo => appinfo -> Maybe ByteString
appInfoGetCommandline appinfo
appinfo =
IO (Maybe ByteString) -> Maybe ByteString
forall a. IO a -> a
unsafePerformIO (IO (Maybe ByteString) -> Maybe ByteString)
-> IO (Maybe ByteString) -> Maybe ByteString
forall a b. (a -> b) -> a -> b
$ do
CString
sPtr <- (\(AppInfo ForeignPtr AppInfo
arg1) -> ForeignPtr AppInfo -> (Ptr AppInfo -> IO CString) -> IO CString
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr AppInfo
arg1 ((Ptr AppInfo -> IO CString) -> IO CString)
-> (Ptr AppInfo -> IO CString) -> IO CString
forall a b. (a -> b) -> a -> b
$ \Ptr AppInfo
argPtr1 ->Ptr AppInfo -> IO CString
g_app_info_get_commandline Ptr AppInfo
argPtr1) (appinfo -> AppInfo
forall o. AppInfoClass o => o -> AppInfo
toAppInfo appinfo
appinfo)
if CString
sPtr CString -> CString -> Bool
forall a. Eq a => a -> a -> Bool
== CString
forall a. Ptr a
nullPtr
then Maybe ByteString -> IO (Maybe ByteString)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ByteString
forall a. Maybe a
Nothing
else do
Int
sLen <- CChar -> CString -> IO Int
forall a. (Storable a, Eq a) => a -> Ptr a -> IO Int
lengthArray0 CChar
0 CString
sPtr
(ByteString -> Maybe ByteString)
-> IO ByteString -> IO (Maybe ByteString)
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (IO ByteString -> IO (Maybe ByteString))
-> IO ByteString -> IO (Maybe ByteString)
forall a b. (a -> b) -> a -> b
$ Ptr Word8 -> Int -> IO () -> IO ByteString
unsafePackCStringFinalizer (CString -> Ptr Word8
forall a b. Ptr a -> Ptr b
castPtr CString
sPtr) (Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
sLen)
(Ptr () -> IO ()
g_free (CString -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr CString
sPtr))
appInfoGetIcon :: AppInfoClass appinfo => appinfo
-> IO (Maybe Icon)
appInfoGetIcon :: forall appinfo. AppInfoClass appinfo => appinfo -> IO (Maybe Icon)
appInfoGetIcon appinfo
appinfo =
(IO (Ptr Icon) -> IO Icon) -> IO (Ptr Icon) -> IO (Maybe Icon)
forall a. (IO (Ptr a) -> IO a) -> IO (Ptr a) -> IO (Maybe a)
maybeNull ((ForeignPtr Icon -> Icon, FinalizerPtr Icon)
-> IO (Ptr Icon) -> IO Icon
forall obj.
GObjectClass obj =>
(ForeignPtr obj -> obj, FinalizerPtr obj) -> IO (Ptr obj) -> IO obj
makeNewGObject (ForeignPtr Icon -> Icon, FinalizerPtr Icon)
forall {a}. (ForeignPtr Icon -> Icon, FinalizerPtr a)
mkIcon) (IO (Ptr Icon) -> IO (Maybe Icon))
-> IO (Ptr Icon) -> IO (Maybe Icon)
forall a b. (a -> b) -> a -> b
$
(\(AppInfo ForeignPtr AppInfo
arg1) -> ForeignPtr AppInfo
-> (Ptr AppInfo -> IO (Ptr Icon)) -> IO (Ptr Icon)
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr AppInfo
arg1 ((Ptr AppInfo -> IO (Ptr Icon)) -> IO (Ptr Icon))
-> (Ptr AppInfo -> IO (Ptr Icon)) -> IO (Ptr Icon)
forall a b. (a -> b) -> a -> b
$ \Ptr AppInfo
argPtr1 ->Ptr AppInfo -> IO (Ptr Icon)
g_app_info_get_icon Ptr AppInfo
argPtr1) (appinfo -> AppInfo
forall o. AppInfoClass o => o -> AppInfo
toAppInfo appinfo
appinfo)
appInfoLaunch :: AppInfoClass appinfo => appinfo
-> [File]
-> Maybe AppLaunchContext
-> IO ()
appInfoLaunch :: forall appinfo.
AppInfoClass appinfo =>
appinfo -> [File] -> Maybe AppLaunchContext -> IO ()
appInfoLaunch appinfo
appinfo [File]
files Maybe AppLaunchContext
launchContext =
[ForeignPtr File] -> ([Ptr File] -> IO ()) -> IO ()
forall a b. [ForeignPtr a] -> ([Ptr a] -> IO b) -> IO b
withForeignPtrs ((File -> ForeignPtr File) -> [File] -> [ForeignPtr File]
forall a b. (a -> b) -> [a] -> [b]
map File -> ForeignPtr File
unFile [File]
files) (([Ptr File] -> IO ()) -> IO ()) -> ([Ptr File] -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \[Ptr File]
wFilePtr ->
[Ptr File] -> (Ptr () -> IO ()) -> IO ()
forall a b. [Ptr a] -> (Ptr () -> IO b) -> IO b
withGList [Ptr File]
wFilePtr ((Ptr () -> IO ()) -> IO ()) -> (Ptr () -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr ()
filesPtr ->
(Ptr (Ptr ()) -> IO ()) -> IO ()
forall a. (Ptr (Ptr ()) -> IO a) -> IO a
propagateGError (\Ptr (Ptr ())
gErrorPtr -> do
(\(AppInfo ForeignPtr AppInfo
arg1) Ptr ()
arg2 (AppLaunchContext ForeignPtr AppLaunchContext
arg3) Ptr (Ptr ())
arg4 -> ForeignPtr AppInfo -> (Ptr AppInfo -> IO CInt) -> IO CInt
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr AppInfo
arg1 ((Ptr AppInfo -> IO CInt) -> IO CInt)
-> (Ptr AppInfo -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \Ptr AppInfo
argPtr1 ->ForeignPtr AppLaunchContext
-> (Ptr AppLaunchContext -> IO CInt) -> IO CInt
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr AppLaunchContext
arg3 ((Ptr AppLaunchContext -> IO CInt) -> IO CInt)
-> (Ptr AppLaunchContext -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \Ptr AppLaunchContext
argPtr3 ->Ptr AppInfo
-> Ptr () -> Ptr AppLaunchContext -> Ptr (Ptr ()) -> IO CInt
g_app_info_launch Ptr AppInfo
argPtr1 Ptr ()
arg2 Ptr AppLaunchContext
argPtr3 Ptr (Ptr ())
arg4)
{-# LINE 236 "./System/GIO/File/AppInfo.chs" #-}
(appinfo -> AppInfo
forall o. AppInfoClass o => o -> AppInfo
toAppInfo appinfo
appinfo)
Ptr ()
filesPtr
(AppLaunchContext -> Maybe AppLaunchContext -> AppLaunchContext
forall a. a -> Maybe a -> a
fromMaybe (ForeignPtr AppLaunchContext -> AppLaunchContext
AppLaunchContext ForeignPtr AppLaunchContext
forall a. ForeignPtr a
nullForeignPtr) Maybe AppLaunchContext
launchContext)
Ptr (Ptr ())
gErrorPtr
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ())
appInfoSupportsFiles :: AppInfoClass appinfo => appinfo
-> IO Bool
appInfoSupportsFiles :: forall appinfo. AppInfoClass appinfo => appinfo -> IO Bool
appInfoSupportsFiles appinfo
appinfo =
(CInt -> Bool) -> IO CInt -> IO Bool
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM CInt -> Bool
forall a. (Eq a, Num a) => a -> Bool
toBool (IO CInt -> IO Bool) -> IO CInt -> IO Bool
forall a b. (a -> b) -> a -> b
$
(\(AppInfo ForeignPtr AppInfo
arg1) -> ForeignPtr AppInfo -> (Ptr AppInfo -> IO CInt) -> IO CInt
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr AppInfo
arg1 ((Ptr AppInfo -> IO CInt) -> IO CInt)
-> (Ptr AppInfo -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \Ptr AppInfo
argPtr1 ->Ptr AppInfo -> IO CInt
g_app_info_supports_files Ptr AppInfo
argPtr1) (appinfo -> AppInfo
forall o. AppInfoClass o => o -> AppInfo
toAppInfo appinfo
appinfo)
appInfoSupportsUris :: AppInfoClass appinfo => appinfo
-> IO Bool
appInfoSupportsUris :: forall appinfo. AppInfoClass appinfo => appinfo -> IO Bool
appInfoSupportsUris appinfo
appinfo =
(CInt -> Bool) -> IO CInt -> IO Bool
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM CInt -> Bool
forall a. (Eq a, Num a) => a -> Bool
toBool (IO CInt -> IO Bool) -> IO CInt -> IO Bool
forall a b. (a -> b) -> a -> b
$
(\(AppInfo ForeignPtr AppInfo
arg1) -> ForeignPtr AppInfo -> (Ptr AppInfo -> IO CInt) -> IO CInt
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr AppInfo
arg1 ((Ptr AppInfo -> IO CInt) -> IO CInt)
-> (Ptr AppInfo -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \Ptr AppInfo
argPtr1 ->Ptr AppInfo -> IO CInt
g_app_info_supports_uris Ptr AppInfo
argPtr1) (appinfo -> AppInfo
forall o. AppInfoClass o => o -> AppInfo
toAppInfo appinfo
appinfo)
appInfoLaunchUris :: (AppInfoClass appinfo, GlibString string)
=> appinfo
-> [string]
-> Maybe AppLaunchContext
-> IO ()
appInfoLaunchUris :: forall appinfo string.
(AppInfoClass appinfo, GlibString string) =>
appinfo -> [string] -> Maybe AppLaunchContext -> IO ()
appInfoLaunchUris appinfo
appinfo [string]
uris Maybe AppLaunchContext
launchContext =
[string] -> (Ptr CString -> IO ()) -> IO ()
forall s a. GlibString s => [s] -> (Ptr CString -> IO a) -> IO a
withUTFStringArray [string]
uris ((Ptr CString -> IO ()) -> IO ())
-> (Ptr CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr CString
urisPtr ->
(Ptr (Ptr ()) -> IO ()) -> IO ()
forall a. (Ptr (Ptr ()) -> IO a) -> IO a
propagateGError (\Ptr (Ptr ())
gErrorPtr -> do
(\(AppInfo ForeignPtr AppInfo
arg1) Ptr ()
arg2 (AppLaunchContext ForeignPtr AppLaunchContext
arg3) Ptr (Ptr ())
arg4 -> ForeignPtr AppInfo -> (Ptr AppInfo -> IO CInt) -> IO CInt
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr AppInfo
arg1 ((Ptr AppInfo -> IO CInt) -> IO CInt)
-> (Ptr AppInfo -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \Ptr AppInfo
argPtr1 ->ForeignPtr AppLaunchContext
-> (Ptr AppLaunchContext -> IO CInt) -> IO CInt
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr AppLaunchContext
arg3 ((Ptr AppLaunchContext -> IO CInt) -> IO CInt)
-> (Ptr AppLaunchContext -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \Ptr AppLaunchContext
argPtr3 ->Ptr AppInfo
-> Ptr () -> Ptr AppLaunchContext -> Ptr (Ptr ()) -> IO CInt
g_app_info_launch_uris Ptr AppInfo
argPtr1 Ptr ()
arg2 Ptr AppLaunchContext
argPtr3 Ptr (Ptr ())
arg4)
{-# LINE 273 "./System/GIO/File/AppInfo.chs" #-}
(appinfo -> AppInfo
forall o. AppInfoClass o => o -> AppInfo
toAppInfo appinfo
appinfo)
(Ptr CString -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr Ptr CString
urisPtr)
(AppLaunchContext -> Maybe AppLaunchContext -> AppLaunchContext
forall a. a -> Maybe a -> a
fromMaybe (ForeignPtr AppLaunchContext -> AppLaunchContext
AppLaunchContext ForeignPtr AppLaunchContext
forall a. ForeignPtr a
nullForeignPtr) Maybe AppLaunchContext
launchContext)
Ptr (Ptr ())
gErrorPtr
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ())
appInfoShouldShow :: AppInfoClass appinfo => appinfo
-> IO Bool
appInfoShouldShow :: forall appinfo. AppInfoClass appinfo => appinfo -> IO Bool
appInfoShouldShow appinfo
appinfo =
(CInt -> Bool) -> IO CInt -> IO Bool
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM CInt -> Bool
forall a. (Eq a, Num a) => a -> Bool
toBool (IO CInt -> IO Bool) -> IO CInt -> IO Bool
forall a b. (a -> b) -> a -> b
$
(\(AppInfo ForeignPtr AppInfo
arg1) -> ForeignPtr AppInfo -> (Ptr AppInfo -> IO CInt) -> IO CInt
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr AppInfo
arg1 ((Ptr AppInfo -> IO CInt) -> IO CInt)
-> (Ptr AppInfo -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \Ptr AppInfo
argPtr1 ->Ptr AppInfo -> IO CInt
g_app_info_should_show Ptr AppInfo
argPtr1) (appinfo -> AppInfo
forall o. AppInfoClass o => o -> AppInfo
toAppInfo appinfo
appinfo)
appInfoCanDelete :: AppInfoClass appinfo => appinfo
-> IO Bool
appInfoCanDelete :: forall appinfo. AppInfoClass appinfo => appinfo -> IO Bool
appInfoCanDelete appinfo
appinfo =
(CInt -> Bool) -> IO CInt -> IO Bool
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM CInt -> Bool
forall a. (Eq a, Num a) => a -> Bool
toBool (IO CInt -> IO Bool) -> IO CInt -> IO Bool
forall a b. (a -> b) -> a -> b
$
(\(AppInfo ForeignPtr AppInfo
arg1) -> ForeignPtr AppInfo -> (Ptr AppInfo -> IO CInt) -> IO CInt
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr AppInfo
arg1 ((Ptr AppInfo -> IO CInt) -> IO CInt)
-> (Ptr AppInfo -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \Ptr AppInfo
argPtr1 ->Ptr AppInfo -> IO CInt
g_app_info_can_delete Ptr AppInfo
argPtr1) (appinfo -> AppInfo
forall o. AppInfoClass o => o -> AppInfo
toAppInfo appinfo
appinfo)
appInfoDelete :: AppInfoClass appinfo => appinfo
-> IO Bool
appInfoDelete :: forall appinfo. AppInfoClass appinfo => appinfo -> IO Bool
appInfoDelete appinfo
appinfo =
(CInt -> Bool) -> IO CInt -> IO Bool
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM CInt -> Bool
forall a. (Eq a, Num a) => a -> Bool
toBool (IO CInt -> IO Bool) -> IO CInt -> IO Bool
forall a b. (a -> b) -> a -> b
$
(\(AppInfo ForeignPtr AppInfo
arg1) -> ForeignPtr AppInfo -> (Ptr AppInfo -> IO CInt) -> IO CInt
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr AppInfo
arg1 ((Ptr AppInfo -> IO CInt) -> IO CInt)
-> (Ptr AppInfo -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \Ptr AppInfo
argPtr1 ->Ptr AppInfo -> IO CInt
g_app_info_delete Ptr AppInfo
argPtr1) (appinfo -> AppInfo
forall o. AppInfoClass o => o -> AppInfo
toAppInfo appinfo
appinfo)
appInfoResetTypeAssociations ::
GlibString string
=> string
-> IO ()
appInfoResetTypeAssociations :: forall string. GlibString string => string -> IO ()
appInfoResetTypeAssociations string
contentType =
string -> (CString -> IO ()) -> IO ()
forall a. string -> (CString -> IO a) -> IO a
forall s a. GlibString s => s -> (CString -> IO a) -> IO a
withUTFString string
contentType ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ CString
contentTypePtr ->
CString -> IO ()
g_app_info_reset_type_associations (CString -> CString
forall a b. Ptr a -> Ptr b
castPtr CString
contentTypePtr)
appInfoSetAsDefaultForType :: (AppInfoClass appinfo, GlibString string)
=> appinfo
-> string
-> IO ()
appInfoSetAsDefaultForType :: forall appinfo string.
(AppInfoClass appinfo, GlibString string) =>
appinfo -> string -> IO ()
appInfoSetAsDefaultForType appinfo
appinfo string
contentType =
string -> (CString -> IO ()) -> IO ()
forall a. string -> (CString -> IO a) -> IO a
forall s a. GlibString s => s -> (CString -> IO a) -> IO a
withUTFString string
contentType ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ CString
contentTypePtr ->
(Ptr (Ptr ()) -> IO ()) -> IO ()
forall a. (Ptr (Ptr ()) -> IO a) -> IO a
propagateGError (\Ptr (Ptr ())
gErrorPtr -> do
(\(AppInfo ForeignPtr AppInfo
arg1) CString
arg2 Ptr (Ptr ())
arg3 -> ForeignPtr AppInfo -> (Ptr AppInfo -> IO CInt) -> IO CInt
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr AppInfo
arg1 ((Ptr AppInfo -> IO CInt) -> IO CInt)
-> (Ptr AppInfo -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \Ptr AppInfo
argPtr1 ->Ptr AppInfo -> CString -> Ptr (Ptr ()) -> IO CInt
g_app_info_set_as_default_for_type Ptr AppInfo
argPtr1 CString
arg2 Ptr (Ptr ())
arg3)
{-# LINE 326 "./System/GIO/File/AppInfo.chs" #-}
(appinfo -> AppInfo
forall o. AppInfoClass o => o -> AppInfo
toAppInfo appinfo
appinfo)
(CString -> CString
forall a b. Ptr a -> Ptr b
castPtr CString
contentTypePtr)
Ptr (Ptr ())
gErrorPtr
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ())
appInfoSetAsDefaultForExtension :: (AppInfoClass appinfo, GlibString string)
=> appinfo
-> string
-> IO ()
appInfoSetAsDefaultForExtension :: forall appinfo string.
(AppInfoClass appinfo, GlibString string) =>
appinfo -> string -> IO ()
appInfoSetAsDefaultForExtension appinfo
appinfo string
extension =
string -> (CString -> IO ()) -> IO ()
forall a. string -> (CString -> IO a) -> IO a
forall s a. GlibString s => s -> (CString -> IO a) -> IO a
withUTFString string
extension ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ CString
extensionPtr ->
(Ptr (Ptr ()) -> IO ()) -> IO ()
forall a. (Ptr (Ptr ()) -> IO a) -> IO a
propagateGError (\Ptr (Ptr ())
gErrorPtr -> do
(\(AppInfo ForeignPtr AppInfo
arg1) CString
arg2 Ptr (Ptr ())
arg3 -> ForeignPtr AppInfo -> (Ptr AppInfo -> IO CInt) -> IO CInt
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr AppInfo
arg1 ((Ptr AppInfo -> IO CInt) -> IO CInt)
-> (Ptr AppInfo -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \Ptr AppInfo
argPtr1 ->Ptr AppInfo -> CString -> Ptr (Ptr ()) -> IO CInt
g_app_info_set_as_default_for_extension Ptr AppInfo
argPtr1 CString
arg2 Ptr (Ptr ())
arg3)
{-# LINE 341 "./System/GIO/File/AppInfo.chs" #-}
(appinfo -> AppInfo
forall o. AppInfoClass o => o -> AppInfo
toAppInfo appinfo
appinfo)
(CString -> CString
forall a b. Ptr a -> Ptr b
castPtr CString
extensionPtr)
Ptr (Ptr ())
gErrorPtr
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ())
appInfoAddSupportsType :: (AppInfoClass appinfo, GlibString string)
=> appinfo
-> string
-> IO ()
appInfoAddSupportsType :: forall appinfo string.
(AppInfoClass appinfo, GlibString string) =>
appinfo -> string -> IO ()
appInfoAddSupportsType appinfo
appinfo string
extension =
string -> (CString -> IO ()) -> IO ()
forall a. string -> (CString -> IO a) -> IO a
forall s a. GlibString s => s -> (CString -> IO a) -> IO a
withUTFString string
extension ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ CString
extensionPtr ->
(Ptr (Ptr ()) -> IO ()) -> IO ()
forall a. (Ptr (Ptr ()) -> IO a) -> IO a
propagateGError (\Ptr (Ptr ())
gErrorPtr -> do
(\(AppInfo ForeignPtr AppInfo
arg1) CString
arg2 Ptr (Ptr ())
arg3 -> ForeignPtr AppInfo -> (Ptr AppInfo -> IO CInt) -> IO CInt
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr AppInfo
arg1 ((Ptr AppInfo -> IO CInt) -> IO CInt)
-> (Ptr AppInfo -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \Ptr AppInfo
argPtr1 ->Ptr AppInfo -> CString -> Ptr (Ptr ()) -> IO CInt
g_app_info_add_supports_type Ptr AppInfo
argPtr1 CString
arg2 Ptr (Ptr ())
arg3)
{-# LINE 357 "./System/GIO/File/AppInfo.chs" #-}
(appinfo -> AppInfo
forall o. AppInfoClass o => o -> AppInfo
toAppInfo appinfo
appinfo)
(CString -> CString
forall a b. Ptr a -> Ptr b
castPtr CString
extensionPtr)
Ptr (Ptr ())
gErrorPtr
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ())
appInfoCanRemoveSupportsType :: AppInfoClass appinfo => appinfo
-> IO Bool
appInfoCanRemoveSupportsType :: forall appinfo. AppInfoClass appinfo => appinfo -> IO Bool
appInfoCanRemoveSupportsType appinfo
appinfo =
(CInt -> Bool) -> IO CInt -> IO Bool
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM CInt -> Bool
forall a. (Eq a, Num a) => a -> Bool
toBool (IO CInt -> IO Bool) -> IO CInt -> IO Bool
forall a b. (a -> b) -> a -> b
$
(\(AppInfo ForeignPtr AppInfo
arg1) -> ForeignPtr AppInfo -> (Ptr AppInfo -> IO CInt) -> IO CInt
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr AppInfo
arg1 ((Ptr AppInfo -> IO CInt) -> IO CInt)
-> (Ptr AppInfo -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \Ptr AppInfo
argPtr1 ->Ptr AppInfo -> IO CInt
g_app_info_can_remove_supports_type Ptr AppInfo
argPtr1) (appinfo -> AppInfo
forall o. AppInfoClass o => o -> AppInfo
toAppInfo appinfo
appinfo)
appInfoRemoveSupportsType :: (AppInfoClass appinfo, GlibString string)
=> appinfo
-> string
-> IO ()
appInfoRemoveSupportsType :: forall appinfo string.
(AppInfoClass appinfo, GlibString string) =>
appinfo -> string -> IO ()
appInfoRemoveSupportsType appinfo
appinfo string
extension =
string -> (CString -> IO ()) -> IO ()
forall a. string -> (CString -> IO a) -> IO a
forall s a. GlibString s => s -> (CString -> IO a) -> IO a
withUTFString string
extension ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ CString
extensionPtr ->
(Ptr (Ptr ()) -> IO ()) -> IO ()
forall a. (Ptr (Ptr ()) -> IO a) -> IO a
propagateGError (\Ptr (Ptr ())
gErrorPtr -> do
(\(AppInfo ForeignPtr AppInfo
arg1) CString
arg2 Ptr (Ptr ())
arg3 -> ForeignPtr AppInfo -> (Ptr AppInfo -> IO CInt) -> IO CInt
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr AppInfo
arg1 ((Ptr AppInfo -> IO CInt) -> IO CInt)
-> (Ptr AppInfo -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \Ptr AppInfo
argPtr1 ->Ptr AppInfo -> CString -> Ptr (Ptr ()) -> IO CInt
g_app_info_remove_supports_type Ptr AppInfo
argPtr1 CString
arg2 Ptr (Ptr ())
arg3)
{-# LINE 379 "./System/GIO/File/AppInfo.chs" #-}
(appinfo -> AppInfo
forall o. AppInfoClass o => o -> AppInfo
toAppInfo appinfo
appinfo)
(CString -> CString
forall a b. Ptr a -> Ptr b
castPtr CString
extensionPtr)
Ptr (Ptr ())
gErrorPtr
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ())
appInfoGetAll :: IO [AppInfo]
appInfoGetAll :: IO [AppInfo]
appInfoGetAll = do
Ptr ()
glistPtr <- IO (Ptr ())
g_app_info_get_all
{-# LINE 392 "./System/GIO/File/AppInfo.chs" #-}
list <- fromGList glistPtr
(Ptr AppInfo -> IO AppInfo) -> [Ptr AppInfo] -> IO [AppInfo]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM ((ForeignPtr AppInfo -> AppInfo, FinalizerPtr AppInfo)
-> IO (Ptr AppInfo) -> IO AppInfo
forall obj.
GObjectClass obj =>
(ForeignPtr obj -> obj, FinalizerPtr obj) -> IO (Ptr obj) -> IO obj
wrapNewGObject (ForeignPtr AppInfo -> AppInfo, FinalizerPtr AppInfo)
forall {a}. (ForeignPtr AppInfo -> AppInfo, FinalizerPtr a)
mkAppInfo (IO (Ptr AppInfo) -> IO AppInfo)
-> (Ptr AppInfo -> IO (Ptr AppInfo)) -> Ptr AppInfo -> IO AppInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr AppInfo -> IO (Ptr AppInfo)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return) [Ptr AppInfo]
list
appInfoGetAllForType ::
GlibString string
=> string
-> IO [AppInfo]
appInfoGetAllForType :: forall string. GlibString string => string -> IO [AppInfo]
appInfoGetAllForType string
contentType =
string -> (CString -> IO [AppInfo]) -> IO [AppInfo]
forall a. string -> (CString -> IO a) -> IO a
forall s a. GlibString s => s -> (CString -> IO a) -> IO a
withUTFString string
contentType ((CString -> IO [AppInfo]) -> IO [AppInfo])
-> (CString -> IO [AppInfo]) -> IO [AppInfo]
forall a b. (a -> b) -> a -> b
$ \ CString
contentTypePtr -> do
Ptr ()
glistPtr <- CString -> IO (Ptr ())
g_app_info_get_all_for_type (CString -> CString
forall a b. Ptr a -> Ptr b
castPtr CString
contentTypePtr)
if Ptr ()
glistPtr Ptr () -> Ptr () -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr ()
forall a. Ptr a
nullPtr
then [AppInfo] -> IO [AppInfo]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return []
else do
[Ptr AppInfo]
list <- Ptr () -> IO [Ptr AppInfo]
forall a. Ptr () -> IO [Ptr a]
fromGList Ptr ()
glistPtr
(Ptr AppInfo -> IO AppInfo) -> [Ptr AppInfo] -> IO [AppInfo]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM ((ForeignPtr AppInfo -> AppInfo, FinalizerPtr AppInfo)
-> IO (Ptr AppInfo) -> IO AppInfo
forall obj.
GObjectClass obj =>
(ForeignPtr obj -> obj, FinalizerPtr obj) -> IO (Ptr obj) -> IO obj
wrapNewGObject (ForeignPtr AppInfo -> AppInfo, FinalizerPtr AppInfo)
forall {a}. (ForeignPtr AppInfo -> AppInfo, FinalizerPtr a)
mkAppInfo (IO (Ptr AppInfo) -> IO AppInfo)
-> (Ptr AppInfo -> IO (Ptr AppInfo)) -> Ptr AppInfo -> IO AppInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr AppInfo -> IO (Ptr AppInfo)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return) [Ptr AppInfo]
list
appInfoGetDefaultForType ::
GlibString string
=> string
-> Bool
-> IO (Maybe AppInfo)
appInfoGetDefaultForType :: forall string.
GlibString string =>
string -> Bool -> IO (Maybe AppInfo)
appInfoGetDefaultForType string
contentType Bool
mustSupportUris =
(IO (Ptr AppInfo) -> IO AppInfo)
-> IO (Ptr AppInfo) -> IO (Maybe AppInfo)
forall a. (IO (Ptr a) -> IO a) -> IO (Ptr a) -> IO (Maybe a)
maybeNull ((ForeignPtr AppInfo -> AppInfo, FinalizerPtr AppInfo)
-> IO (Ptr AppInfo) -> IO AppInfo
forall obj.
GObjectClass obj =>
(ForeignPtr obj -> obj, FinalizerPtr obj) -> IO (Ptr obj) -> IO obj
wrapNewGObject (ForeignPtr AppInfo -> AppInfo, FinalizerPtr AppInfo)
forall {a}. (ForeignPtr AppInfo -> AppInfo, FinalizerPtr a)
mkAppInfo) (IO (Ptr AppInfo) -> IO (Maybe AppInfo))
-> IO (Ptr AppInfo) -> IO (Maybe AppInfo)
forall a b. (a -> b) -> a -> b
$
string -> (CString -> IO (Ptr AppInfo)) -> IO (Ptr AppInfo)
forall a. string -> (CString -> IO a) -> IO a
forall s a. GlibString s => s -> (CString -> IO a) -> IO a
withUTFString string
contentType ((CString -> IO (Ptr AppInfo)) -> IO (Ptr AppInfo))
-> (CString -> IO (Ptr AppInfo)) -> IO (Ptr AppInfo)
forall a b. (a -> b) -> a -> b
$ \ CString
contentTypePtr -> do
CString -> CInt -> IO (Ptr AppInfo)
g_app_info_get_default_for_type
{-# LINE 419 "./System/GIO/File/AppInfo.chs" #-}
(CString -> CString
forall a b. Ptr a -> Ptr b
castPtr CString
contentTypePtr)
(Bool -> CInt
forall a. Num a => Bool -> a
fromBool Bool
mustSupportUris)
appInfoGetDefaultForUriScheme ::
GlibString string
=> string
-> IO (Maybe AppInfo)
appInfoGetDefaultForUriScheme :: forall string. GlibString string => string -> IO (Maybe AppInfo)
appInfoGetDefaultForUriScheme string
uriScheme =
(IO (Ptr AppInfo) -> IO AppInfo)
-> IO (Ptr AppInfo) -> IO (Maybe AppInfo)
forall a. (IO (Ptr a) -> IO a) -> IO (Ptr a) -> IO (Maybe a)
maybeNull ((ForeignPtr AppInfo -> AppInfo, FinalizerPtr AppInfo)
-> IO (Ptr AppInfo) -> IO AppInfo
forall obj.
GObjectClass obj =>
(ForeignPtr obj -> obj, FinalizerPtr obj) -> IO (Ptr obj) -> IO obj
wrapNewGObject (ForeignPtr AppInfo -> AppInfo, FinalizerPtr AppInfo)
forall {a}. (ForeignPtr AppInfo -> AppInfo, FinalizerPtr a)
mkAppInfo) (IO (Ptr AppInfo) -> IO (Maybe AppInfo))
-> IO (Ptr AppInfo) -> IO (Maybe AppInfo)
forall a b. (a -> b) -> a -> b
$
string -> (CString -> IO (Ptr AppInfo)) -> IO (Ptr AppInfo)
forall a. string -> (CString -> IO a) -> IO a
forall s a. GlibString s => s -> (CString -> IO a) -> IO a
withUTFString string
uriScheme ((CString -> IO (Ptr AppInfo)) -> IO (Ptr AppInfo))
-> (CString -> IO (Ptr AppInfo)) -> IO (Ptr AppInfo)
forall a b. (a -> b) -> a -> b
$ \ CString
uriSchemePtr ->
CString -> IO (Ptr AppInfo)
g_app_info_get_default_for_uri_scheme (CString -> CString
forall a b. Ptr a -> Ptr b
castPtr CString
uriSchemePtr)
appInfoLaunchDefaultForUri ::
GlibString string
=> string
-> AppLaunchContext
-> IO ()
appInfoLaunchDefaultForUri :: forall string.
GlibString string =>
string -> AppLaunchContext -> IO ()
appInfoLaunchDefaultForUri string
uri AppLaunchContext
launchContext =
string -> (CString -> IO ()) -> IO ()
forall a. string -> (CString -> IO a) -> IO a
forall s a. GlibString s => s -> (CString -> IO a) -> IO a
withUTFString string
uri ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ CString
uriPtr ->
(Ptr (Ptr ()) -> IO ()) -> IO ()
forall a. (Ptr (Ptr ()) -> IO a) -> IO a
propagateGError (\Ptr (Ptr ())
gErrorPtr -> do
(\CString
arg1 (AppLaunchContext ForeignPtr AppLaunchContext
arg2) Ptr (Ptr ())
arg3 -> ForeignPtr AppLaunchContext
-> (Ptr AppLaunchContext -> IO CInt) -> IO CInt
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr AppLaunchContext
arg2 ((Ptr AppLaunchContext -> IO CInt) -> IO CInt)
-> (Ptr AppLaunchContext -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \Ptr AppLaunchContext
argPtr2 ->CString -> Ptr AppLaunchContext -> Ptr (Ptr ()) -> IO CInt
g_app_info_launch_default_for_uri CString
arg1 Ptr AppLaunchContext
argPtr2 Ptr (Ptr ())
arg3)
{-# LINE 445 "./System/GIO/File/AppInfo.chs" #-}
(CString -> CString
forall a b. Ptr a -> Ptr b
castPtr CString
uriPtr)
AppLaunchContext
launchContext
Ptr (Ptr ())
gErrorPtr
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ())
appLaunchContextGetDisplay :: (AppInfoClass appinfo, GlibString string)
=> AppLaunchContext
-> appinfo
-> [File]
-> IO string
appLaunchContextGetDisplay :: forall appinfo string.
(AppInfoClass appinfo, GlibString string) =>
AppLaunchContext -> appinfo -> [File] -> IO string
appLaunchContextGetDisplay AppLaunchContext
launchContext appinfo
appinfo [File]
files =
[ForeignPtr File] -> ([Ptr File] -> IO string) -> IO string
forall a b. [ForeignPtr a] -> ([Ptr a] -> IO b) -> IO b
withForeignPtrs ((File -> ForeignPtr File) -> [File] -> [ForeignPtr File]
forall a b. (a -> b) -> [a] -> [b]
map File -> ForeignPtr File
unFile [File]
files) (([Ptr File] -> IO string) -> IO string)
-> ([Ptr File] -> IO string) -> IO string
forall a b. (a -> b) -> a -> b
$ \[Ptr File]
wFilePtr ->
[Ptr File] -> (Ptr () -> IO string) -> IO string
forall a b. [Ptr a] -> (Ptr () -> IO b) -> IO b
withGList [Ptr File]
wFilePtr ((Ptr () -> IO string) -> IO string)
-> (Ptr () -> IO string) -> IO string
forall a b. (a -> b) -> a -> b
$ \Ptr ()
filesPtr ->
(\(AppLaunchContext ForeignPtr AppLaunchContext
arg1) (AppInfo ForeignPtr AppInfo
arg2) Ptr ()
arg3 -> ForeignPtr AppLaunchContext
-> (Ptr AppLaunchContext -> IO CString) -> IO CString
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr AppLaunchContext
arg1 ((Ptr AppLaunchContext -> IO CString) -> IO CString)
-> (Ptr AppLaunchContext -> IO CString) -> IO CString
forall a b. (a -> b) -> a -> b
$ \Ptr AppLaunchContext
argPtr1 ->ForeignPtr AppInfo -> (Ptr AppInfo -> IO CString) -> IO CString
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr AppInfo
arg2 ((Ptr AppInfo -> IO CString) -> IO CString)
-> (Ptr AppInfo -> IO CString) -> IO CString
forall a b. (a -> b) -> a -> b
$ \Ptr AppInfo
argPtr2 ->Ptr AppLaunchContext -> Ptr AppInfo -> Ptr () -> IO CString
g_app_launch_context_get_display Ptr AppLaunchContext
argPtr1 Ptr AppInfo
argPtr2 Ptr ()
arg3)
{-# LINE 461 "./System/GIO/File/AppInfo.chs" #-}
(AppLaunchContext -> AppLaunchContext
forall o. AppLaunchContextClass o => o -> AppLaunchContext
toAppLaunchContext AppLaunchContext
launchContext)
(appinfo -> AppInfo
forall o. AppInfoClass o => o -> AppInfo
toAppInfo appinfo
appinfo)
Ptr ()
filesPtr
IO CString -> (CString -> IO string) -> IO string
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= CString -> IO string
forall s. GlibString s => CString -> IO s
readUTFString
appLaunchContextGetStartupNotifyId :: (AppInfoClass appinfo, GlibString string)
=> AppLaunchContext
-> appinfo
-> [File]
-> IO (Maybe string)
appLaunchContextGetStartupNotifyId :: forall appinfo string.
(AppInfoClass appinfo, GlibString string) =>
AppLaunchContext -> appinfo -> [File] -> IO (Maybe string)
appLaunchContextGetStartupNotifyId AppLaunchContext
launchContext appinfo
appinfo [File]
files =
[ForeignPtr File]
-> ([Ptr File] -> IO (Maybe string)) -> IO (Maybe string)
forall a b. [ForeignPtr a] -> ([Ptr a] -> IO b) -> IO b
withForeignPtrs ((File -> ForeignPtr File) -> [File] -> [ForeignPtr File]
forall a b. (a -> b) -> [a] -> [b]
map File -> ForeignPtr File
unFile [File]
files) (([Ptr File] -> IO (Maybe string)) -> IO (Maybe string))
-> ([Ptr File] -> IO (Maybe string)) -> IO (Maybe string)
forall a b. (a -> b) -> a -> b
$ \[Ptr File]
wFilePtr ->
[Ptr File] -> (Ptr () -> IO (Maybe string)) -> IO (Maybe string)
forall a b. [Ptr a] -> (Ptr () -> IO b) -> IO b
withGList [Ptr File]
wFilePtr ((Ptr () -> IO (Maybe string)) -> IO (Maybe string))
-> (Ptr () -> IO (Maybe string)) -> IO (Maybe string)
forall a b. (a -> b) -> a -> b
$ \Ptr ()
filesPtr ->
(\(AppLaunchContext ForeignPtr AppLaunchContext
arg1) (AppInfo ForeignPtr AppInfo
arg2) Ptr ()
arg3 -> ForeignPtr AppLaunchContext
-> (Ptr AppLaunchContext -> IO CString) -> IO CString
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr AppLaunchContext
arg1 ((Ptr AppLaunchContext -> IO CString) -> IO CString)
-> (Ptr AppLaunchContext -> IO CString) -> IO CString
forall a b. (a -> b) -> a -> b
$ \Ptr AppLaunchContext
argPtr1 ->ForeignPtr AppInfo -> (Ptr AppInfo -> IO CString) -> IO CString
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr AppInfo
arg2 ((Ptr AppInfo -> IO CString) -> IO CString)
-> (Ptr AppInfo -> IO CString) -> IO CString
forall a b. (a -> b) -> a -> b
$ \Ptr AppInfo
argPtr2 ->Ptr AppLaunchContext -> Ptr AppInfo -> Ptr () -> IO CString
g_app_launch_context_get_startup_notify_id Ptr AppLaunchContext
argPtr1 Ptr AppInfo
argPtr2 Ptr ()
arg3)
{-# LINE 479 "./System/GIO/File/AppInfo.chs" #-}
(AppLaunchContext -> AppLaunchContext
forall o. AppLaunchContextClass o => o -> AppLaunchContext
toAppLaunchContext AppLaunchContext
launchContext)
(appinfo -> AppInfo
forall o. AppInfoClass o => o -> AppInfo
toAppInfo appinfo
appinfo)
Ptr ()
filesPtr
IO CString -> (CString -> IO (Maybe string)) -> IO (Maybe string)
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (CString -> IO string) -> CString -> IO (Maybe string)
forall a b. (Ptr a -> IO b) -> Ptr a -> IO (Maybe b)
maybePeek CString -> IO string
forall s. GlibString s => CString -> IO s
readUTFString
appLaunchContextLaunchFailed :: GlibString string
=> AppLaunchContext
-> string
-> IO ()
appLaunchContextLaunchFailed :: forall string.
GlibString string =>
AppLaunchContext -> string -> IO ()
appLaunchContextLaunchFailed AppLaunchContext
launchContext string
startupNotifyId =
string -> (CString -> IO ()) -> IO ()
forall a. string -> (CString -> IO a) -> IO a
forall s a. GlibString s => s -> (CString -> IO a) -> IO a
withUTFString string
startupNotifyId ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ CString
startupNotifyIdPtr ->
(\(AppLaunchContext ForeignPtr AppLaunchContext
arg1) CString
arg2 -> ForeignPtr AppLaunchContext
-> (Ptr AppLaunchContext -> IO ()) -> IO ()
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr AppLaunchContext
arg1 ((Ptr AppLaunchContext -> IO ()) -> IO ())
-> (Ptr AppLaunchContext -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr AppLaunchContext
argPtr1 ->Ptr AppLaunchContext -> CString -> IO ()
g_app_launch_context_launch_failed Ptr AppLaunchContext
argPtr1 CString
arg2)
{-# LINE 493 "./System/GIO/File/AppInfo.chs" #-}
(toAppLaunchContext launchContext)
(CString -> CString
forall a b. Ptr a -> Ptr b
castPtr CString
startupNotifyIdPtr)
appLaunchContextNew :: IO AppLaunchContext
appLaunchContextNew :: IO AppLaunchContext
appLaunchContextNew =
(ForeignPtr AppLaunchContext -> AppLaunchContext,
FinalizerPtr AppLaunchContext)
-> IO (Ptr AppLaunchContext) -> IO AppLaunchContext
forall obj.
GObjectClass obj =>
(ForeignPtr obj -> obj, FinalizerPtr obj) -> IO (Ptr obj) -> IO obj
wrapNewGObject (ForeignPtr AppLaunchContext -> AppLaunchContext,
FinalizerPtr AppLaunchContext)
forall {a}.
(ForeignPtr AppLaunchContext -> AppLaunchContext, FinalizerPtr a)
mkAppLaunchContext (IO (Ptr AppLaunchContext) -> IO AppLaunchContext)
-> IO (Ptr AppLaunchContext) -> IO AppLaunchContext
forall a b. (a -> b) -> a -> b
$
IO (Ptr AppLaunchContext)
g_app_launch_context_new
{-# LINE 502 "./System/GIO/File/AppInfo.chs" #-}
foreign import ccall safe "g_app_info_create_from_commandline"
g_app_info_create_from_commandline :: ((Ptr CChar) -> ((Ptr CChar) -> (CInt -> ((Ptr (Ptr ())) -> (IO (Ptr AppInfo))))))
foreign import ccall safe "g_app_info_dup"
g_app_info_dup :: ((Ptr AppInfo) -> (IO (Ptr AppInfo)))
foreign import ccall safe "g_app_info_equal"
g_app_info_equal :: ((Ptr AppInfo) -> ((Ptr AppInfo) -> (IO CInt)))
foreign import ccall safe "g_app_info_get_id"
g_app_info_get_id :: ((Ptr AppInfo) -> (IO (Ptr CChar)))
foreign import ccall safe "g_app_info_get_name"
g_app_info_get_name :: ((Ptr AppInfo) -> (IO (Ptr CChar)))
foreign import ccall safe "g_app_info_get_display_name"
g_app_info_get_display_name :: ((Ptr AppInfo) -> (IO (Ptr CChar)))
foreign import ccall safe "g_app_info_get_description"
g_app_info_get_description :: ((Ptr AppInfo) -> (IO (Ptr CChar)))
foreign import ccall safe "g_app_info_get_executable"
g_app_info_get_executable :: ((Ptr AppInfo) -> (IO (Ptr CChar)))
foreign import ccall safe "g_app_info_get_commandline"
g_app_info_get_commandline :: ((Ptr AppInfo) -> (IO (Ptr CChar)))
foreign import ccall unsafe "g_free"
g_free :: ((Ptr ()) -> (IO ()))
foreign import ccall safe "g_app_info_get_icon"
g_app_info_get_icon :: ((Ptr AppInfo) -> (IO (Ptr Icon)))
foreign import ccall safe "g_app_info_launch"
g_app_info_launch :: ((Ptr AppInfo) -> ((Ptr ()) -> ((Ptr AppLaunchContext) -> ((Ptr (Ptr ())) -> (IO CInt)))))
foreign import ccall safe "g_app_info_supports_files"
g_app_info_supports_files :: ((Ptr AppInfo) -> (IO CInt))
foreign import ccall safe "g_app_info_supports_uris"
g_app_info_supports_uris :: ((Ptr AppInfo) -> (IO CInt))
foreign import ccall safe "g_app_info_launch_uris"
g_app_info_launch_uris :: ((Ptr AppInfo) -> ((Ptr ()) -> ((Ptr AppLaunchContext) -> ((Ptr (Ptr ())) -> (IO CInt)))))
foreign import ccall safe "g_app_info_should_show"
g_app_info_should_show :: ((Ptr AppInfo) -> (IO CInt))
foreign import ccall safe "g_app_info_can_delete"
g_app_info_can_delete :: ((Ptr AppInfo) -> (IO CInt))
foreign import ccall safe "g_app_info_delete"
g_app_info_delete :: ((Ptr AppInfo) -> (IO CInt))
foreign import ccall safe "g_app_info_reset_type_associations"
g_app_info_reset_type_associations :: ((Ptr CChar) -> (IO ()))
foreign import ccall safe "g_app_info_set_as_default_for_type"
g_app_info_set_as_default_for_type :: ((Ptr AppInfo) -> ((Ptr CChar) -> ((Ptr (Ptr ())) -> (IO CInt))))
foreign import ccall safe "g_app_info_set_as_default_for_extension"
g_app_info_set_as_default_for_extension :: ((Ptr AppInfo) -> ((Ptr CChar) -> ((Ptr (Ptr ())) -> (IO CInt))))
foreign import ccall safe "g_app_info_add_supports_type"
g_app_info_add_supports_type :: ((Ptr AppInfo) -> ((Ptr CChar) -> ((Ptr (Ptr ())) -> (IO CInt))))
foreign import ccall safe "g_app_info_can_remove_supports_type"
g_app_info_can_remove_supports_type :: ((Ptr AppInfo) -> (IO CInt))
foreign import ccall safe "g_app_info_remove_supports_type"
g_app_info_remove_supports_type :: ((Ptr AppInfo) -> ((Ptr CChar) -> ((Ptr (Ptr ())) -> (IO CInt))))
foreign import ccall safe "g_app_info_get_all"
g_app_info_get_all :: (IO (Ptr ()))
foreign import ccall safe "g_app_info_get_all_for_type"
g_app_info_get_all_for_type :: ((Ptr CChar) -> (IO (Ptr ())))
foreign import ccall safe "g_app_info_get_default_for_type"
g_app_info_get_default_for_type :: ((Ptr CChar) -> (CInt -> (IO (Ptr AppInfo))))
foreign import ccall safe "g_app_info_get_default_for_uri_scheme"
g_app_info_get_default_for_uri_scheme :: ((Ptr CChar) -> (IO (Ptr AppInfo)))
foreign import ccall safe "g_app_info_launch_default_for_uri"
g_app_info_launch_default_for_uri :: ((Ptr CChar) -> ((Ptr AppLaunchContext) -> ((Ptr (Ptr ())) -> (IO CInt))))
foreign import ccall safe "g_app_launch_context_get_display"
g_app_launch_context_get_display :: ((Ptr AppLaunchContext) -> ((Ptr AppInfo) -> ((Ptr ()) -> (IO (Ptr CChar)))))
foreign import ccall safe "g_app_launch_context_get_startup_notify_id"
g_app_launch_context_get_startup_notify_id :: ((Ptr AppLaunchContext) -> ((Ptr AppInfo) -> ((Ptr ()) -> (IO (Ptr CChar)))))
foreign import ccall safe "g_app_launch_context_launch_failed"
g_app_launch_context_launch_failed :: ((Ptr AppLaunchContext) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "g_app_launch_context_new"
g_app_launch_context_new :: (IO (Ptr AppLaunchContext))