{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A @GtkFileLauncher@ object collects the arguments that are needed to open a
-- file with an application.
-- 
-- Depending on system configuration, user preferences and available APIs, this
-- may or may not show an app chooser dialog or launch the default application
-- right away.
-- 
-- The operation is started with the 'GI.Gtk.Objects.FileLauncher.fileLauncherLaunch' function.
-- This API follows the GIO async pattern, and the result can be obtained by
-- calling 'GI.Gtk.Objects.FileLauncher.fileLauncherLaunchFinish'.
-- 
-- To launch uris that don\'t represent files, use t'GI.Gtk.Objects.UriLauncher.UriLauncher'.
-- 
-- /Since: 4.10/

#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif

module GI.Gtk.Objects.FileLauncher
    ( 

-- * Exported types
    FileLauncher(..)                        ,
    IsFileLauncher                          ,
    toFileLauncher                          ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [launch]("GI.Gtk.Objects.FileLauncher#g:method:launch"), [launchFinish]("GI.Gtk.Objects.FileLauncher#g:method:launchFinish"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [openContainingFolder]("GI.Gtk.Objects.FileLauncher#g:method:openContainingFolder"), [openContainingFolderFinish]("GI.Gtk.Objects.FileLauncher#g:method:openContainingFolderFinish"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getData]("GI.GObject.Objects.Object#g:method:getData"), [getFile]("GI.Gtk.Objects.FileLauncher#g:method:getFile"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setFile]("GI.Gtk.Objects.FileLauncher#g:method:setFile"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty").

#if defined(ENABLE_OVERLOADING)
    ResolveFileLauncherMethod               ,
#endif

-- ** getFile #method:getFile#

#if defined(ENABLE_OVERLOADING)
    FileLauncherGetFileMethodInfo           ,
#endif
    fileLauncherGetFile                     ,


-- ** launch #method:launch#

#if defined(ENABLE_OVERLOADING)
    FileLauncherLaunchMethodInfo            ,
#endif
    fileLauncherLaunch                      ,


-- ** launchFinish #method:launchFinish#

#if defined(ENABLE_OVERLOADING)
    FileLauncherLaunchFinishMethodInfo      ,
#endif
    fileLauncherLaunchFinish                ,


-- ** new #method:new#

    fileLauncherNew                         ,


-- ** openContainingFolder #method:openContainingFolder#

#if defined(ENABLE_OVERLOADING)
    FileLauncherOpenContainingFolderMethodInfo,
#endif
    fileLauncherOpenContainingFolder        ,


-- ** openContainingFolderFinish #method:openContainingFolderFinish#

#if defined(ENABLE_OVERLOADING)
    FileLauncherOpenContainingFolderFinishMethodInfo,
#endif
    fileLauncherOpenContainingFolderFinish  ,


-- ** setFile #method:setFile#

#if defined(ENABLE_OVERLOADING)
    FileLauncherSetFileMethodInfo           ,
#endif
    fileLauncherSetFile                     ,




 -- * Properties


-- ** file #attr:file#
-- | The file to launch.
-- 
-- /Since: 4.10/

#if defined(ENABLE_OVERLOADING)
    FileLauncherFilePropertyInfo            ,
#endif
    clearFileLauncherFile                   ,
    constructFileLauncherFile               ,
#if defined(ENABLE_OVERLOADING)
    fileLauncherFile                        ,
#endif
    getFileLauncherFile                     ,
    setFileLauncherFile                     ,




    ) where

import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.Kind as DK
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R

import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gio.Callbacks as Gio.Callbacks
import qualified GI.Gio.Interfaces.AsyncResult as Gio.AsyncResult
import qualified GI.Gio.Interfaces.File as Gio.File
import qualified GI.Gio.Objects.Cancellable as Gio.Cancellable
import {-# SOURCE #-} qualified GI.Gtk.Objects.Window as Gtk.Window

-- | Memory-managed wrapper type.
newtype FileLauncher = FileLauncher (SP.ManagedPtr FileLauncher)
    deriving (FileLauncher -> FileLauncher -> Bool
(FileLauncher -> FileLauncher -> Bool)
-> (FileLauncher -> FileLauncher -> Bool) -> Eq FileLauncher
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FileLauncher -> FileLauncher -> Bool
== :: FileLauncher -> FileLauncher -> Bool
$c/= :: FileLauncher -> FileLauncher -> Bool
/= :: FileLauncher -> FileLauncher -> Bool
Eq)

instance SP.ManagedPtrNewtype FileLauncher where
    toManagedPtr :: FileLauncher -> ManagedPtr FileLauncher
toManagedPtr (FileLauncher ManagedPtr FileLauncher
p) = ManagedPtr FileLauncher
p

foreign import ccall "gtk_file_launcher_get_type"
    c_gtk_file_launcher_get_type :: IO B.Types.GType

instance B.Types.TypedObject FileLauncher where
    glibType :: IO GType
glibType = IO GType
c_gtk_file_launcher_get_type

instance B.Types.GObject FileLauncher

-- | Type class for types which can be safely cast to `FileLauncher`, for instance with `toFileLauncher`.
class (SP.GObject o, O.IsDescendantOf FileLauncher o) => IsFileLauncher o
instance (SP.GObject o, O.IsDescendantOf FileLauncher o) => IsFileLauncher o

instance O.HasParentTypes FileLauncher
type instance O.ParentTypes FileLauncher = '[GObject.Object.Object]

-- | Cast to `FileLauncher`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toFileLauncher :: (MIO.MonadIO m, IsFileLauncher o) => o -> m FileLauncher
toFileLauncher :: forall (m :: * -> *) o.
(MonadIO m, IsFileLauncher o) =>
o -> m FileLauncher
toFileLauncher = IO FileLauncher -> m FileLauncher
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO FileLauncher -> m FileLauncher)
-> (o -> IO FileLauncher) -> o -> m FileLauncher
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr FileLauncher -> FileLauncher) -> o -> IO FileLauncher
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr FileLauncher -> FileLauncher
FileLauncher

-- | Convert 'FileLauncher' to and from 'Data.GI.Base.GValue.GValue'. See 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue (Maybe FileLauncher) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gtk_file_launcher_get_type
    gvalueSet_ :: Ptr GValue -> Maybe FileLauncher -> IO ()
gvalueSet_ Ptr GValue
gv Maybe FileLauncher
P.Nothing = Ptr GValue -> Ptr FileLauncher -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr FileLauncher
forall a. Ptr a
FP.nullPtr :: FP.Ptr FileLauncher)
    gvalueSet_ Ptr GValue
gv (P.Just FileLauncher
obj) = FileLauncher -> (Ptr FileLauncher -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr FileLauncher
obj (Ptr GValue -> Ptr FileLauncher -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe FileLauncher)
gvalueGet_ Ptr GValue
gv = do
        Ptr FileLauncher
ptr <- Ptr GValue -> IO (Ptr FileLauncher)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr FileLauncher)
        if Ptr FileLauncher
ptr Ptr FileLauncher -> Ptr FileLauncher -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr FileLauncher
forall a. Ptr a
FP.nullPtr
        then FileLauncher -> Maybe FileLauncher
forall a. a -> Maybe a
P.Just (FileLauncher -> Maybe FileLauncher)
-> IO FileLauncher -> IO (Maybe FileLauncher)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr FileLauncher -> FileLauncher)
-> Ptr FileLauncher -> IO FileLauncher
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr FileLauncher -> FileLauncher
FileLauncher Ptr FileLauncher
ptr
        else Maybe FileLauncher -> IO (Maybe FileLauncher)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe FileLauncher
forall a. Maybe a
P.Nothing
        
    

#if defined(ENABLE_OVERLOADING)
type family ResolveFileLauncherMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveFileLauncherMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveFileLauncherMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveFileLauncherMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveFileLauncherMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveFileLauncherMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveFileLauncherMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveFileLauncherMethod "launch" o = FileLauncherLaunchMethodInfo
    ResolveFileLauncherMethod "launchFinish" o = FileLauncherLaunchFinishMethodInfo
    ResolveFileLauncherMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveFileLauncherMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveFileLauncherMethod "openContainingFolder" o = FileLauncherOpenContainingFolderMethodInfo
    ResolveFileLauncherMethod "openContainingFolderFinish" o = FileLauncherOpenContainingFolderFinishMethodInfo
    ResolveFileLauncherMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveFileLauncherMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveFileLauncherMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveFileLauncherMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveFileLauncherMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveFileLauncherMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveFileLauncherMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveFileLauncherMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveFileLauncherMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveFileLauncherMethod "getFile" o = FileLauncherGetFileMethodInfo
    ResolveFileLauncherMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveFileLauncherMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveFileLauncherMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveFileLauncherMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveFileLauncherMethod "setFile" o = FileLauncherSetFileMethodInfo
    ResolveFileLauncherMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveFileLauncherMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveFileLauncherMethod t FileLauncher, O.OverloadedMethod info FileLauncher p) => OL.IsLabel t (FileLauncher -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif

#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveFileLauncherMethod t FileLauncher, O.OverloadedMethod info FileLauncher p, R.HasField t FileLauncher p) => R.HasField t FileLauncher p where
    getField = O.overloadedMethod @info

#endif

instance (info ~ ResolveFileLauncherMethod t FileLauncher, O.OverloadedMethodInfo info FileLauncher) => OL.IsLabel t (O.MethodProxy info FileLauncher) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif

#endif

-- VVV Prop "file"
   -- Type: TInterface (Name {namespace = "Gio", name = "File"})
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just True,Just True)

-- | Get the value of the “@file@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' fileLauncher #file
-- @
getFileLauncherFile :: (MonadIO m, IsFileLauncher o) => o -> m (Maybe Gio.File.File)
getFileLauncherFile :: forall (m :: * -> *) o.
(MonadIO m, IsFileLauncher o) =>
o -> m (Maybe File)
getFileLauncherFile o
obj = IO (Maybe File) -> m (Maybe File)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe File) -> m (Maybe File))
-> IO (Maybe File) -> m (Maybe File)
forall a b. (a -> b) -> a -> b
$ o -> String -> (ManagedPtr File -> File) -> IO (Maybe File)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"file" ManagedPtr File -> File
Gio.File.File

-- | Set the value of the “@file@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' fileLauncher [ #file 'Data.GI.Base.Attributes.:=' value ]
-- @
setFileLauncherFile :: (MonadIO m, IsFileLauncher o, Gio.File.IsFile a) => o -> a -> m ()
setFileLauncherFile :: forall (m :: * -> *) o a.
(MonadIO m, IsFileLauncher o, IsFile a) =>
o -> a -> m ()
setFileLauncherFile o
obj a
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Maybe a -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"file" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)

-- | Construct a `GValueConstruct` with valid value for the “@file@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructFileLauncherFile :: (IsFileLauncher o, MIO.MonadIO m, Gio.File.IsFile a) => a -> m (GValueConstruct o)
constructFileLauncherFile :: forall o (m :: * -> *) a.
(IsFileLauncher o, MonadIO m, IsFile a) =>
a -> m (GValueConstruct o)
constructFileLauncherFile a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"file" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)

-- | Set the value of the “@file@” property to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #file
-- @
clearFileLauncherFile :: (MonadIO m, IsFileLauncher o) => o -> m ()
clearFileLauncherFile :: forall (m :: * -> *) o. (MonadIO m, IsFileLauncher o) => o -> m ()
clearFileLauncherFile o
obj = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe File -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"file" (Maybe File
forall a. Maybe a
Nothing :: Maybe Gio.File.File)

#if defined(ENABLE_OVERLOADING)
data FileLauncherFilePropertyInfo
instance AttrInfo FileLauncherFilePropertyInfo where
    type AttrAllowedOps FileLauncherFilePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint FileLauncherFilePropertyInfo = IsFileLauncher
    type AttrSetTypeConstraint FileLauncherFilePropertyInfo = Gio.File.IsFile
    type AttrTransferTypeConstraint FileLauncherFilePropertyInfo = Gio.File.IsFile
    type AttrTransferType FileLauncherFilePropertyInfo = Gio.File.File
    type AttrGetType FileLauncherFilePropertyInfo = (Maybe Gio.File.File)
    type AttrLabel FileLauncherFilePropertyInfo = "file"
    type AttrOrigin FileLauncherFilePropertyInfo = FileLauncher
    attrGet = getFileLauncherFile
    attrSet = setFileLauncherFile
    attrTransfer _ v = do
        unsafeCastTo Gio.File.File v
    attrConstruct = constructFileLauncherFile
    attrClear = clearFileLauncherFile
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.FileLauncher.file"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-FileLauncher.html#g:attr:file"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList FileLauncher
type instance O.AttributeList FileLauncher = FileLauncherAttributeList
type FileLauncherAttributeList = ('[ '("file", FileLauncherFilePropertyInfo)] :: [(Symbol, DK.Type)])
#endif

#if defined(ENABLE_OVERLOADING)
fileLauncherFile :: AttrLabelProxy "file"
fileLauncherFile = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList FileLauncher = FileLauncherSignalList
type FileLauncherSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, DK.Type)])

#endif

-- method FileLauncher::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "file"
--           , argType = TInterface Name { namespace = "Gio" , name = "File" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the file to open" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gtk" , name = "FileLauncher" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_file_launcher_new" gtk_file_launcher_new :: 
    Ptr Gio.File.File ->                    -- file : TInterface (Name {namespace = "Gio", name = "File"})
    IO (Ptr FileLauncher)

-- | Creates a new @GtkFileLauncher@ object.
-- 
-- /Since: 4.10/
fileLauncherNew ::
    (B.CallStack.HasCallStack, MonadIO m, Gio.File.IsFile a) =>
    Maybe (a)
    -- ^ /@file@/: the file to open
    -> m FileLauncher
    -- ^ __Returns:__ the new @GtkFileLauncher@
fileLauncherNew :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFile a) =>
Maybe a -> m FileLauncher
fileLauncherNew Maybe a
file = IO FileLauncher -> m FileLauncher
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO FileLauncher -> m FileLauncher)
-> IO FileLauncher -> m FileLauncher
forall a b. (a -> b) -> a -> b
$ do
    Ptr File
maybeFile <- case Maybe a
file of
        Maybe a
Nothing -> Ptr File -> IO (Ptr File)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr File
forall a. Ptr a
nullPtr
        Just a
jFile -> do
            Ptr File
jFile' <- a -> IO (Ptr File)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
jFile
            Ptr File -> IO (Ptr File)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr File
jFile'
    Ptr FileLauncher
result <- Ptr File -> IO (Ptr FileLauncher)
gtk_file_launcher_new Ptr File
maybeFile
    Text -> Ptr FileLauncher -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"fileLauncherNew" Ptr FileLauncher
result
    FileLauncher
result' <- ((ManagedPtr FileLauncher -> FileLauncher)
-> Ptr FileLauncher -> IO FileLauncher
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr FileLauncher -> FileLauncher
FileLauncher) Ptr FileLauncher
result
    Maybe a -> (a -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe a
file a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    FileLauncher -> IO FileLauncher
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FileLauncher
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method FileLauncher::get_file
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "FileLauncher" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkFileLauncher`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gio" , name = "File" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_file_launcher_get_file" gtk_file_launcher_get_file :: 
    Ptr FileLauncher ->                     -- self : TInterface (Name {namespace = "Gtk", name = "FileLauncher"})
    IO (Ptr Gio.File.File)

-- | Gets the file that will be opened.
-- 
-- /Since: 4.10/
fileLauncherGetFile ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileLauncher a) =>
    a
    -- ^ /@self@/: a @GtkFileLauncher@
    -> m (Maybe Gio.File.File)
    -- ^ __Returns:__ the file
fileLauncherGetFile :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFileLauncher a) =>
a -> m (Maybe File)
fileLauncherGetFile a
self = IO (Maybe File) -> m (Maybe File)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe File) -> m (Maybe File))
-> IO (Maybe File) -> m (Maybe File)
forall a b. (a -> b) -> a -> b
$ do
    Ptr FileLauncher
self' <- a -> IO (Ptr FileLauncher)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr File
result <- Ptr FileLauncher -> IO (Ptr File)
gtk_file_launcher_get_file Ptr FileLauncher
self'
    Maybe File
maybeResult <- Ptr File -> (Ptr File -> IO File) -> IO (Maybe File)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr File
result ((Ptr File -> IO File) -> IO (Maybe File))
-> (Ptr File -> IO File) -> IO (Maybe File)
forall a b. (a -> b) -> a -> b
$ \Ptr File
result' -> do
        File
result'' <- ((ManagedPtr File -> File) -> Ptr File -> IO File
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr File -> File
Gio.File.File) Ptr File
result'
        File -> IO File
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return File
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Maybe File -> IO (Maybe File)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe File
maybeResult

#if defined(ENABLE_OVERLOADING)
data FileLauncherGetFileMethodInfo
instance (signature ~ (m (Maybe Gio.File.File)), MonadIO m, IsFileLauncher a) => O.OverloadedMethod FileLauncherGetFileMethodInfo a signature where
    overloadedMethod = fileLauncherGetFile

instance O.OverloadedMethodInfo FileLauncherGetFileMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.FileLauncher.fileLauncherGetFile",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-FileLauncher.html#v:fileLauncherGetFile"
        })


#endif

-- method FileLauncher::launch
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "FileLauncher" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkFileLauncher`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "parent"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Window" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the parent `GtkWindow`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GCancellable` to cancel the operation"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "callback"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "AsyncReadyCallback" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a callback to call when the operation is complete"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = 4
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "data to pass to @callback"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_file_launcher_launch" gtk_file_launcher_launch :: 
    Ptr FileLauncher ->                     -- self : TInterface (Name {namespace = "Gtk", name = "FileLauncher"})
    Ptr Gtk.Window.Window ->                -- parent : TInterface (Name {namespace = "Gtk", name = "Window"})
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    FunPtr Gio.Callbacks.C_AsyncReadyCallback -> -- callback : TInterface (Name {namespace = "Gio", name = "AsyncReadyCallback"})
    Ptr () ->                               -- user_data : TBasicType TPtr
    IO ()

-- | Launch an application to open the file.
-- 
-- This may present an app chooser dialog to the user.
-- 
-- The /@callback@/ will be called when the operation is completed.
-- It should call 'GI.Gtk.Objects.FileLauncher.fileLauncherLaunchFinish' to obtain
-- the result.
-- 
-- /Since: 4.10/
fileLauncherLaunch ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileLauncher a, Gtk.Window.IsWindow b, Gio.Cancellable.IsCancellable c) =>
    a
    -- ^ /@self@/: a @GtkFileLauncher@
    -> Maybe (b)
    -- ^ /@parent@/: the parent @GtkWindow@
    -> Maybe (c)
    -- ^ /@cancellable@/: a @GCancellable@ to cancel the operation
    -> Maybe (Gio.Callbacks.AsyncReadyCallback)
    -- ^ /@callback@/: a callback to call when the operation is complete
    -> m ()
fileLauncherLaunch :: forall (m :: * -> *) a b c.
(HasCallStack, MonadIO m, IsFileLauncher a, IsWindow b,
 IsCancellable c) =>
a -> Maybe b -> Maybe c -> Maybe AsyncReadyCallback -> m ()
fileLauncherLaunch a
self Maybe b
parent Maybe c
cancellable Maybe AsyncReadyCallback
callback = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr FileLauncher
self' <- a -> IO (Ptr FileLauncher)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Window
maybeParent <- case Maybe b
parent of
        Maybe b
Nothing -> Ptr Window -> IO (Ptr Window)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Window
forall a. Ptr a
nullPtr
        Just b
jParent -> do
            Ptr Window
jParent' <- b -> IO (Ptr Window)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jParent
            Ptr Window -> IO (Ptr Window)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Window
jParent'
    Ptr Cancellable
maybeCancellable <- case Maybe c
cancellable of
        Maybe c
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
        Just c
jCancellable -> do
            Ptr Cancellable
jCancellable' <- c -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr c
jCancellable
            Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
    FunPtr C_AsyncReadyCallback
maybeCallback <- case Maybe AsyncReadyCallback
callback of
        Maybe AsyncReadyCallback
Nothing -> FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Any -> FunPtr C_AsyncReadyCallback
forall a b. Ptr a -> FunPtr b
castPtrToFunPtr Ptr Any
forall a. Ptr a
nullPtr)
        Just AsyncReadyCallback
jCallback -> do
            Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback <- IO (Ptr (FunPtr C_AsyncReadyCallback))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr Gio.Callbacks.C_AsyncReadyCallback))
            FunPtr C_AsyncReadyCallback
jCallback' <- C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
Gio.Callbacks.mk_AsyncReadyCallback (Maybe (Ptr (FunPtr C_AsyncReadyCallback))
-> AsyncReadyCallback -> C_AsyncReadyCallback
Gio.Callbacks.wrap_AsyncReadyCallback (Ptr (FunPtr C_AsyncReadyCallback)
-> Maybe (Ptr (FunPtr C_AsyncReadyCallback))
forall a. a -> Maybe a
Just Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback) AsyncReadyCallback
jCallback)
            Ptr (FunPtr C_AsyncReadyCallback)
-> FunPtr C_AsyncReadyCallback -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback FunPtr C_AsyncReadyCallback
jCallback'
            FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_AsyncReadyCallback
jCallback'
    let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
    Ptr FileLauncher
-> Ptr Window
-> Ptr Cancellable
-> FunPtr C_AsyncReadyCallback
-> Ptr ()
-> IO ()
gtk_file_launcher_launch Ptr FileLauncher
self' Ptr Window
maybeParent Ptr Cancellable
maybeCancellable FunPtr C_AsyncReadyCallback
maybeCallback Ptr ()
forall a. Ptr a
userData
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
parent b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    Maybe c -> (c -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe c
cancellable c -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data FileLauncherLaunchMethodInfo
instance (signature ~ (Maybe (b) -> Maybe (c) -> Maybe (Gio.Callbacks.AsyncReadyCallback) -> m ()), MonadIO m, IsFileLauncher a, Gtk.Window.IsWindow b, Gio.Cancellable.IsCancellable c) => O.OverloadedMethod FileLauncherLaunchMethodInfo a signature where
    overloadedMethod = fileLauncherLaunch

instance O.OverloadedMethodInfo FileLauncherLaunchMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.FileLauncher.fileLauncherLaunch",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-FileLauncher.html#v:fileLauncherLaunch"
        })


#endif

-- method FileLauncher::launch_finish
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "FileLauncher" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkFileLauncher`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "result"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "AsyncResult" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GAsyncResult`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "gtk_file_launcher_launch_finish" gtk_file_launcher_launch_finish :: 
    Ptr FileLauncher ->                     -- self : TInterface (Name {namespace = "Gtk", name = "FileLauncher"})
    Ptr Gio.AsyncResult.AsyncResult ->      -- result : TInterface (Name {namespace = "Gio", name = "AsyncResult"})
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Finishes the 'GI.Gtk.Objects.FileLauncher.fileLauncherLaunch' call and
-- returns the result.
-- 
-- /Since: 4.10/
fileLauncherLaunchFinish ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileLauncher a, Gio.AsyncResult.IsAsyncResult b) =>
    a
    -- ^ /@self@/: a @GtkFileLauncher@
    -> b
    -- ^ /@result@/: a @GAsyncResult@
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
fileLauncherLaunchFinish :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsFileLauncher a, IsAsyncResult b) =>
a -> b -> m ()
fileLauncherLaunchFinish a
self b
result_ = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr FileLauncher
self' <- a -> IO (Ptr FileLauncher)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr AsyncResult
result_' <- b -> IO (Ptr AsyncResult)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
result_
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr FileLauncher -> Ptr AsyncResult -> Ptr (Ptr GError) -> IO CInt
gtk_file_launcher_launch_finish Ptr FileLauncher
self' Ptr AsyncResult
result_'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
        b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
result_
        () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
data FileLauncherLaunchFinishMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsFileLauncher a, Gio.AsyncResult.IsAsyncResult b) => O.OverloadedMethod FileLauncherLaunchFinishMethodInfo a signature where
    overloadedMethod = fileLauncherLaunchFinish

instance O.OverloadedMethodInfo FileLauncherLaunchFinishMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.FileLauncher.fileLauncherLaunchFinish",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-FileLauncher.html#v:fileLauncherLaunchFinish"
        })


#endif

-- method FileLauncher::open_containing_folder
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "FileLauncher" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkFileLauncher`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "parent"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Window" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the parent `GtkWindow`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GCancellable` to cancel the operation"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "callback"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "AsyncReadyCallback" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a callback to call when the operation is complete"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = 4
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "data to pass to @callback"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_file_launcher_open_containing_folder" gtk_file_launcher_open_containing_folder :: 
    Ptr FileLauncher ->                     -- self : TInterface (Name {namespace = "Gtk", name = "FileLauncher"})
    Ptr Gtk.Window.Window ->                -- parent : TInterface (Name {namespace = "Gtk", name = "Window"})
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    FunPtr Gio.Callbacks.C_AsyncReadyCallback -> -- callback : TInterface (Name {namespace = "Gio", name = "AsyncReadyCallback"})
    Ptr () ->                               -- user_data : TBasicType TPtr
    IO ()

-- | Launch a file manager to show the file in its parent directory.
-- 
-- This is only supported native files. It will fail if /@file@/
-- is e.g. a http:\/\/ uri.
-- 
-- The /@callback@/ will be called when the operation is completed.
-- It should call 'GI.Gtk.Objects.FileLauncher.fileLauncherOpenContainingFolderFinish'
-- to obtain the result.
-- 
-- /Since: 4.10/
fileLauncherOpenContainingFolder ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileLauncher a, Gtk.Window.IsWindow b, Gio.Cancellable.IsCancellable c) =>
    a
    -- ^ /@self@/: a @GtkFileLauncher@
    -> Maybe (b)
    -- ^ /@parent@/: the parent @GtkWindow@
    -> Maybe (c)
    -- ^ /@cancellable@/: a @GCancellable@ to cancel the operation
    -> Maybe (Gio.Callbacks.AsyncReadyCallback)
    -- ^ /@callback@/: a callback to call when the operation is complete
    -> m ()
fileLauncherOpenContainingFolder :: forall (m :: * -> *) a b c.
(HasCallStack, MonadIO m, IsFileLauncher a, IsWindow b,
 IsCancellable c) =>
a -> Maybe b -> Maybe c -> Maybe AsyncReadyCallback -> m ()
fileLauncherOpenContainingFolder a
self Maybe b
parent Maybe c
cancellable Maybe AsyncReadyCallback
callback = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr FileLauncher
self' <- a -> IO (Ptr FileLauncher)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Window
maybeParent <- case Maybe b
parent of
        Maybe b
Nothing -> Ptr Window -> IO (Ptr Window)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Window
forall a. Ptr a
nullPtr
        Just b
jParent -> do
            Ptr Window
jParent' <- b -> IO (Ptr Window)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jParent
            Ptr Window -> IO (Ptr Window)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Window
jParent'
    Ptr Cancellable
maybeCancellable <- case Maybe c
cancellable of
        Maybe c
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
        Just c
jCancellable -> do
            Ptr Cancellable
jCancellable' <- c -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr c
jCancellable
            Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
    FunPtr C_AsyncReadyCallback
maybeCallback <- case Maybe AsyncReadyCallback
callback of
        Maybe AsyncReadyCallback
Nothing -> FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Any -> FunPtr C_AsyncReadyCallback
forall a b. Ptr a -> FunPtr b
castPtrToFunPtr Ptr Any
forall a. Ptr a
nullPtr)
        Just AsyncReadyCallback
jCallback -> do
            Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback <- IO (Ptr (FunPtr C_AsyncReadyCallback))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr Gio.Callbacks.C_AsyncReadyCallback))
            FunPtr C_AsyncReadyCallback
jCallback' <- C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
Gio.Callbacks.mk_AsyncReadyCallback (Maybe (Ptr (FunPtr C_AsyncReadyCallback))
-> AsyncReadyCallback -> C_AsyncReadyCallback
Gio.Callbacks.wrap_AsyncReadyCallback (Ptr (FunPtr C_AsyncReadyCallback)
-> Maybe (Ptr (FunPtr C_AsyncReadyCallback))
forall a. a -> Maybe a
Just Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback) AsyncReadyCallback
jCallback)
            Ptr (FunPtr C_AsyncReadyCallback)
-> FunPtr C_AsyncReadyCallback -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback FunPtr C_AsyncReadyCallback
jCallback'
            FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_AsyncReadyCallback
jCallback'
    let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
    Ptr FileLauncher
-> Ptr Window
-> Ptr Cancellable
-> FunPtr C_AsyncReadyCallback
-> Ptr ()
-> IO ()
gtk_file_launcher_open_containing_folder Ptr FileLauncher
self' Ptr Window
maybeParent Ptr Cancellable
maybeCancellable FunPtr C_AsyncReadyCallback
maybeCallback Ptr ()
forall a. Ptr a
userData
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
parent b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    Maybe c -> (c -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe c
cancellable c -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data FileLauncherOpenContainingFolderMethodInfo
instance (signature ~ (Maybe (b) -> Maybe (c) -> Maybe (Gio.Callbacks.AsyncReadyCallback) -> m ()), MonadIO m, IsFileLauncher a, Gtk.Window.IsWindow b, Gio.Cancellable.IsCancellable c) => O.OverloadedMethod FileLauncherOpenContainingFolderMethodInfo a signature where
    overloadedMethod = fileLauncherOpenContainingFolder

instance O.OverloadedMethodInfo FileLauncherOpenContainingFolderMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.FileLauncher.fileLauncherOpenContainingFolder",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-FileLauncher.html#v:fileLauncherOpenContainingFolder"
        })


#endif

-- method FileLauncher::open_containing_folder_finish
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "FileLauncher" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkFileLauncher`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "result"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "AsyncResult" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GAsyncResult`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "gtk_file_launcher_open_containing_folder_finish" gtk_file_launcher_open_containing_folder_finish :: 
    Ptr FileLauncher ->                     -- self : TInterface (Name {namespace = "Gtk", name = "FileLauncher"})
    Ptr Gio.AsyncResult.AsyncResult ->      -- result : TInterface (Name {namespace = "Gio", name = "AsyncResult"})
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Finishes the 'GI.Gtk.Objects.FileLauncher.fileLauncherOpenContainingFolder'
-- call and returns the result.
-- 
-- /Since: 4.10/
fileLauncherOpenContainingFolderFinish ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileLauncher a, Gio.AsyncResult.IsAsyncResult b) =>
    a
    -- ^ /@self@/: a @GtkFileLauncher@
    -> b
    -- ^ /@result@/: a @GAsyncResult@
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
fileLauncherOpenContainingFolderFinish :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsFileLauncher a, IsAsyncResult b) =>
a -> b -> m ()
fileLauncherOpenContainingFolderFinish a
self b
result_ = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr FileLauncher
self' <- a -> IO (Ptr FileLauncher)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr AsyncResult
result_' <- b -> IO (Ptr AsyncResult)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
result_
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr FileLauncher -> Ptr AsyncResult -> Ptr (Ptr GError) -> IO CInt
gtk_file_launcher_open_containing_folder_finish Ptr FileLauncher
self' Ptr AsyncResult
result_'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
        b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
result_
        () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
data FileLauncherOpenContainingFolderFinishMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsFileLauncher a, Gio.AsyncResult.IsAsyncResult b) => O.OverloadedMethod FileLauncherOpenContainingFolderFinishMethodInfo a signature where
    overloadedMethod = fileLauncherOpenContainingFolderFinish

instance O.OverloadedMethodInfo FileLauncherOpenContainingFolderFinishMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.FileLauncher.fileLauncherOpenContainingFolderFinish",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-FileLauncher.html#v:fileLauncherOpenContainingFolderFinish"
        })


#endif

-- method FileLauncher::set_file
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "FileLauncher" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkFileLauncher`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "file"
--           , argType = TInterface Name { namespace = "Gio" , name = "File" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GFile`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_file_launcher_set_file" gtk_file_launcher_set_file :: 
    Ptr FileLauncher ->                     -- self : TInterface (Name {namespace = "Gtk", name = "FileLauncher"})
    Ptr Gio.File.File ->                    -- file : TInterface (Name {namespace = "Gio", name = "File"})
    IO ()

-- | Sets the file that will be opened.
-- 
-- /Since: 4.10/
fileLauncherSetFile ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileLauncher a, Gio.File.IsFile b) =>
    a
    -- ^ /@self@/: a @GtkFileLauncher@
    -> Maybe (b)
    -- ^ /@file@/: a @GFile@
    -> m ()
fileLauncherSetFile :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsFileLauncher a, IsFile b) =>
a -> Maybe b -> m ()
fileLauncherSetFile a
self Maybe b
file = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr FileLauncher
self' <- a -> IO (Ptr FileLauncher)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr File
maybeFile <- case Maybe b
file of
        Maybe b
Nothing -> Ptr File -> IO (Ptr File)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr File
forall a. Ptr a
nullPtr
        Just b
jFile -> do
            Ptr File
jFile' <- b -> IO (Ptr File)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jFile
            Ptr File -> IO (Ptr File)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr File
jFile'
    Ptr FileLauncher -> Ptr File -> IO ()
gtk_file_launcher_set_file Ptr FileLauncher
self' Ptr File
maybeFile
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
file b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data FileLauncherSetFileMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsFileLauncher a, Gio.File.IsFile b) => O.OverloadedMethod FileLauncherSetFileMethodInfo a signature where
    overloadedMethod = fileLauncherSetFile

instance O.OverloadedMethodInfo FileLauncherSetFileMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.FileLauncher.fileLauncherSetFile",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-FileLauncher.html#v:fileLauncherSetFile"
        })


#endif