{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A @GtkUriLauncher@ object collects the arguments that are needed to open a uri
-- 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.UriLauncher.uriLauncherLaunch' function.
-- This API follows the GIO async pattern, and the result can be obtained by
-- calling 'GI.Gtk.Objects.UriLauncher.uriLauncherLaunchFinish'.
-- 
-- To launch a file, use t'GI.Gtk.Objects.FileLauncher.FileLauncher'.
-- 
-- /Since: 4.10/

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

module GI.Gtk.Objects.UriLauncher
    ( 

-- * Exported types
    UriLauncher(..)                         ,
    IsUriLauncher                           ,
    toUriLauncher                           ,


 -- * 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.UriLauncher#g:method:launch"), [launchFinish]("GI.Gtk.Objects.UriLauncher#g:method:launchFinish"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [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"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getUri]("GI.Gtk.Objects.UriLauncher#g:method:getUri").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setUri]("GI.Gtk.Objects.UriLauncher#g:method:setUri").

#if defined(ENABLE_OVERLOADING)
    ResolveUriLauncherMethod                ,
#endif

-- ** getUri #method:getUri#

#if defined(ENABLE_OVERLOADING)
    UriLauncherGetUriMethodInfo             ,
#endif
    uriLauncherGetUri                       ,


-- ** launch #method:launch#

#if defined(ENABLE_OVERLOADING)
    UriLauncherLaunchMethodInfo             ,
#endif
    uriLauncherLaunch                       ,


-- ** launchFinish #method:launchFinish#

#if defined(ENABLE_OVERLOADING)
    UriLauncherLaunchFinishMethodInfo       ,
#endif
    uriLauncherLaunchFinish                 ,


-- ** new #method:new#

    uriLauncherNew                          ,


-- ** setUri #method:setUri#

#if defined(ENABLE_OVERLOADING)
    UriLauncherSetUriMethodInfo             ,
#endif
    uriLauncherSetUri                       ,




 -- * Properties


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

#if defined(ENABLE_OVERLOADING)
    UriLauncherUriPropertyInfo              ,
#endif
    clearUriLauncherUri                     ,
    constructUriLauncherUri                 ,
    getUriLauncherUri                       ,
    setUriLauncherUri                       ,
#if defined(ENABLE_OVERLOADING)
    uriLauncherUri                          ,
#endif




    ) 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 Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT

-- Workaround for https://gitlab.haskell.org/ghc/ghc/-/issues/23392
#if MIN_VERSION_base(4,18,0)
import qualified GI.Cairo.Structs.Context as Cairo.Context
import qualified GI.Cairo.Structs.FontOptions as Cairo.FontOptions
import qualified GI.GLib.Callbacks as GLib.Callbacks
import qualified GI.GLib.Structs.Bytes as GLib.Bytes
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gdk.Flags as Gdk.Flags
import qualified GI.Gdk.Interfaces.Paintable as Gdk.Paintable
import qualified GI.Gdk.Objects.Clipboard as Gdk.Clipboard
import qualified GI.Gdk.Objects.Cursor as Gdk.Cursor
import qualified GI.Gdk.Objects.Device as Gdk.Device
import qualified GI.Gdk.Objects.Display as Gdk.Display
import qualified GI.Gdk.Objects.Event as Gdk.Event
import qualified GI.Gdk.Objects.FrameClock as Gdk.FrameClock
import qualified GI.Gdk.Objects.Monitor as Gdk.Monitor
import qualified GI.Gdk.Objects.Snapshot as Gdk.Snapshot
import qualified GI.Gdk.Objects.Surface as Gdk.Surface
import qualified GI.Gdk.Objects.Texture as Gdk.Texture
import qualified GI.Gdk.Structs.RGBA as Gdk.RGBA
import qualified GI.Gdk.Structs.Rectangle as Gdk.Rectangle
import qualified GI.Gio.Callbacks as Gio.Callbacks
import qualified GI.Gio.Flags as Gio.Flags
import qualified GI.Gio.Interfaces.ActionGroup as Gio.ActionGroup
import qualified GI.Gio.Interfaces.ActionMap as Gio.ActionMap
import qualified GI.Gio.Interfaces.AsyncResult as Gio.AsyncResult
import qualified GI.Gio.Interfaces.Icon as Gio.Icon
import qualified GI.Gio.Interfaces.ListModel as Gio.ListModel
import qualified GI.Gio.Objects.Application as Gio.Application
import qualified GI.Gio.Objects.Cancellable as Gio.Cancellable
import qualified GI.Gio.Objects.Menu as Gio.Menu
import qualified GI.Gio.Objects.MenuModel as Gio.MenuModel
import qualified GI.Graphene.Structs.Matrix as Graphene.Matrix
import qualified GI.Graphene.Structs.Point as Graphene.Point
import qualified GI.Graphene.Structs.Point3D as Graphene.Point3D
import qualified GI.Graphene.Structs.Rect as Graphene.Rect
import qualified GI.Graphene.Structs.Size as Graphene.Size
import qualified GI.Graphene.Structs.Vec3 as Graphene.Vec3
import qualified GI.Graphene.Structs.Vec4 as Graphene.Vec4
import qualified GI.Gsk.Enums as Gsk.Enums
import qualified GI.Gsk.Objects.GLShader as Gsk.GLShader
import qualified GI.Gsk.Objects.RenderNode as Gsk.RenderNode
import qualified GI.Gsk.Objects.Renderer as Gsk.Renderer
import qualified GI.Gsk.Structs.ColorStop as Gsk.ColorStop
import qualified GI.Gsk.Structs.Path as Gsk.Path
import qualified GI.Gsk.Structs.RoundedRect as Gsk.RoundedRect
import qualified GI.Gsk.Structs.Shadow as Gsk.Shadow
import qualified GI.Gsk.Structs.Stroke as Gsk.Stroke
import qualified GI.Gsk.Structs.Transform as Gsk.Transform
import qualified GI.Gtk.Callbacks as Gtk.Callbacks
import {-# SOURCE #-} qualified GI.Gtk.Enums as Gtk.Enums
import {-# SOURCE #-} qualified GI.Gtk.Flags as Gtk.Flags
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Accessible as Gtk.Accessible
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Buildable as Gtk.Buildable
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.ConstraintTarget as Gtk.ConstraintTarget
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Native as Gtk.Native
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Root as Gtk.Root
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.ShortcutManager as Gtk.ShortcutManager
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.StyleProvider as Gtk.StyleProvider
import {-# SOURCE #-} qualified GI.Gtk.Objects.ATContext as Gtk.ATContext
import {-# SOURCE #-} qualified GI.Gtk.Objects.Application as Gtk.Application
import {-# SOURCE #-} qualified GI.Gtk.Objects.EventController as Gtk.EventController
import {-# SOURCE #-} qualified GI.Gtk.Objects.LayoutChild as Gtk.LayoutChild
import {-# SOURCE #-} qualified GI.Gtk.Objects.LayoutManager as Gtk.LayoutManager
import {-# SOURCE #-} qualified GI.Gtk.Objects.Settings as Gtk.Settings
import {-# SOURCE #-} qualified GI.Gtk.Objects.Snapshot as Gtk.Snapshot
import {-# SOURCE #-} qualified GI.Gtk.Objects.StyleContext as Gtk.StyleContext
import {-# SOURCE #-} qualified GI.Gtk.Objects.Tooltip as Gtk.Tooltip
import {-# SOURCE #-} qualified GI.Gtk.Objects.Widget as Gtk.Widget
import {-# SOURCE #-} qualified GI.Gtk.Objects.Window as Gtk.Window
import {-# SOURCE #-} qualified GI.Gtk.Objects.WindowGroup as Gtk.WindowGroup
import {-# SOURCE #-} qualified GI.Gtk.Structs.Border as Gtk.Border
import {-# SOURCE #-} qualified GI.Gtk.Structs.Requisition as Gtk.Requisition
import qualified GI.Pango.Enums as Pango.Enums
import qualified GI.Pango.Objects.Context as Pango.Context
import qualified GI.Pango.Objects.FontMap as Pango.FontMap
import qualified GI.Pango.Objects.Layout as Pango.Layout

#else
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.Objects.Cancellable as Gio.Cancellable
import {-# SOURCE #-} qualified GI.Gtk.Objects.Window as Gtk.Window

#endif

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

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

foreign import ccall "gtk_uri_launcher_get_type"
    c_gtk_uri_launcher_get_type :: IO B.Types.GType

instance B.Types.TypedObject UriLauncher where
    glibType :: IO GType
glibType = IO GType
c_gtk_uri_launcher_get_type

instance B.Types.GObject UriLauncher

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

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

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

-- | Convert 'UriLauncher' 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 UriLauncher) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gtk_uri_launcher_get_type
    gvalueSet_ :: Ptr GValue -> Maybe UriLauncher -> IO ()
gvalueSet_ Ptr GValue
gv Maybe UriLauncher
P.Nothing = Ptr GValue -> Ptr UriLauncher -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr UriLauncher
forall a. Ptr a
FP.nullPtr :: FP.Ptr UriLauncher)
    gvalueSet_ Ptr GValue
gv (P.Just UriLauncher
obj) = UriLauncher -> (Ptr UriLauncher -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr UriLauncher
obj (Ptr GValue -> Ptr UriLauncher -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe UriLauncher)
gvalueGet_ Ptr GValue
gv = do
        Ptr UriLauncher
ptr <- Ptr GValue -> IO (Ptr UriLauncher)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr UriLauncher)
        if Ptr UriLauncher
ptr Ptr UriLauncher -> Ptr UriLauncher -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr UriLauncher
forall a. Ptr a
FP.nullPtr
        then UriLauncher -> Maybe UriLauncher
forall a. a -> Maybe a
P.Just (UriLauncher -> Maybe UriLauncher)
-> IO UriLauncher -> IO (Maybe UriLauncher)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr UriLauncher -> UriLauncher)
-> Ptr UriLauncher -> IO UriLauncher
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr UriLauncher -> UriLauncher
UriLauncher Ptr UriLauncher
ptr
        else Maybe UriLauncher -> IO (Maybe UriLauncher)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe UriLauncher
forall a. Maybe a
P.Nothing
        
    

#if defined(ENABLE_OVERLOADING)
type family ResolveUriLauncherMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveUriLauncherMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveUriLauncherMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveUriLauncherMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveUriLauncherMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveUriLauncherMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveUriLauncherMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveUriLauncherMethod "launch" o = UriLauncherLaunchMethodInfo
    ResolveUriLauncherMethod "launchFinish" o = UriLauncherLaunchFinishMethodInfo
    ResolveUriLauncherMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveUriLauncherMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveUriLauncherMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveUriLauncherMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveUriLauncherMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveUriLauncherMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveUriLauncherMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveUriLauncherMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveUriLauncherMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveUriLauncherMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveUriLauncherMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveUriLauncherMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveUriLauncherMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveUriLauncherMethod "getUri" o = UriLauncherGetUriMethodInfo
    ResolveUriLauncherMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveUriLauncherMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveUriLauncherMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveUriLauncherMethod "setUri" o = UriLauncherSetUriMethodInfo
    ResolveUriLauncherMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveUriLauncherMethod t UriLauncher, O.OverloadedMethod info UriLauncher p) => OL.IsLabel t (UriLauncher -> 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 ~ ResolveUriLauncherMethod t UriLauncher, O.OverloadedMethod info UriLauncher p, R.HasField t UriLauncher p) => R.HasField t UriLauncher p where
    getField = O.overloadedMethod @info

#endif

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

#endif

-- VVV Prop "uri"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just True,Just True)

-- | Get the value of the “@uri@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' uriLauncher #uri
-- @
getUriLauncherUri :: (MonadIO m, IsUriLauncher o) => o -> m (Maybe T.Text)
getUriLauncherUri :: forall (m :: * -> *) o.
(MonadIO m, IsUriLauncher o) =>
o -> m (Maybe Text)
getUriLauncherUri o
obj = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"uri"

-- | Set the value of the “@uri@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' uriLauncher [ #uri 'Data.GI.Base.Attributes.:=' value ]
-- @
setUriLauncherUri :: (MonadIO m, IsUriLauncher o) => o -> T.Text -> m ()
setUriLauncherUri :: forall (m :: * -> *) o.
(MonadIO m, IsUriLauncher o) =>
o -> Text -> m ()
setUriLauncherUri o
obj Text
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 Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"uri" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Construct a `GValueConstruct` with valid value for the “@uri@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructUriLauncherUri :: (IsUriLauncher o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructUriLauncherUri :: forall o (m :: * -> *).
(IsUriLauncher o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructUriLauncherUri Text
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 Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"uri" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

-- | Set the value of the “@uri@” 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' #uri
-- @
clearUriLauncherUri :: (MonadIO m, IsUriLauncher o) => o -> m ()
clearUriLauncherUri :: forall (m :: * -> *) o. (MonadIO m, IsUriLauncher o) => o -> m ()
clearUriLauncherUri 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 Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"uri" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)

#if defined(ENABLE_OVERLOADING)
data UriLauncherUriPropertyInfo
instance AttrInfo UriLauncherUriPropertyInfo where
    type AttrAllowedOps UriLauncherUriPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint UriLauncherUriPropertyInfo = IsUriLauncher
    type AttrSetTypeConstraint UriLauncherUriPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint UriLauncherUriPropertyInfo = (~) T.Text
    type AttrTransferType UriLauncherUriPropertyInfo = T.Text
    type AttrGetType UriLauncherUriPropertyInfo = (Maybe T.Text)
    type AttrLabel UriLauncherUriPropertyInfo = "uri"
    type AttrOrigin UriLauncherUriPropertyInfo = UriLauncher
    attrGet = getUriLauncherUri
    attrSet = setUriLauncherUri
    attrTransfer _ v = do
        return v
    attrConstruct = constructUriLauncherUri
    attrClear = clearUriLauncherUri
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.UriLauncher.uri"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.9/docs/GI-Gtk-Objects-UriLauncher.html#g:attr:uri"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList UriLauncher
type instance O.AttributeList UriLauncher = UriLauncherAttributeList
type UriLauncherAttributeList = ('[ '("uri", UriLauncherUriPropertyInfo)] :: [(Symbol, DK.Type)])
#endif

#if defined(ENABLE_OVERLOADING)
uriLauncherUri :: AttrLabelProxy "uri"
uriLauncherUri = AttrLabelProxy

#endif

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

#endif

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

foreign import ccall "gtk_uri_launcher_new" gtk_uri_launcher_new :: 
    CString ->                              -- uri : TBasicType TUTF8
    IO (Ptr UriLauncher)

-- | Creates a new @GtkUriLauncher@ object.
-- 
-- /Since: 4.10/
uriLauncherNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Maybe (T.Text)
    -- ^ /@uri@/: the uri to open
    -> m UriLauncher
    -- ^ __Returns:__ the new @GtkUriLauncher@
uriLauncherNew :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Maybe Text -> m UriLauncher
uriLauncherNew Maybe Text
uri = IO UriLauncher -> m UriLauncher
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO UriLauncher -> m UriLauncher)
-> IO UriLauncher -> m UriLauncher
forall a b. (a -> b) -> a -> b
$ do
    Ptr CChar
maybeUri <- case Maybe Text
uri of
        Maybe Text
Nothing -> Ptr CChar -> IO (Ptr CChar)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
nullPtr
        Just Text
jUri -> do
            Ptr CChar
jUri' <- Text -> IO (Ptr CChar)
textToCString Text
jUri
            Ptr CChar -> IO (Ptr CChar)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
jUri'
    Ptr UriLauncher
result <- Ptr CChar -> IO (Ptr UriLauncher)
gtk_uri_launcher_new Ptr CChar
maybeUri
    Text -> Ptr UriLauncher -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"uriLauncherNew" Ptr UriLauncher
result
    UriLauncher
result' <- ((ManagedPtr UriLauncher -> UriLauncher)
-> Ptr UriLauncher -> IO UriLauncher
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr UriLauncher -> UriLauncher
UriLauncher) Ptr UriLauncher
result
    Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
maybeUri
    UriLauncher -> IO UriLauncher
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return UriLauncher
result'

#if defined(ENABLE_OVERLOADING)
#endif

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

foreign import ccall "gtk_uri_launcher_get_uri" gtk_uri_launcher_get_uri :: 
    Ptr UriLauncher ->                      -- self : TInterface (Name {namespace = "Gtk", name = "UriLauncher"})
    IO CString

-- | Gets the uri that will be opened.
-- 
-- /Since: 4.10/
uriLauncherGetUri ::
    (B.CallStack.HasCallStack, MonadIO m, IsUriLauncher a) =>
    a
    -- ^ /@self@/: a @GtkUriLauncher@
    -> m (Maybe T.Text)
    -- ^ __Returns:__ the uri
uriLauncherGetUri :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsUriLauncher a) =>
a -> m (Maybe Text)
uriLauncherGetUri a
self = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ do
    Ptr UriLauncher
self' <- a -> IO (Ptr UriLauncher)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr CChar
result <- Ptr UriLauncher -> IO (Ptr CChar)
gtk_uri_launcher_get_uri Ptr UriLauncher
self'
    Maybe Text
maybeResult <- Ptr CChar -> (Ptr CChar -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr CChar
result ((Ptr CChar -> IO Text) -> IO (Maybe Text))
-> (Ptr CChar -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \Ptr CChar
result' -> do
        Text
result'' <- HasCallStack => Ptr CChar -> IO Text
Ptr CChar -> IO Text
cstringToText Ptr CChar
result'
        Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Maybe Text -> IO (Maybe Text)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

#if defined(ENABLE_OVERLOADING)
data UriLauncherGetUriMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m, IsUriLauncher a) => O.OverloadedMethod UriLauncherGetUriMethodInfo a signature where
    overloadedMethod = uriLauncherGetUri

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


#endif

-- method UriLauncher::launch
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "UriLauncher" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkUriLauncher`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_uri_launcher_launch" gtk_uri_launcher_launch :: 
    Ptr UriLauncher ->                      -- self : TInterface (Name {namespace = "Gtk", name = "UriLauncher"})
    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 uri.
-- 
-- 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.UriLauncher.uriLauncherLaunchFinish' to obtain
-- the result.
-- 
-- /Since: 4.10/
uriLauncherLaunch ::
    (B.CallStack.HasCallStack, MonadIO m, IsUriLauncher a, Gtk.Window.IsWindow b, Gio.Cancellable.IsCancellable c) =>
    a
    -- ^ /@self@/: a @GtkUriLauncher@
    -> 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 ()
uriLauncherLaunch :: forall (m :: * -> *) a b c.
(HasCallStack, MonadIO m, IsUriLauncher a, IsWindow b,
 IsCancellable c) =>
a -> Maybe b -> Maybe c -> Maybe AsyncReadyCallback -> m ()
uriLauncherLaunch 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 UriLauncher
self' <- a -> IO (Ptr UriLauncher)
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_WithClosures -> 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 -> AsyncReadyCallback_WithClosures
Gio.Callbacks.drop_closures_AsyncReadyCallback 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 UriLauncher
-> Ptr Window
-> Ptr Cancellable
-> FunPtr C_AsyncReadyCallback
-> Ptr ()
-> IO ()
gtk_uri_launcher_launch Ptr UriLauncher
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 UriLauncherLaunchMethodInfo
instance (signature ~ (Maybe (b) -> Maybe (c) -> Maybe (Gio.Callbacks.AsyncReadyCallback) -> m ()), MonadIO m, IsUriLauncher a, Gtk.Window.IsWindow b, Gio.Cancellable.IsCancellable c) => O.OverloadedMethod UriLauncherLaunchMethodInfo a signature where
    overloadedMethod = uriLauncherLaunch

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


#endif

-- method UriLauncher::launch_finish
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "UriLauncher" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkUriLauncher`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = 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
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

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

-- | Finishes the 'GI.Gtk.Objects.UriLauncher.uriLauncherLaunch' call and
-- returns the result.
-- 
-- /Since: 4.10/
uriLauncherLaunchFinish ::
    (B.CallStack.HasCallStack, MonadIO m, IsUriLauncher a, Gio.AsyncResult.IsAsyncResult b) =>
    a
    -- ^ /@self@/: a @GtkUriLauncher@
    -> b
    -- ^ /@result@/: a @GAsyncResult@
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
uriLauncherLaunchFinish :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsUriLauncher a, IsAsyncResult b) =>
a -> b -> m ()
uriLauncherLaunchFinish 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 UriLauncher
self' <- a -> IO (Ptr UriLauncher)
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 UriLauncher -> Ptr AsyncResult -> Ptr (Ptr GError) -> IO CInt
gtk_uri_launcher_launch_finish Ptr UriLauncher
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 UriLauncherLaunchFinishMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsUriLauncher a, Gio.AsyncResult.IsAsyncResult b) => O.OverloadedMethod UriLauncherLaunchFinishMethodInfo a signature where
    overloadedMethod = uriLauncherLaunchFinish

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


#endif

-- method UriLauncher::set_uri
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "UriLauncher" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkUriLauncher`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "uri"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the uri" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_uri_launcher_set_uri" gtk_uri_launcher_set_uri :: 
    Ptr UriLauncher ->                      -- self : TInterface (Name {namespace = "Gtk", name = "UriLauncher"})
    CString ->                              -- uri : TBasicType TUTF8
    IO ()

-- | Sets the uri that will be opened.
-- 
-- /Since: 4.10/
uriLauncherSetUri ::
    (B.CallStack.HasCallStack, MonadIO m, IsUriLauncher a) =>
    a
    -- ^ /@self@/: a @GtkUriLauncher@
    -> Maybe (T.Text)
    -- ^ /@uri@/: the uri
    -> m ()
uriLauncherSetUri :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsUriLauncher a) =>
a -> Maybe Text -> m ()
uriLauncherSetUri a
self Maybe Text
uri = 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 UriLauncher
self' <- a -> IO (Ptr UriLauncher)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr CChar
maybeUri <- case Maybe Text
uri of
        Maybe Text
Nothing -> Ptr CChar -> IO (Ptr CChar)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
nullPtr
        Just Text
jUri -> do
            Ptr CChar
jUri' <- Text -> IO (Ptr CChar)
textToCString Text
jUri
            Ptr CChar -> IO (Ptr CChar)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
jUri'
    Ptr UriLauncher -> Ptr CChar -> IO ()
gtk_uri_launcher_set_uri Ptr UriLauncher
self' Ptr CChar
maybeUri
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
maybeUri
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data UriLauncherSetUriMethodInfo
instance (signature ~ (Maybe (T.Text) -> m ()), MonadIO m, IsUriLauncher a) => O.OverloadedMethod UriLauncherSetUriMethodInfo a signature where
    overloadedMethod = uriLauncherSetUri

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


#endif