{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- t'GI.Gio.Interfaces.Drive.Drive' - this represent a piece of hardware connected to the machine.
-- It\'s generally only created for removable hardware or hardware with
-- removable media.
-- 
-- t'GI.Gio.Interfaces.Drive.Drive' is a container class for t'GI.Gio.Interfaces.Volume.Volume' objects that stem from
-- the same piece of media. As such, t'GI.Gio.Interfaces.Drive.Drive' abstracts a drive with
-- (or without) removable media and provides operations for querying
-- whether media is available, determining whether media change is
-- automatically detected and ejecting the media.
-- 
-- If the t'GI.Gio.Interfaces.Drive.Drive' reports that media isn\'t automatically detected, one
-- can poll for media; typically one should not do this periodically
-- as a poll for media operation is potentially expensive and may
-- spin up the drive creating noise.
-- 
-- t'GI.Gio.Interfaces.Drive.Drive' supports starting and stopping drives with authentication
-- support for the former. This can be used to support a diverse set
-- of use cases including connecting\/disconnecting iSCSI devices,
-- powering down external disk enclosures and starting\/stopping
-- multi-disk devices such as RAID devices. Note that the actual
-- semantics and side-effects of starting\/stopping a t'GI.Gio.Interfaces.Drive.Drive' may vary
-- according to implementation. To choose the correct verbs in e.g. a
-- file manager, use 'GI.Gio.Interfaces.Drive.driveGetStartStopType'.
-- 
-- For porting from GnomeVFS note that there is no equivalent of
-- t'GI.Gio.Interfaces.Drive.Drive' in that API.

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

module GI.Gio.Interfaces.Drive
    ( 

-- * Exported types
    Drive(..)                               ,
    IsDrive                                 ,
    toDrive                                 ,


 -- * 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"), [canEject]("GI.Gio.Interfaces.Drive#g:method:canEject"), [canPollForMedia]("GI.Gio.Interfaces.Drive#g:method:canPollForMedia"), [canStart]("GI.Gio.Interfaces.Drive#g:method:canStart"), [canStartDegraded]("GI.Gio.Interfaces.Drive#g:method:canStartDegraded"), [canStop]("GI.Gio.Interfaces.Drive#g:method:canStop"), [eject]("GI.Gio.Interfaces.Drive#g:method:eject"), [ejectFinish]("GI.Gio.Interfaces.Drive#g:method:ejectFinish"), [ejectWithOperation]("GI.Gio.Interfaces.Drive#g:method:ejectWithOperation"), [ejectWithOperationFinish]("GI.Gio.Interfaces.Drive#g:method:ejectWithOperationFinish"), [enumerateIdentifiers]("GI.Gio.Interfaces.Drive#g:method:enumerateIdentifiers"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [hasMedia]("GI.Gio.Interfaces.Drive#g:method:hasMedia"), [hasVolumes]("GI.Gio.Interfaces.Drive#g:method:hasVolumes"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [isMediaCheckAutomatic]("GI.Gio.Interfaces.Drive#g:method:isMediaCheckAutomatic"), [isMediaRemovable]("GI.Gio.Interfaces.Drive#g:method:isMediaRemovable"), [isRemovable]("GI.Gio.Interfaces.Drive#g:method:isRemovable"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [pollForMedia]("GI.Gio.Interfaces.Drive#g:method:pollForMedia"), [pollForMediaFinish]("GI.Gio.Interfaces.Drive#g:method:pollForMediaFinish"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [start]("GI.Gio.Interfaces.Drive#g:method:start"), [startFinish]("GI.Gio.Interfaces.Drive#g:method:startFinish"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [stop]("GI.Gio.Interfaces.Drive#g:method:stop"), [stopFinish]("GI.Gio.Interfaces.Drive#g:method:stopFinish"), [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"), [getIcon]("GI.Gio.Interfaces.Drive#g:method:getIcon"), [getIdentifier]("GI.Gio.Interfaces.Drive#g:method:getIdentifier"), [getName]("GI.Gio.Interfaces.Drive#g:method:getName"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getSortKey]("GI.Gio.Interfaces.Drive#g:method:getSortKey"), [getStartStopType]("GI.Gio.Interfaces.Drive#g:method:getStartStopType"), [getSymbolicIcon]("GI.Gio.Interfaces.Drive#g:method:getSymbolicIcon"), [getVolumes]("GI.Gio.Interfaces.Drive#g:method:getVolumes").
-- 
-- ==== 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").

#if defined(ENABLE_OVERLOADING)
    ResolveDriveMethod                      ,
#endif

-- ** canEject #method:canEject#

#if defined(ENABLE_OVERLOADING)
    DriveCanEjectMethodInfo                 ,
#endif
    driveCanEject                           ,


-- ** canPollForMedia #method:canPollForMedia#

#if defined(ENABLE_OVERLOADING)
    DriveCanPollForMediaMethodInfo          ,
#endif
    driveCanPollForMedia                    ,


-- ** canStart #method:canStart#

#if defined(ENABLE_OVERLOADING)
    DriveCanStartMethodInfo                 ,
#endif
    driveCanStart                           ,


-- ** canStartDegraded #method:canStartDegraded#

#if defined(ENABLE_OVERLOADING)
    DriveCanStartDegradedMethodInfo         ,
#endif
    driveCanStartDegraded                   ,


-- ** canStop #method:canStop#

#if defined(ENABLE_OVERLOADING)
    DriveCanStopMethodInfo                  ,
#endif
    driveCanStop                            ,


-- ** eject #method:eject#

#if defined(ENABLE_OVERLOADING)
    DriveEjectMethodInfo                    ,
#endif
    driveEject                              ,


-- ** ejectFinish #method:ejectFinish#

#if defined(ENABLE_OVERLOADING)
    DriveEjectFinishMethodInfo              ,
#endif
    driveEjectFinish                        ,


-- ** ejectWithOperation #method:ejectWithOperation#

#if defined(ENABLE_OVERLOADING)
    DriveEjectWithOperationMethodInfo       ,
#endif
    driveEjectWithOperation                 ,


-- ** ejectWithOperationFinish #method:ejectWithOperationFinish#

#if defined(ENABLE_OVERLOADING)
    DriveEjectWithOperationFinishMethodInfo ,
#endif
    driveEjectWithOperationFinish           ,


-- ** enumerateIdentifiers #method:enumerateIdentifiers#

#if defined(ENABLE_OVERLOADING)
    DriveEnumerateIdentifiersMethodInfo     ,
#endif
    driveEnumerateIdentifiers               ,


-- ** getIcon #method:getIcon#

#if defined(ENABLE_OVERLOADING)
    DriveGetIconMethodInfo                  ,
#endif
    driveGetIcon                            ,


-- ** getIdentifier #method:getIdentifier#

#if defined(ENABLE_OVERLOADING)
    DriveGetIdentifierMethodInfo            ,
#endif
    driveGetIdentifier                      ,


-- ** getName #method:getName#

#if defined(ENABLE_OVERLOADING)
    DriveGetNameMethodInfo                  ,
#endif
    driveGetName                            ,


-- ** getSortKey #method:getSortKey#

#if defined(ENABLE_OVERLOADING)
    DriveGetSortKeyMethodInfo               ,
#endif
    driveGetSortKey                         ,


-- ** getStartStopType #method:getStartStopType#

#if defined(ENABLE_OVERLOADING)
    DriveGetStartStopTypeMethodInfo         ,
#endif
    driveGetStartStopType                   ,


-- ** getSymbolicIcon #method:getSymbolicIcon#

#if defined(ENABLE_OVERLOADING)
    DriveGetSymbolicIconMethodInfo          ,
#endif
    driveGetSymbolicIcon                    ,


-- ** getVolumes #method:getVolumes#

#if defined(ENABLE_OVERLOADING)
    DriveGetVolumesMethodInfo               ,
#endif
    driveGetVolumes                         ,


-- ** hasMedia #method:hasMedia#

#if defined(ENABLE_OVERLOADING)
    DriveHasMediaMethodInfo                 ,
#endif
    driveHasMedia                           ,


-- ** hasVolumes #method:hasVolumes#

#if defined(ENABLE_OVERLOADING)
    DriveHasVolumesMethodInfo               ,
#endif
    driveHasVolumes                         ,


-- ** isMediaCheckAutomatic #method:isMediaCheckAutomatic#

#if defined(ENABLE_OVERLOADING)
    DriveIsMediaCheckAutomaticMethodInfo    ,
#endif
    driveIsMediaCheckAutomatic              ,


-- ** isMediaRemovable #method:isMediaRemovable#

#if defined(ENABLE_OVERLOADING)
    DriveIsMediaRemovableMethodInfo         ,
#endif
    driveIsMediaRemovable                   ,


-- ** isRemovable #method:isRemovable#

#if defined(ENABLE_OVERLOADING)
    DriveIsRemovableMethodInfo              ,
#endif
    driveIsRemovable                        ,


-- ** pollForMedia #method:pollForMedia#

#if defined(ENABLE_OVERLOADING)
    DrivePollForMediaMethodInfo             ,
#endif
    drivePollForMedia                       ,


-- ** pollForMediaFinish #method:pollForMediaFinish#

#if defined(ENABLE_OVERLOADING)
    DrivePollForMediaFinishMethodInfo       ,
#endif
    drivePollForMediaFinish                 ,


-- ** start #method:start#

#if defined(ENABLE_OVERLOADING)
    DriveStartMethodInfo                    ,
#endif
    driveStart                              ,


-- ** startFinish #method:startFinish#

#if defined(ENABLE_OVERLOADING)
    DriveStartFinishMethodInfo              ,
#endif
    driveStartFinish                        ,


-- ** stop #method:stop#

#if defined(ENABLE_OVERLOADING)
    DriveStopMethodInfo                     ,
#endif
    driveStop                               ,


-- ** stopFinish #method:stopFinish#

#if defined(ENABLE_OVERLOADING)
    DriveStopFinishMethodInfo               ,
#endif
    driveStopFinish                         ,




 -- * Signals


-- ** changed #signal:changed#

    C_DriveChangedCallback                  ,
    DriveChangedCallback                    ,
#if defined(ENABLE_OVERLOADING)
    DriveChangedSignalInfo                  ,
#endif
    afterDriveChanged                       ,
    genClosure_DriveChanged                 ,
    mk_DriveChangedCallback                 ,
    noDriveChangedCallback                  ,
    onDriveChanged                          ,
    wrap_DriveChangedCallback               ,


-- ** disconnected #signal:disconnected#

    C_DriveDisconnectedCallback             ,
    DriveDisconnectedCallback               ,
#if defined(ENABLE_OVERLOADING)
    DriveDisconnectedSignalInfo             ,
#endif
    afterDriveDisconnected                  ,
    genClosure_DriveDisconnected            ,
    mk_DriveDisconnectedCallback            ,
    noDriveDisconnectedCallback             ,
    onDriveDisconnected                     ,
    wrap_DriveDisconnectedCallback          ,


-- ** ejectButton #signal:ejectButton#

    C_DriveEjectButtonCallback              ,
    DriveEjectButtonCallback                ,
#if defined(ENABLE_OVERLOADING)
    DriveEjectButtonSignalInfo              ,
#endif
    afterDriveEjectButton                   ,
    genClosure_DriveEjectButton             ,
    mk_DriveEjectButtonCallback             ,
    noDriveEjectButtonCallback              ,
    onDriveEjectButton                      ,
    wrap_DriveEjectButtonCallback           ,


-- ** stopButton #signal:stopButton#

    C_DriveStopButtonCallback               ,
    DriveStopButtonCallback                 ,
#if defined(ENABLE_OVERLOADING)
    DriveStopButtonSignalInfo               ,
#endif
    afterDriveStopButton                    ,
    genClosure_DriveStopButton              ,
    mk_DriveStopButtonCallback              ,
    noDriveStopButtonCallback               ,
    onDriveStopButton                       ,
    wrap_DriveStopButtonCallback            ,




    ) 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.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.Text as T
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 {-# SOURCE #-} qualified GI.Gio.Enums as Gio.Enums
import {-# SOURCE #-} qualified GI.Gio.Flags as Gio.Flags
import {-# SOURCE #-} qualified GI.Gio.Interfaces.AsyncResult as Gio.AsyncResult
import {-# SOURCE #-} qualified GI.Gio.Interfaces.Icon as Gio.Icon
import {-# SOURCE #-} qualified GI.Gio.Interfaces.Volume as Gio.Volume
import {-# SOURCE #-} qualified GI.Gio.Objects.Cancellable as Gio.Cancellable
import {-# SOURCE #-} qualified GI.Gio.Objects.MountOperation as Gio.MountOperation

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

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

foreign import ccall "g_drive_get_type"
    c_g_drive_get_type :: IO B.Types.GType

instance B.Types.TypedObject Drive where
    glibType :: IO GType
glibType = IO GType
c_g_drive_get_type

instance B.Types.GObject Drive

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

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

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

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

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Drive
type instance O.AttributeList Drive = DriveAttributeList
type DriveAttributeList = ('[ ] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveDriveMethod (t :: Symbol) (o :: *) :: * where
    ResolveDriveMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveDriveMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveDriveMethod "canEject" o = DriveCanEjectMethodInfo
    ResolveDriveMethod "canPollForMedia" o = DriveCanPollForMediaMethodInfo
    ResolveDriveMethod "canStart" o = DriveCanStartMethodInfo
    ResolveDriveMethod "canStartDegraded" o = DriveCanStartDegradedMethodInfo
    ResolveDriveMethod "canStop" o = DriveCanStopMethodInfo
    ResolveDriveMethod "eject" o = DriveEjectMethodInfo
    ResolveDriveMethod "ejectFinish" o = DriveEjectFinishMethodInfo
    ResolveDriveMethod "ejectWithOperation" o = DriveEjectWithOperationMethodInfo
    ResolveDriveMethod "ejectWithOperationFinish" o = DriveEjectWithOperationFinishMethodInfo
    ResolveDriveMethod "enumerateIdentifiers" o = DriveEnumerateIdentifiersMethodInfo
    ResolveDriveMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveDriveMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveDriveMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveDriveMethod "hasMedia" o = DriveHasMediaMethodInfo
    ResolveDriveMethod "hasVolumes" o = DriveHasVolumesMethodInfo
    ResolveDriveMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveDriveMethod "isMediaCheckAutomatic" o = DriveIsMediaCheckAutomaticMethodInfo
    ResolveDriveMethod "isMediaRemovable" o = DriveIsMediaRemovableMethodInfo
    ResolveDriveMethod "isRemovable" o = DriveIsRemovableMethodInfo
    ResolveDriveMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveDriveMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveDriveMethod "pollForMedia" o = DrivePollForMediaMethodInfo
    ResolveDriveMethod "pollForMediaFinish" o = DrivePollForMediaFinishMethodInfo
    ResolveDriveMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveDriveMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveDriveMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveDriveMethod "start" o = DriveStartMethodInfo
    ResolveDriveMethod "startFinish" o = DriveStartFinishMethodInfo
    ResolveDriveMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveDriveMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveDriveMethod "stop" o = DriveStopMethodInfo
    ResolveDriveMethod "stopFinish" o = DriveStopFinishMethodInfo
    ResolveDriveMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveDriveMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveDriveMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveDriveMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveDriveMethod "getIcon" o = DriveGetIconMethodInfo
    ResolveDriveMethod "getIdentifier" o = DriveGetIdentifierMethodInfo
    ResolveDriveMethod "getName" o = DriveGetNameMethodInfo
    ResolveDriveMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveDriveMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveDriveMethod "getSortKey" o = DriveGetSortKeyMethodInfo
    ResolveDriveMethod "getStartStopType" o = DriveGetStartStopTypeMethodInfo
    ResolveDriveMethod "getSymbolicIcon" o = DriveGetSymbolicIconMethodInfo
    ResolveDriveMethod "getVolumes" o = DriveGetVolumesMethodInfo
    ResolveDriveMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveDriveMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveDriveMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveDriveMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

-- method Drive::can_eject
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "drive"
--           , argType = TInterface Name { namespace = "Gio" , name = "Drive" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDrive." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "g_drive_can_eject" g_drive_can_eject :: 
    Ptr Drive ->                            -- drive : TInterface (Name {namespace = "Gio", name = "Drive"})
    IO CInt

-- | Checks if a drive can be ejected.
driveCanEject ::
    (B.CallStack.HasCallStack, MonadIO m, IsDrive a) =>
    a
    -- ^ /@drive@/: a t'GI.Gio.Interfaces.Drive.Drive'.
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the /@drive@/ can be ejected, 'P.False' otherwise.
driveCanEject :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDrive a) =>
a -> m Bool
driveCanEject a
drive = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Drive
drive' <- a -> IO (Ptr Drive)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
drive
    CInt
result <- Ptr Drive -> IO CInt
g_drive_can_eject Ptr Drive
drive'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
drive
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data DriveCanEjectMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsDrive a) => O.OverloadedMethod DriveCanEjectMethodInfo a signature where
    overloadedMethod = driveCanEject

instance O.OverloadedMethodInfo DriveCanEjectMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Interfaces.Drive.driveCanEject",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Interfaces-Drive.html#v:driveCanEject"
        }


#endif

-- method Drive::can_poll_for_media
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "drive"
--           , argType = TInterface Name { namespace = "Gio" , name = "Drive" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDrive." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "g_drive_can_poll_for_media" g_drive_can_poll_for_media :: 
    Ptr Drive ->                            -- drive : TInterface (Name {namespace = "Gio", name = "Drive"})
    IO CInt

-- | Checks if a drive can be polled for media changes.
driveCanPollForMedia ::
    (B.CallStack.HasCallStack, MonadIO m, IsDrive a) =>
    a
    -- ^ /@drive@/: a t'GI.Gio.Interfaces.Drive.Drive'.
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the /@drive@/ can be polled for media changes,
    --     'P.False' otherwise.
driveCanPollForMedia :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDrive a) =>
a -> m Bool
driveCanPollForMedia a
drive = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Drive
drive' <- a -> IO (Ptr Drive)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
drive
    CInt
result <- Ptr Drive -> IO CInt
g_drive_can_poll_for_media Ptr Drive
drive'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
drive
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data DriveCanPollForMediaMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsDrive a) => O.OverloadedMethod DriveCanPollForMediaMethodInfo a signature where
    overloadedMethod = driveCanPollForMedia

instance O.OverloadedMethodInfo DriveCanPollForMediaMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Interfaces.Drive.driveCanPollForMedia",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Interfaces-Drive.html#v:driveCanPollForMedia"
        }


#endif

-- method Drive::can_start
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "drive"
--           , argType = TInterface Name { namespace = "Gio" , name = "Drive" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDrive." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "g_drive_can_start" g_drive_can_start :: 
    Ptr Drive ->                            -- drive : TInterface (Name {namespace = "Gio", name = "Drive"})
    IO CInt

-- | Checks if a drive can be started.
-- 
-- /Since: 2.22/
driveCanStart ::
    (B.CallStack.HasCallStack, MonadIO m, IsDrive a) =>
    a
    -- ^ /@drive@/: a t'GI.Gio.Interfaces.Drive.Drive'.
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the /@drive@/ can be started, 'P.False' otherwise.
driveCanStart :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDrive a) =>
a -> m Bool
driveCanStart a
drive = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Drive
drive' <- a -> IO (Ptr Drive)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
drive
    CInt
result <- Ptr Drive -> IO CInt
g_drive_can_start Ptr Drive
drive'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
drive
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data DriveCanStartMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsDrive a) => O.OverloadedMethod DriveCanStartMethodInfo a signature where
    overloadedMethod = driveCanStart

instance O.OverloadedMethodInfo DriveCanStartMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Interfaces.Drive.driveCanStart",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Interfaces-Drive.html#v:driveCanStart"
        }


#endif

-- method Drive::can_start_degraded
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "drive"
--           , argType = TInterface Name { namespace = "Gio" , name = "Drive" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDrive." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "g_drive_can_start_degraded" g_drive_can_start_degraded :: 
    Ptr Drive ->                            -- drive : TInterface (Name {namespace = "Gio", name = "Drive"})
    IO CInt

-- | Checks if a drive can be started degraded.
-- 
-- /Since: 2.22/
driveCanStartDegraded ::
    (B.CallStack.HasCallStack, MonadIO m, IsDrive a) =>
    a
    -- ^ /@drive@/: a t'GI.Gio.Interfaces.Drive.Drive'.
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the /@drive@/ can be started degraded, 'P.False' otherwise.
driveCanStartDegraded :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDrive a) =>
a -> m Bool
driveCanStartDegraded a
drive = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Drive
drive' <- a -> IO (Ptr Drive)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
drive
    CInt
result <- Ptr Drive -> IO CInt
g_drive_can_start_degraded Ptr Drive
drive'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
drive
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data DriveCanStartDegradedMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsDrive a) => O.OverloadedMethod DriveCanStartDegradedMethodInfo a signature where
    overloadedMethod = driveCanStartDegraded

instance O.OverloadedMethodInfo DriveCanStartDegradedMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Interfaces.Drive.driveCanStartDegraded",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Interfaces-Drive.html#v:driveCanStartDegraded"
        }


#endif

-- method Drive::can_stop
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "drive"
--           , argType = TInterface Name { namespace = "Gio" , name = "Drive" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDrive." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "g_drive_can_stop" g_drive_can_stop :: 
    Ptr Drive ->                            -- drive : TInterface (Name {namespace = "Gio", name = "Drive"})
    IO CInt

-- | Checks if a drive can be stopped.
-- 
-- /Since: 2.22/
driveCanStop ::
    (B.CallStack.HasCallStack, MonadIO m, IsDrive a) =>
    a
    -- ^ /@drive@/: a t'GI.Gio.Interfaces.Drive.Drive'.
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the /@drive@/ can be stopped, 'P.False' otherwise.
driveCanStop :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDrive a) =>
a -> m Bool
driveCanStop a
drive = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Drive
drive' <- a -> IO (Ptr Drive)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
drive
    CInt
result <- Ptr Drive -> IO CInt
g_drive_can_stop Ptr Drive
drive'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
drive
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data DriveCanStopMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsDrive a) => O.OverloadedMethod DriveCanStopMethodInfo a signature where
    overloadedMethod = driveCanStop

instance O.OverloadedMethodInfo DriveCanStopMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Interfaces.Drive.driveCanStop",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Interfaces-Drive.html#v:driveCanStop"
        }


#endif

-- method Drive::eject
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "drive"
--           , argType = TInterface Name { namespace = "Gio" , name = "Drive" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDrive." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "MountUnmountFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "flags affecting the unmount if required for eject"
--                 , 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 "optional #GCancellable object, %NULL to ignore."
--                 , 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 #GAsyncReadyCallback, or %NULL."
--                 , 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 "user 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 "g_drive_eject" g_drive_eject :: 
    Ptr Drive ->                            -- drive : TInterface (Name {namespace = "Gio", name = "Drive"})
    CUInt ->                                -- flags : TInterface (Name {namespace = "Gio", name = "MountUnmountFlags"})
    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 ()

{-# DEPRECATED driveEject ["(Since version 2.22)","Use 'GI.Gio.Interfaces.Drive.driveEjectWithOperation' instead."] #-}
-- | Asynchronously ejects a drive.
-- 
-- When the operation is finished, /@callback@/ will be called.
-- You can then call 'GI.Gio.Interfaces.Drive.driveEjectFinish' to obtain the
-- result of the operation.
driveEject ::
    (B.CallStack.HasCallStack, MonadIO m, IsDrive a, Gio.Cancellable.IsCancellable b) =>
    a
    -- ^ /@drive@/: a t'GI.Gio.Interfaces.Drive.Drive'.
    -> [Gio.Flags.MountUnmountFlags]
    -- ^ /@flags@/: flags affecting the unmount if required for eject
    -> Maybe (b)
    -- ^ /@cancellable@/: optional t'GI.Gio.Objects.Cancellable.Cancellable' object, 'P.Nothing' to ignore.
    -> Maybe (Gio.Callbacks.AsyncReadyCallback)
    -- ^ /@callback@/: a t'GI.Gio.Callbacks.AsyncReadyCallback', or 'P.Nothing'.
    -> m ()
driveEject :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDrive a, IsCancellable b) =>
a
-> [MountUnmountFlags]
-> Maybe b
-> Maybe AsyncReadyCallback
-> m ()
driveEject a
drive [MountUnmountFlags]
flags Maybe b
cancellable Maybe AsyncReadyCallback
callback = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Drive
drive' <- a -> IO (Ptr Drive)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
drive
    let flags' :: CUInt
flags' = [MountUnmountFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [MountUnmountFlags]
flags
    Ptr Cancellable
maybeCancellable <- case Maybe b
cancellable of
        Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
        Just b
jCancellable -> do
            Ptr Cancellable
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
            Ptr Cancellable -> IO (Ptr Cancellable)
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 (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 (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 Drive
-> CUInt
-> Ptr Cancellable
-> FunPtr C_AsyncReadyCallback
-> Ptr ()
-> IO ()
g_drive_eject Ptr Drive
drive' CUInt
flags' Ptr Cancellable
maybeCancellable FunPtr C_AsyncReadyCallback
maybeCallback Ptr ()
forall a. Ptr a
userData
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
drive
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
cancellable b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DriveEjectMethodInfo
instance (signature ~ ([Gio.Flags.MountUnmountFlags] -> Maybe (b) -> Maybe (Gio.Callbacks.AsyncReadyCallback) -> m ()), MonadIO m, IsDrive a, Gio.Cancellable.IsCancellable b) => O.OverloadedMethod DriveEjectMethodInfo a signature where
    overloadedMethod = driveEject

instance O.OverloadedMethodInfo DriveEjectMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Interfaces.Drive.driveEject",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Interfaces-Drive.html#v:driveEject"
        }


#endif

-- method Drive::eject_finish
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "drive"
--           , argType = TInterface Name { namespace = "Gio" , name = "Drive" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDrive." , 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 "g_drive_eject_finish" g_drive_eject_finish :: 
    Ptr Drive ->                            -- drive : TInterface (Name {namespace = "Gio", name = "Drive"})
    Ptr Gio.AsyncResult.AsyncResult ->      -- result : TInterface (Name {namespace = "Gio", name = "AsyncResult"})
    Ptr (Ptr GError) ->                     -- error
    IO CInt

{-# DEPRECATED driveEjectFinish ["(Since version 2.22)","Use 'GI.Gio.Interfaces.Drive.driveEjectWithOperationFinish' instead."] #-}
-- | Finishes ejecting a drive.
driveEjectFinish ::
    (B.CallStack.HasCallStack, MonadIO m, IsDrive a, Gio.AsyncResult.IsAsyncResult b) =>
    a
    -- ^ /@drive@/: a t'GI.Gio.Interfaces.Drive.Drive'.
    -> b
    -- ^ /@result@/: a t'GI.Gio.Interfaces.AsyncResult.AsyncResult'.
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
driveEjectFinish :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDrive a, IsAsyncResult b) =>
a -> b -> m ()
driveEjectFinish a
drive b
result_ = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Drive
drive' <- a -> IO (Ptr Drive)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
drive
    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 Drive -> Ptr AsyncResult -> Ptr (Ptr GError) -> IO CInt
g_drive_eject_finish Ptr Drive
drive' Ptr AsyncResult
result_'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
drive
        b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
result_
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

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

instance O.OverloadedMethodInfo DriveEjectFinishMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Interfaces.Drive.driveEjectFinish",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Interfaces-Drive.html#v:driveEjectFinish"
        }


#endif

-- method Drive::eject_with_operation
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "drive"
--           , argType = TInterface Name { namespace = "Gio" , name = "Drive" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDrive." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "MountUnmountFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "flags affecting the unmount if required for eject"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "mount_operation"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "MountOperation" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #GMountOperation or %NULL to avoid\n    user interaction."
--                 , 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 "optional #GCancellable object, %NULL to ignore."
--                 , 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 #GAsyncReadyCallback, or %NULL."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = 5
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "user data passed 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 "g_drive_eject_with_operation" g_drive_eject_with_operation :: 
    Ptr Drive ->                            -- drive : TInterface (Name {namespace = "Gio", name = "Drive"})
    CUInt ->                                -- flags : TInterface (Name {namespace = "Gio", name = "MountUnmountFlags"})
    Ptr Gio.MountOperation.MountOperation -> -- mount_operation : TInterface (Name {namespace = "Gio", name = "MountOperation"})
    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 ()

-- | Ejects a drive. This is an asynchronous operation, and is
-- finished by calling 'GI.Gio.Interfaces.Drive.driveEjectWithOperationFinish' with the /@drive@/
-- and t'GI.Gio.Interfaces.AsyncResult.AsyncResult' data returned in the /@callback@/.
-- 
-- /Since: 2.22/
driveEjectWithOperation ::
    (B.CallStack.HasCallStack, MonadIO m, IsDrive a, Gio.MountOperation.IsMountOperation b, Gio.Cancellable.IsCancellable c) =>
    a
    -- ^ /@drive@/: a t'GI.Gio.Interfaces.Drive.Drive'.
    -> [Gio.Flags.MountUnmountFlags]
    -- ^ /@flags@/: flags affecting the unmount if required for eject
    -> Maybe (b)
    -- ^ /@mountOperation@/: a t'GI.Gio.Objects.MountOperation.MountOperation' or 'P.Nothing' to avoid
    --     user interaction.
    -> Maybe (c)
    -- ^ /@cancellable@/: optional t'GI.Gio.Objects.Cancellable.Cancellable' object, 'P.Nothing' to ignore.
    -> Maybe (Gio.Callbacks.AsyncReadyCallback)
    -- ^ /@callback@/: a t'GI.Gio.Callbacks.AsyncReadyCallback', or 'P.Nothing'.
    -> m ()
driveEjectWithOperation :: forall (m :: * -> *) a b c.
(HasCallStack, MonadIO m, IsDrive a, IsMountOperation b,
 IsCancellable c) =>
a
-> [MountUnmountFlags]
-> Maybe b
-> Maybe c
-> Maybe AsyncReadyCallback
-> m ()
driveEjectWithOperation a
drive [MountUnmountFlags]
flags Maybe b
mountOperation Maybe c
cancellable Maybe AsyncReadyCallback
callback = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Drive
drive' <- a -> IO (Ptr Drive)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
drive
    let flags' :: CUInt
flags' = [MountUnmountFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [MountUnmountFlags]
flags
    Ptr MountOperation
maybeMountOperation <- case Maybe b
mountOperation of
        Maybe b
Nothing -> Ptr MountOperation -> IO (Ptr MountOperation)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr MountOperation
forall a. Ptr a
nullPtr
        Just b
jMountOperation -> do
            Ptr MountOperation
jMountOperation' <- b -> IO (Ptr MountOperation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jMountOperation
            Ptr MountOperation -> IO (Ptr MountOperation)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr MountOperation
jMountOperation'
    Ptr Cancellable
maybeCancellable <- case Maybe c
cancellable of
        Maybe c
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
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 (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 (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 (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 Drive
-> CUInt
-> Ptr MountOperation
-> Ptr Cancellable
-> FunPtr C_AsyncReadyCallback
-> Ptr ()
-> IO ()
g_drive_eject_with_operation Ptr Drive
drive' CUInt
flags' Ptr MountOperation
maybeMountOperation Ptr Cancellable
maybeCancellable FunPtr C_AsyncReadyCallback
maybeCallback Ptr ()
forall a. Ptr a
userData
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
drive
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
mountOperation 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 (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DriveEjectWithOperationMethodInfo
instance (signature ~ ([Gio.Flags.MountUnmountFlags] -> Maybe (b) -> Maybe (c) -> Maybe (Gio.Callbacks.AsyncReadyCallback) -> m ()), MonadIO m, IsDrive a, Gio.MountOperation.IsMountOperation b, Gio.Cancellable.IsCancellable c) => O.OverloadedMethod DriveEjectWithOperationMethodInfo a signature where
    overloadedMethod = driveEjectWithOperation

instance O.OverloadedMethodInfo DriveEjectWithOperationMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Interfaces.Drive.driveEjectWithOperation",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Interfaces-Drive.html#v:driveEjectWithOperation"
        }


#endif

-- method Drive::eject_with_operation_finish
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "drive"
--           , argType = TInterface Name { namespace = "Gio" , name = "Drive" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDrive." , 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 "g_drive_eject_with_operation_finish" g_drive_eject_with_operation_finish :: 
    Ptr Drive ->                            -- drive : TInterface (Name {namespace = "Gio", name = "Drive"})
    Ptr Gio.AsyncResult.AsyncResult ->      -- result : TInterface (Name {namespace = "Gio", name = "AsyncResult"})
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Finishes ejecting a drive. If any errors occurred during the operation,
-- /@error@/ will be set to contain the errors and 'P.False' will be returned.
-- 
-- /Since: 2.22/
driveEjectWithOperationFinish ::
    (B.CallStack.HasCallStack, MonadIO m, IsDrive a, Gio.AsyncResult.IsAsyncResult b) =>
    a
    -- ^ /@drive@/: a t'GI.Gio.Interfaces.Drive.Drive'.
    -> b
    -- ^ /@result@/: a t'GI.Gio.Interfaces.AsyncResult.AsyncResult'.
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
driveEjectWithOperationFinish :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDrive a, IsAsyncResult b) =>
a -> b -> m ()
driveEjectWithOperationFinish a
drive b
result_ = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Drive
drive' <- a -> IO (Ptr Drive)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
drive
    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 Drive -> Ptr AsyncResult -> Ptr (Ptr GError) -> IO CInt
g_drive_eject_with_operation_finish Ptr Drive
drive' Ptr AsyncResult
result_'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
drive
        b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
result_
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

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

instance O.OverloadedMethodInfo DriveEjectWithOperationFinishMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Interfaces.Drive.driveEjectWithOperationFinish",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Interfaces-Drive.html#v:driveEjectWithOperationFinish"
        }


#endif

-- method Drive::enumerate_identifiers
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "drive"
--           , argType = TInterface Name { namespace = "Gio" , name = "Drive" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDrive" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TCArray True (-1) (-1) (TBasicType TUTF8))
-- throws : False
-- Skip return : False

foreign import ccall "g_drive_enumerate_identifiers" g_drive_enumerate_identifiers :: 
    Ptr Drive ->                            -- drive : TInterface (Name {namespace = "Gio", name = "Drive"})
    IO (Ptr CString)

-- | Gets the kinds of identifiers that /@drive@/ has.
-- Use 'GI.Gio.Interfaces.Drive.driveGetIdentifier' to obtain the identifiers
-- themselves.
driveEnumerateIdentifiers ::
    (B.CallStack.HasCallStack, MonadIO m, IsDrive a) =>
    a
    -- ^ /@drive@/: a t'GI.Gio.Interfaces.Drive.Drive'
    -> m [T.Text]
    -- ^ __Returns:__ a 'P.Nothing'-terminated
    --     array of strings containing kinds of identifiers. Use 'GI.GLib.Functions.strfreev'
    --     to free.
driveEnumerateIdentifiers :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDrive a) =>
a -> m [Text]
driveEnumerateIdentifiers a
drive = IO [Text] -> m [Text]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Text] -> m [Text]) -> IO [Text] -> m [Text]
forall a b. (a -> b) -> a -> b
$ do
    Ptr Drive
drive' <- a -> IO (Ptr Drive)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
drive
    Ptr CString
result <- Ptr Drive -> IO (Ptr CString)
g_drive_enumerate_identifiers Ptr Drive
drive'
    Text -> Ptr CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"driveEnumerateIdentifiers" Ptr CString
result
    [Text]
result' <- HasCallStack => Ptr CString -> IO [Text]
Ptr CString -> IO [Text]
unpackZeroTerminatedUTF8CArray Ptr CString
result
    (CString -> IO ()) -> Ptr CString -> IO ()
forall a b. (Ptr a -> IO b) -> Ptr (Ptr a) -> IO ()
mapZeroTerminatedCArray CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
result
    Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
drive
    [Text] -> IO [Text]
forall (m :: * -> *) a. Monad m => a -> m a
return [Text]
result'

#if defined(ENABLE_OVERLOADING)
data DriveEnumerateIdentifiersMethodInfo
instance (signature ~ (m [T.Text]), MonadIO m, IsDrive a) => O.OverloadedMethod DriveEnumerateIdentifiersMethodInfo a signature where
    overloadedMethod = driveEnumerateIdentifiers

instance O.OverloadedMethodInfo DriveEnumerateIdentifiersMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Interfaces.Drive.driveEnumerateIdentifiers",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Interfaces-Drive.html#v:driveEnumerateIdentifiers"
        }


#endif

-- method Drive::get_icon
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "drive"
--           , argType = TInterface Name { namespace = "Gio" , name = "Drive" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDrive." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gio" , name = "Icon" })
-- throws : False
-- Skip return : False

foreign import ccall "g_drive_get_icon" g_drive_get_icon :: 
    Ptr Drive ->                            -- drive : TInterface (Name {namespace = "Gio", name = "Drive"})
    IO (Ptr Gio.Icon.Icon)

-- | Gets the icon for /@drive@/.
driveGetIcon ::
    (B.CallStack.HasCallStack, MonadIO m, IsDrive a) =>
    a
    -- ^ /@drive@/: a t'GI.Gio.Interfaces.Drive.Drive'.
    -> m Gio.Icon.Icon
    -- ^ __Returns:__ t'GI.Gio.Interfaces.Icon.Icon' for the /@drive@/.
    --    Free the returned object with 'GI.GObject.Objects.Object.objectUnref'.
driveGetIcon :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDrive a) =>
a -> m Icon
driveGetIcon a
drive = IO Icon -> m Icon
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Icon -> m Icon) -> IO Icon -> m Icon
forall a b. (a -> b) -> a -> b
$ do
    Ptr Drive
drive' <- a -> IO (Ptr Drive)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
drive
    Ptr Icon
result <- Ptr Drive -> IO (Ptr Icon)
g_drive_get_icon Ptr Drive
drive'
    Text -> Ptr Icon -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"driveGetIcon" Ptr Icon
result
    Icon
result' <- ((ManagedPtr Icon -> Icon) -> Ptr Icon -> IO Icon
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Icon -> Icon
Gio.Icon.Icon) Ptr Icon
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
drive
    Icon -> IO Icon
forall (m :: * -> *) a. Monad m => a -> m a
return Icon
result'

#if defined(ENABLE_OVERLOADING)
data DriveGetIconMethodInfo
instance (signature ~ (m Gio.Icon.Icon), MonadIO m, IsDrive a) => O.OverloadedMethod DriveGetIconMethodInfo a signature where
    overloadedMethod = driveGetIcon

instance O.OverloadedMethodInfo DriveGetIconMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Interfaces.Drive.driveGetIcon",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Interfaces-Drive.html#v:driveGetIcon"
        }


#endif

-- method Drive::get_identifier
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "drive"
--           , argType = TInterface Name { namespace = "Gio" , name = "Drive" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDrive" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "kind"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the kind of identifier to return"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "g_drive_get_identifier" g_drive_get_identifier :: 
    Ptr Drive ->                            -- drive : TInterface (Name {namespace = "Gio", name = "Drive"})
    CString ->                              -- kind : TBasicType TUTF8
    IO CString

-- | Gets the identifier of the given kind for /@drive@/. The only
-- identifier currently available is
-- 'GI.Gio.Constants.DRIVE_IDENTIFIER_KIND_UNIX_DEVICE'.
driveGetIdentifier ::
    (B.CallStack.HasCallStack, MonadIO m, IsDrive a) =>
    a
    -- ^ /@drive@/: a t'GI.Gio.Interfaces.Drive.Drive'
    -> T.Text
    -- ^ /@kind@/: the kind of identifier to return
    -> m (Maybe T.Text)
    -- ^ __Returns:__ a newly allocated string containing the
    --     requested identifier, or 'P.Nothing' if the t'GI.Gio.Interfaces.Drive.Drive'
    --     doesn\'t have this kind of identifier.
driveGetIdentifier :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDrive a) =>
a -> Text -> m (Maybe Text)
driveGetIdentifier a
drive Text
kind = IO (Maybe Text) -> m (Maybe Text)
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 Drive
drive' <- a -> IO (Ptr Drive)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
drive
    CString
kind' <- Text -> IO CString
textToCString Text
kind
    CString
result <- Ptr Drive -> CString -> IO CString
g_drive_get_identifier Ptr Drive
drive' CString
kind'
    Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
result' -> do
        Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result'
        Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
drive
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
kind'
    Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

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

instance O.OverloadedMethodInfo DriveGetIdentifierMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Interfaces.Drive.driveGetIdentifier",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Interfaces-Drive.html#v:driveGetIdentifier"
        }


#endif

-- method Drive::get_name
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "drive"
--           , argType = TInterface Name { namespace = "Gio" , name = "Drive" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDrive." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "g_drive_get_name" g_drive_get_name :: 
    Ptr Drive ->                            -- drive : TInterface (Name {namespace = "Gio", name = "Drive"})
    IO CString

-- | Gets the name of /@drive@/.
driveGetName ::
    (B.CallStack.HasCallStack, MonadIO m, IsDrive a) =>
    a
    -- ^ /@drive@/: a t'GI.Gio.Interfaces.Drive.Drive'.
    -> m T.Text
    -- ^ __Returns:__ a string containing /@drive@/\'s name. The returned
    --     string should be freed when no longer needed.
driveGetName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDrive a) =>
a -> m Text
driveGetName a
drive = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr Drive
drive' <- a -> IO (Ptr Drive)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
drive
    CString
result <- Ptr Drive -> IO CString
g_drive_get_name Ptr Drive
drive'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"driveGetName" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
drive
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data DriveGetNameMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsDrive a) => O.OverloadedMethod DriveGetNameMethodInfo a signature where
    overloadedMethod = driveGetName

instance O.OverloadedMethodInfo DriveGetNameMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Interfaces.Drive.driveGetName",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Interfaces-Drive.html#v:driveGetName"
        }


#endif

-- method Drive::get_sort_key
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "drive"
--           , argType = TInterface Name { namespace = "Gio" , name = "Drive" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GDrive." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "g_drive_get_sort_key" g_drive_get_sort_key :: 
    Ptr Drive ->                            -- drive : TInterface (Name {namespace = "Gio", name = "Drive"})
    IO CString

-- | Gets the sort key for /@drive@/, if any.
-- 
-- /Since: 2.32/
driveGetSortKey ::
    (B.CallStack.HasCallStack, MonadIO m, IsDrive a) =>
    a
    -- ^ /@drive@/: A t'GI.Gio.Interfaces.Drive.Drive'.
    -> m (Maybe T.Text)
    -- ^ __Returns:__ Sorting key for /@drive@/ or 'P.Nothing' if no such key is available.
driveGetSortKey :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDrive a) =>
a -> m (Maybe Text)
driveGetSortKey a
drive = IO (Maybe Text) -> m (Maybe Text)
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 Drive
drive' <- a -> IO (Ptr Drive)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
drive
    CString
result <- Ptr Drive -> IO CString
g_drive_get_sort_key Ptr Drive
drive'
    Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
result' -> do
        Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
drive
    Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

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

instance O.OverloadedMethodInfo DriveGetSortKeyMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Interfaces.Drive.driveGetSortKey",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Interfaces-Drive.html#v:driveGetSortKey"
        }


#endif

-- method Drive::get_start_stop_type
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "drive"
--           , argType = TInterface Name { namespace = "Gio" , name = "Drive" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDrive." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "Gio" , name = "DriveStartStopType" })
-- throws : False
-- Skip return : False

foreign import ccall "g_drive_get_start_stop_type" g_drive_get_start_stop_type :: 
    Ptr Drive ->                            -- drive : TInterface (Name {namespace = "Gio", name = "Drive"})
    IO CUInt

-- | Gets a hint about how a drive can be started\/stopped.
-- 
-- /Since: 2.22/
driveGetStartStopType ::
    (B.CallStack.HasCallStack, MonadIO m, IsDrive a) =>
    a
    -- ^ /@drive@/: a t'GI.Gio.Interfaces.Drive.Drive'.
    -> m Gio.Enums.DriveStartStopType
    -- ^ __Returns:__ A value from the t'GI.Gio.Enums.DriveStartStopType' enumeration.
driveGetStartStopType :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDrive a) =>
a -> m DriveStartStopType
driveGetStartStopType a
drive = IO DriveStartStopType -> m DriveStartStopType
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DriveStartStopType -> m DriveStartStopType)
-> IO DriveStartStopType -> m DriveStartStopType
forall a b. (a -> b) -> a -> b
$ do
    Ptr Drive
drive' <- a -> IO (Ptr Drive)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
drive
    CUInt
result <- Ptr Drive -> IO CUInt
g_drive_get_start_stop_type Ptr Drive
drive'
    let result' :: DriveStartStopType
result' = (Int -> DriveStartStopType
forall a. Enum a => Int -> a
toEnum (Int -> DriveStartStopType)
-> (CUInt -> Int) -> CUInt -> DriveStartStopType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
drive
    DriveStartStopType -> IO DriveStartStopType
forall (m :: * -> *) a. Monad m => a -> m a
return DriveStartStopType
result'

#if defined(ENABLE_OVERLOADING)
data DriveGetStartStopTypeMethodInfo
instance (signature ~ (m Gio.Enums.DriveStartStopType), MonadIO m, IsDrive a) => O.OverloadedMethod DriveGetStartStopTypeMethodInfo a signature where
    overloadedMethod = driveGetStartStopType

instance O.OverloadedMethodInfo DriveGetStartStopTypeMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Interfaces.Drive.driveGetStartStopType",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Interfaces-Drive.html#v:driveGetStartStopType"
        }


#endif

-- method Drive::get_symbolic_icon
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "drive"
--           , argType = TInterface Name { namespace = "Gio" , name = "Drive" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDrive." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gio" , name = "Icon" })
-- throws : False
-- Skip return : False

foreign import ccall "g_drive_get_symbolic_icon" g_drive_get_symbolic_icon :: 
    Ptr Drive ->                            -- drive : TInterface (Name {namespace = "Gio", name = "Drive"})
    IO (Ptr Gio.Icon.Icon)

-- | Gets the icon for /@drive@/.
-- 
-- /Since: 2.34/
driveGetSymbolicIcon ::
    (B.CallStack.HasCallStack, MonadIO m, IsDrive a) =>
    a
    -- ^ /@drive@/: a t'GI.Gio.Interfaces.Drive.Drive'.
    -> m Gio.Icon.Icon
    -- ^ __Returns:__ symbolic t'GI.Gio.Interfaces.Icon.Icon' for the /@drive@/.
    --    Free the returned object with 'GI.GObject.Objects.Object.objectUnref'.
driveGetSymbolicIcon :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDrive a) =>
a -> m Icon
driveGetSymbolicIcon a
drive = IO Icon -> m Icon
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Icon -> m Icon) -> IO Icon -> m Icon
forall a b. (a -> b) -> a -> b
$ do
    Ptr Drive
drive' <- a -> IO (Ptr Drive)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
drive
    Ptr Icon
result <- Ptr Drive -> IO (Ptr Icon)
g_drive_get_symbolic_icon Ptr Drive
drive'
    Text -> Ptr Icon -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"driveGetSymbolicIcon" Ptr Icon
result
    Icon
result' <- ((ManagedPtr Icon -> Icon) -> Ptr Icon -> IO Icon
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Icon -> Icon
Gio.Icon.Icon) Ptr Icon
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
drive
    Icon -> IO Icon
forall (m :: * -> *) a. Monad m => a -> m a
return Icon
result'

#if defined(ENABLE_OVERLOADING)
data DriveGetSymbolicIconMethodInfo
instance (signature ~ (m Gio.Icon.Icon), MonadIO m, IsDrive a) => O.OverloadedMethod DriveGetSymbolicIconMethodInfo a signature where
    overloadedMethod = driveGetSymbolicIcon

instance O.OverloadedMethodInfo DriveGetSymbolicIconMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Interfaces.Drive.driveGetSymbolicIcon",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Interfaces-Drive.html#v:driveGetSymbolicIcon"
        }


#endif

-- method Drive::get_volumes
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "drive"
--           , argType = TInterface Name { namespace = "Gio" , name = "Drive" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDrive." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TGList (TInterface Name { namespace = "Gio" , name = "Volume" }))
-- throws : False
-- Skip return : False

foreign import ccall "g_drive_get_volumes" g_drive_get_volumes :: 
    Ptr Drive ->                            -- drive : TInterface (Name {namespace = "Gio", name = "Drive"})
    IO (Ptr (GList (Ptr Gio.Volume.Volume)))

-- | Get a list of mountable volumes for /@drive@/.
-- 
-- The returned list should be freed with @/g_list_free()/@, after
-- its elements have been unreffed with 'GI.GObject.Objects.Object.objectUnref'.
driveGetVolumes ::
    (B.CallStack.HasCallStack, MonadIO m, IsDrive a) =>
    a
    -- ^ /@drive@/: a t'GI.Gio.Interfaces.Drive.Drive'.
    -> m [Gio.Volume.Volume]
    -- ^ __Returns:__ t'GI.GLib.Structs.List.List' containing any t'GI.Gio.Interfaces.Volume.Volume' objects on the given /@drive@/.
driveGetVolumes :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDrive a) =>
a -> m [Volume]
driveGetVolumes a
drive = IO [Volume] -> m [Volume]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Volume] -> m [Volume]) -> IO [Volume] -> m [Volume]
forall a b. (a -> b) -> a -> b
$ do
    Ptr Drive
drive' <- a -> IO (Ptr Drive)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
drive
    Ptr (GList (Ptr Volume))
result <- Ptr Drive -> IO (Ptr (GList (Ptr Volume)))
g_drive_get_volumes Ptr Drive
drive'
    [Ptr Volume]
result' <- Ptr (GList (Ptr Volume)) -> IO [Ptr Volume]
forall a. Ptr (GList (Ptr a)) -> IO [Ptr a]
unpackGList Ptr (GList (Ptr Volume))
result
    [Volume]
result'' <- (Ptr Volume -> IO Volume) -> [Ptr Volume] -> IO [Volume]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ((ManagedPtr Volume -> Volume) -> Ptr Volume -> IO Volume
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Volume -> Volume
Gio.Volume.Volume) [Ptr Volume]
result'
    Ptr (GList (Ptr Volume)) -> IO ()
forall a. Ptr (GList a) -> IO ()
g_list_free Ptr (GList (Ptr Volume))
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
drive
    [Volume] -> IO [Volume]
forall (m :: * -> *) a. Monad m => a -> m a
return [Volume]
result''

#if defined(ENABLE_OVERLOADING)
data DriveGetVolumesMethodInfo
instance (signature ~ (m [Gio.Volume.Volume]), MonadIO m, IsDrive a) => O.OverloadedMethod DriveGetVolumesMethodInfo a signature where
    overloadedMethod = driveGetVolumes

instance O.OverloadedMethodInfo DriveGetVolumesMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Interfaces.Drive.driveGetVolumes",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Interfaces-Drive.html#v:driveGetVolumes"
        }


#endif

-- method Drive::has_media
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "drive"
--           , argType = TInterface Name { namespace = "Gio" , name = "Drive" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDrive." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "g_drive_has_media" g_drive_has_media :: 
    Ptr Drive ->                            -- drive : TInterface (Name {namespace = "Gio", name = "Drive"})
    IO CInt

-- | Checks if the /@drive@/ has media. Note that the OS may not be polling
-- the drive for media changes; see 'GI.Gio.Interfaces.Drive.driveIsMediaCheckAutomatic'
-- for more details.
driveHasMedia ::
    (B.CallStack.HasCallStack, MonadIO m, IsDrive a) =>
    a
    -- ^ /@drive@/: a t'GI.Gio.Interfaces.Drive.Drive'.
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@drive@/ has media, 'P.False' otherwise.
driveHasMedia :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDrive a) =>
a -> m Bool
driveHasMedia a
drive = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Drive
drive' <- a -> IO (Ptr Drive)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
drive
    CInt
result <- Ptr Drive -> IO CInt
g_drive_has_media Ptr Drive
drive'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
drive
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data DriveHasMediaMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsDrive a) => O.OverloadedMethod DriveHasMediaMethodInfo a signature where
    overloadedMethod = driveHasMedia

instance O.OverloadedMethodInfo DriveHasMediaMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Interfaces.Drive.driveHasMedia",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Interfaces-Drive.html#v:driveHasMedia"
        }


#endif

-- method Drive::has_volumes
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "drive"
--           , argType = TInterface Name { namespace = "Gio" , name = "Drive" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDrive." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "g_drive_has_volumes" g_drive_has_volumes :: 
    Ptr Drive ->                            -- drive : TInterface (Name {namespace = "Gio", name = "Drive"})
    IO CInt

-- | Check if /@drive@/ has any mountable volumes.
driveHasVolumes ::
    (B.CallStack.HasCallStack, MonadIO m, IsDrive a) =>
    a
    -- ^ /@drive@/: a t'GI.Gio.Interfaces.Drive.Drive'.
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the /@drive@/ contains volumes, 'P.False' otherwise.
driveHasVolumes :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDrive a) =>
a -> m Bool
driveHasVolumes a
drive = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Drive
drive' <- a -> IO (Ptr Drive)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
drive
    CInt
result <- Ptr Drive -> IO CInt
g_drive_has_volumes Ptr Drive
drive'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
drive
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data DriveHasVolumesMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsDrive a) => O.OverloadedMethod DriveHasVolumesMethodInfo a signature where
    overloadedMethod = driveHasVolumes

instance O.OverloadedMethodInfo DriveHasVolumesMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Interfaces.Drive.driveHasVolumes",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Interfaces-Drive.html#v:driveHasVolumes"
        }


#endif

-- method Drive::is_media_check_automatic
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "drive"
--           , argType = TInterface Name { namespace = "Gio" , name = "Drive" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDrive." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "g_drive_is_media_check_automatic" g_drive_is_media_check_automatic :: 
    Ptr Drive ->                            -- drive : TInterface (Name {namespace = "Gio", name = "Drive"})
    IO CInt

-- | Checks if /@drive@/ is capable of automatically detecting media changes.
driveIsMediaCheckAutomatic ::
    (B.CallStack.HasCallStack, MonadIO m, IsDrive a) =>
    a
    -- ^ /@drive@/: a t'GI.Gio.Interfaces.Drive.Drive'.
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the /@drive@/ is capable of automatically detecting
    --     media changes, 'P.False' otherwise.
driveIsMediaCheckAutomatic :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDrive a) =>
a -> m Bool
driveIsMediaCheckAutomatic a
drive = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Drive
drive' <- a -> IO (Ptr Drive)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
drive
    CInt
result <- Ptr Drive -> IO CInt
g_drive_is_media_check_automatic Ptr Drive
drive'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
drive
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data DriveIsMediaCheckAutomaticMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsDrive a) => O.OverloadedMethod DriveIsMediaCheckAutomaticMethodInfo a signature where
    overloadedMethod = driveIsMediaCheckAutomatic

instance O.OverloadedMethodInfo DriveIsMediaCheckAutomaticMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Interfaces.Drive.driveIsMediaCheckAutomatic",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Interfaces-Drive.html#v:driveIsMediaCheckAutomatic"
        }


#endif

-- method Drive::is_media_removable
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "drive"
--           , argType = TInterface Name { namespace = "Gio" , name = "Drive" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDrive." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "g_drive_is_media_removable" g_drive_is_media_removable :: 
    Ptr Drive ->                            -- drive : TInterface (Name {namespace = "Gio", name = "Drive"})
    IO CInt

-- | Checks if the /@drive@/ supports removable media.
driveIsMediaRemovable ::
    (B.CallStack.HasCallStack, MonadIO m, IsDrive a) =>
    a
    -- ^ /@drive@/: a t'GI.Gio.Interfaces.Drive.Drive'.
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@drive@/ supports removable media, 'P.False' otherwise.
driveIsMediaRemovable :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDrive a) =>
a -> m Bool
driveIsMediaRemovable a
drive = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Drive
drive' <- a -> IO (Ptr Drive)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
drive
    CInt
result <- Ptr Drive -> IO CInt
g_drive_is_media_removable Ptr Drive
drive'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
drive
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data DriveIsMediaRemovableMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsDrive a) => O.OverloadedMethod DriveIsMediaRemovableMethodInfo a signature where
    overloadedMethod = driveIsMediaRemovable

instance O.OverloadedMethodInfo DriveIsMediaRemovableMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Interfaces.Drive.driveIsMediaRemovable",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Interfaces-Drive.html#v:driveIsMediaRemovable"
        }


#endif

-- method Drive::is_removable
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "drive"
--           , argType = TInterface Name { namespace = "Gio" , name = "Drive" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDrive." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "g_drive_is_removable" g_drive_is_removable :: 
    Ptr Drive ->                            -- drive : TInterface (Name {namespace = "Gio", name = "Drive"})
    IO CInt

-- | Checks if the t'GI.Gio.Interfaces.Drive.Drive' and\/or its media is considered removable by the user.
-- See 'GI.Gio.Interfaces.Drive.driveIsMediaRemovable'.
-- 
-- /Since: 2.50/
driveIsRemovable ::
    (B.CallStack.HasCallStack, MonadIO m, IsDrive a) =>
    a
    -- ^ /@drive@/: a t'GI.Gio.Interfaces.Drive.Drive'.
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@drive@/ and\/or its media is considered removable, 'P.False' otherwise.
driveIsRemovable :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDrive a) =>
a -> m Bool
driveIsRemovable a
drive = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Drive
drive' <- a -> IO (Ptr Drive)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
drive
    CInt
result <- Ptr Drive -> IO CInt
g_drive_is_removable Ptr Drive
drive'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
drive
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data DriveIsRemovableMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsDrive a) => O.OverloadedMethod DriveIsRemovableMethodInfo a signature where
    overloadedMethod = driveIsRemovable

instance O.OverloadedMethodInfo DriveIsRemovableMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Interfaces.Drive.driveIsRemovable",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Interfaces-Drive.html#v:driveIsRemovable"
        }


#endif

-- method Drive::poll_for_media
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "drive"
--           , argType = TInterface Name { namespace = "Gio" , name = "Drive" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDrive." , 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 "optional #GCancellable object, %NULL to ignore."
--                 , 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 #GAsyncReadyCallback, or %NULL."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = 3
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "user 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 "g_drive_poll_for_media" g_drive_poll_for_media :: 
    Ptr Drive ->                            -- drive : TInterface (Name {namespace = "Gio", name = "Drive"})
    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 ()

-- | Asynchronously polls /@drive@/ to see if media has been inserted or removed.
-- 
-- When the operation is finished, /@callback@/ will be called.
-- You can then call 'GI.Gio.Interfaces.Drive.drivePollForMediaFinish' to obtain the
-- result of the operation.
drivePollForMedia ::
    (B.CallStack.HasCallStack, MonadIO m, IsDrive a, Gio.Cancellable.IsCancellable b) =>
    a
    -- ^ /@drive@/: a t'GI.Gio.Interfaces.Drive.Drive'.
    -> Maybe (b)
    -- ^ /@cancellable@/: optional t'GI.Gio.Objects.Cancellable.Cancellable' object, 'P.Nothing' to ignore.
    -> Maybe (Gio.Callbacks.AsyncReadyCallback)
    -- ^ /@callback@/: a t'GI.Gio.Callbacks.AsyncReadyCallback', or 'P.Nothing'.
    -> m ()
drivePollForMedia :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDrive a, IsCancellable b) =>
a -> Maybe b -> Maybe AsyncReadyCallback -> m ()
drivePollForMedia a
drive Maybe b
cancellable Maybe AsyncReadyCallback
callback = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Drive
drive' <- a -> IO (Ptr Drive)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
drive
    Ptr Cancellable
maybeCancellable <- case Maybe b
cancellable of
        Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
        Just b
jCancellable -> do
            Ptr Cancellable
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
            Ptr Cancellable -> IO (Ptr Cancellable)
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 (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 (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 Drive
-> Ptr Cancellable
-> FunPtr C_AsyncReadyCallback
-> Ptr ()
-> IO ()
g_drive_poll_for_media Ptr Drive
drive' Ptr Cancellable
maybeCancellable FunPtr C_AsyncReadyCallback
maybeCallback Ptr ()
forall a. Ptr a
userData
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
drive
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
cancellable b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DrivePollForMediaMethodInfo
instance (signature ~ (Maybe (b) -> Maybe (Gio.Callbacks.AsyncReadyCallback) -> m ()), MonadIO m, IsDrive a, Gio.Cancellable.IsCancellable b) => O.OverloadedMethod DrivePollForMediaMethodInfo a signature where
    overloadedMethod = drivePollForMedia

instance O.OverloadedMethodInfo DrivePollForMediaMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Interfaces.Drive.drivePollForMedia",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Interfaces-Drive.html#v:drivePollForMedia"
        }


#endif

-- method Drive::poll_for_media_finish
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "drive"
--           , argType = TInterface Name { namespace = "Gio" , name = "Drive" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDrive." , 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 "g_drive_poll_for_media_finish" g_drive_poll_for_media_finish :: 
    Ptr Drive ->                            -- drive : TInterface (Name {namespace = "Gio", name = "Drive"})
    Ptr Gio.AsyncResult.AsyncResult ->      -- result : TInterface (Name {namespace = "Gio", name = "AsyncResult"})
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Finishes an operation started with 'GI.Gio.Interfaces.Drive.drivePollForMedia' on a drive.
drivePollForMediaFinish ::
    (B.CallStack.HasCallStack, MonadIO m, IsDrive a, Gio.AsyncResult.IsAsyncResult b) =>
    a
    -- ^ /@drive@/: a t'GI.Gio.Interfaces.Drive.Drive'.
    -> b
    -- ^ /@result@/: a t'GI.Gio.Interfaces.AsyncResult.AsyncResult'.
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
drivePollForMediaFinish :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDrive a, IsAsyncResult b) =>
a -> b -> m ()
drivePollForMediaFinish a
drive b
result_ = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Drive
drive' <- a -> IO (Ptr Drive)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
drive
    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 Drive -> Ptr AsyncResult -> Ptr (Ptr GError) -> IO CInt
g_drive_poll_for_media_finish Ptr Drive
drive' Ptr AsyncResult
result_'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
drive
        b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
result_
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

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

instance O.OverloadedMethodInfo DrivePollForMediaFinishMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Interfaces.Drive.drivePollForMediaFinish",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Interfaces-Drive.html#v:drivePollForMediaFinish"
        }


#endif

-- method Drive::start
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "drive"
--           , argType = TInterface Name { namespace = "Gio" , name = "Drive" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDrive." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DriveStartFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "flags affecting the start operation."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "mount_operation"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "MountOperation" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #GMountOperation or %NULL to avoid\n    user interaction."
--                 , 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 "optional #GCancellable object, %NULL to ignore."
--                 , 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 #GAsyncReadyCallback, or %NULL."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = 5
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "user 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 "g_drive_start" g_drive_start :: 
    Ptr Drive ->                            -- drive : TInterface (Name {namespace = "Gio", name = "Drive"})
    CUInt ->                                -- flags : TInterface (Name {namespace = "Gio", name = "DriveStartFlags"})
    Ptr Gio.MountOperation.MountOperation -> -- mount_operation : TInterface (Name {namespace = "Gio", name = "MountOperation"})
    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 ()

-- | Asynchronously starts a drive.
-- 
-- When the operation is finished, /@callback@/ will be called.
-- You can then call 'GI.Gio.Interfaces.Drive.driveStartFinish' to obtain the
-- result of the operation.
-- 
-- /Since: 2.22/
driveStart ::
    (B.CallStack.HasCallStack, MonadIO m, IsDrive a, Gio.MountOperation.IsMountOperation b, Gio.Cancellable.IsCancellable c) =>
    a
    -- ^ /@drive@/: a t'GI.Gio.Interfaces.Drive.Drive'.
    -> [Gio.Flags.DriveStartFlags]
    -- ^ /@flags@/: flags affecting the start operation.
    -> Maybe (b)
    -- ^ /@mountOperation@/: a t'GI.Gio.Objects.MountOperation.MountOperation' or 'P.Nothing' to avoid
    --     user interaction.
    -> Maybe (c)
    -- ^ /@cancellable@/: optional t'GI.Gio.Objects.Cancellable.Cancellable' object, 'P.Nothing' to ignore.
    -> Maybe (Gio.Callbacks.AsyncReadyCallback)
    -- ^ /@callback@/: a t'GI.Gio.Callbacks.AsyncReadyCallback', or 'P.Nothing'.
    -> m ()
driveStart :: forall (m :: * -> *) a b c.
(HasCallStack, MonadIO m, IsDrive a, IsMountOperation b,
 IsCancellable c) =>
a
-> [DriveStartFlags]
-> Maybe b
-> Maybe c
-> Maybe AsyncReadyCallback
-> m ()
driveStart a
drive [DriveStartFlags]
flags Maybe b
mountOperation Maybe c
cancellable Maybe AsyncReadyCallback
callback = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Drive
drive' <- a -> IO (Ptr Drive)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
drive
    let flags' :: CUInt
flags' = [DriveStartFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [DriveStartFlags]
flags
    Ptr MountOperation
maybeMountOperation <- case Maybe b
mountOperation of
        Maybe b
Nothing -> Ptr MountOperation -> IO (Ptr MountOperation)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr MountOperation
forall a. Ptr a
nullPtr
        Just b
jMountOperation -> do
            Ptr MountOperation
jMountOperation' <- b -> IO (Ptr MountOperation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jMountOperation
            Ptr MountOperation -> IO (Ptr MountOperation)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr MountOperation
jMountOperation'
    Ptr Cancellable
maybeCancellable <- case Maybe c
cancellable of
        Maybe c
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
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 (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 (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 (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 Drive
-> CUInt
-> Ptr MountOperation
-> Ptr Cancellable
-> FunPtr C_AsyncReadyCallback
-> Ptr ()
-> IO ()
g_drive_start Ptr Drive
drive' CUInt
flags' Ptr MountOperation
maybeMountOperation Ptr Cancellable
maybeCancellable FunPtr C_AsyncReadyCallback
maybeCallback Ptr ()
forall a. Ptr a
userData
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
drive
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
mountOperation 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 (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DriveStartMethodInfo
instance (signature ~ ([Gio.Flags.DriveStartFlags] -> Maybe (b) -> Maybe (c) -> Maybe (Gio.Callbacks.AsyncReadyCallback) -> m ()), MonadIO m, IsDrive a, Gio.MountOperation.IsMountOperation b, Gio.Cancellable.IsCancellable c) => O.OverloadedMethod DriveStartMethodInfo a signature where
    overloadedMethod = driveStart

instance O.OverloadedMethodInfo DriveStartMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Interfaces.Drive.driveStart",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Interfaces-Drive.html#v:driveStart"
        }


#endif

-- method Drive::start_finish
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "drive"
--           , argType = TInterface Name { namespace = "Gio" , name = "Drive" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDrive." , 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 "g_drive_start_finish" g_drive_start_finish :: 
    Ptr Drive ->                            -- drive : TInterface (Name {namespace = "Gio", name = "Drive"})
    Ptr Gio.AsyncResult.AsyncResult ->      -- result : TInterface (Name {namespace = "Gio", name = "AsyncResult"})
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Finishes starting a drive.
-- 
-- /Since: 2.22/
driveStartFinish ::
    (B.CallStack.HasCallStack, MonadIO m, IsDrive a, Gio.AsyncResult.IsAsyncResult b) =>
    a
    -- ^ /@drive@/: a t'GI.Gio.Interfaces.Drive.Drive'.
    -> b
    -- ^ /@result@/: a t'GI.Gio.Interfaces.AsyncResult.AsyncResult'.
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
driveStartFinish :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDrive a, IsAsyncResult b) =>
a -> b -> m ()
driveStartFinish a
drive b
result_ = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Drive
drive' <- a -> IO (Ptr Drive)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
drive
    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 Drive -> Ptr AsyncResult -> Ptr (Ptr GError) -> IO CInt
g_drive_start_finish Ptr Drive
drive' Ptr AsyncResult
result_'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
drive
        b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
result_
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

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

instance O.OverloadedMethodInfo DriveStartFinishMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Interfaces.Drive.driveStartFinish",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Interfaces-Drive.html#v:driveStartFinish"
        }


#endif

-- method Drive::stop
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "drive"
--           , argType = TInterface Name { namespace = "Gio" , name = "Drive" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDrive." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "MountUnmountFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "flags affecting the unmount if required for stopping."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "mount_operation"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "MountOperation" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #GMountOperation or %NULL to avoid\n    user interaction."
--                 , 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 "optional #GCancellable object, %NULL to ignore."
--                 , 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 #GAsyncReadyCallback, or %NULL."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = 5
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "user 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 "g_drive_stop" g_drive_stop :: 
    Ptr Drive ->                            -- drive : TInterface (Name {namespace = "Gio", name = "Drive"})
    CUInt ->                                -- flags : TInterface (Name {namespace = "Gio", name = "MountUnmountFlags"})
    Ptr Gio.MountOperation.MountOperation -> -- mount_operation : TInterface (Name {namespace = "Gio", name = "MountOperation"})
    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 ()

-- | Asynchronously stops a drive.
-- 
-- When the operation is finished, /@callback@/ will be called.
-- You can then call 'GI.Gio.Interfaces.Drive.driveStopFinish' to obtain the
-- result of the operation.
-- 
-- /Since: 2.22/
driveStop ::
    (B.CallStack.HasCallStack, MonadIO m, IsDrive a, Gio.MountOperation.IsMountOperation b, Gio.Cancellable.IsCancellable c) =>
    a
    -- ^ /@drive@/: a t'GI.Gio.Interfaces.Drive.Drive'.
    -> [Gio.Flags.MountUnmountFlags]
    -- ^ /@flags@/: flags affecting the unmount if required for stopping.
    -> Maybe (b)
    -- ^ /@mountOperation@/: a t'GI.Gio.Objects.MountOperation.MountOperation' or 'P.Nothing' to avoid
    --     user interaction.
    -> Maybe (c)
    -- ^ /@cancellable@/: optional t'GI.Gio.Objects.Cancellable.Cancellable' object, 'P.Nothing' to ignore.
    -> Maybe (Gio.Callbacks.AsyncReadyCallback)
    -- ^ /@callback@/: a t'GI.Gio.Callbacks.AsyncReadyCallback', or 'P.Nothing'.
    -> m ()
driveStop :: forall (m :: * -> *) a b c.
(HasCallStack, MonadIO m, IsDrive a, IsMountOperation b,
 IsCancellable c) =>
a
-> [MountUnmountFlags]
-> Maybe b
-> Maybe c
-> Maybe AsyncReadyCallback
-> m ()
driveStop a
drive [MountUnmountFlags]
flags Maybe b
mountOperation Maybe c
cancellable Maybe AsyncReadyCallback
callback = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Drive
drive' <- a -> IO (Ptr Drive)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
drive
    let flags' :: CUInt
flags' = [MountUnmountFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [MountUnmountFlags]
flags
    Ptr MountOperation
maybeMountOperation <- case Maybe b
mountOperation of
        Maybe b
Nothing -> Ptr MountOperation -> IO (Ptr MountOperation)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr MountOperation
forall a. Ptr a
nullPtr
        Just b
jMountOperation -> do
            Ptr MountOperation
jMountOperation' <- b -> IO (Ptr MountOperation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jMountOperation
            Ptr MountOperation -> IO (Ptr MountOperation)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr MountOperation
jMountOperation'
    Ptr Cancellable
maybeCancellable <- case Maybe c
cancellable of
        Maybe c
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
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 (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 (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 (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 Drive
-> CUInt
-> Ptr MountOperation
-> Ptr Cancellable
-> FunPtr C_AsyncReadyCallback
-> Ptr ()
-> IO ()
g_drive_stop Ptr Drive
drive' CUInt
flags' Ptr MountOperation
maybeMountOperation Ptr Cancellable
maybeCancellable FunPtr C_AsyncReadyCallback
maybeCallback Ptr ()
forall a. Ptr a
userData
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
drive
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
mountOperation 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 (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DriveStopMethodInfo
instance (signature ~ ([Gio.Flags.MountUnmountFlags] -> Maybe (b) -> Maybe (c) -> Maybe (Gio.Callbacks.AsyncReadyCallback) -> m ()), MonadIO m, IsDrive a, Gio.MountOperation.IsMountOperation b, Gio.Cancellable.IsCancellable c) => O.OverloadedMethod DriveStopMethodInfo a signature where
    overloadedMethod = driveStop

instance O.OverloadedMethodInfo DriveStopMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Interfaces.Drive.driveStop",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Interfaces-Drive.html#v:driveStop"
        }


#endif

-- method Drive::stop_finish
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "drive"
--           , argType = TInterface Name { namespace = "Gio" , name = "Drive" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDrive." , 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 "g_drive_stop_finish" g_drive_stop_finish :: 
    Ptr Drive ->                            -- drive : TInterface (Name {namespace = "Gio", name = "Drive"})
    Ptr Gio.AsyncResult.AsyncResult ->      -- result : TInterface (Name {namespace = "Gio", name = "AsyncResult"})
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Finishes stopping a drive.
-- 
-- /Since: 2.22/
driveStopFinish ::
    (B.CallStack.HasCallStack, MonadIO m, IsDrive a, Gio.AsyncResult.IsAsyncResult b) =>
    a
    -- ^ /@drive@/: a t'GI.Gio.Interfaces.Drive.Drive'.
    -> b
    -- ^ /@result@/: a t'GI.Gio.Interfaces.AsyncResult.AsyncResult'.
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
driveStopFinish :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDrive a, IsAsyncResult b) =>
a -> b -> m ()
driveStopFinish a
drive b
result_ = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Drive
drive' <- a -> IO (Ptr Drive)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
drive
    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 Drive -> Ptr AsyncResult -> Ptr (Ptr GError) -> IO CInt
g_drive_stop_finish Ptr Drive
drive' Ptr AsyncResult
result_'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
drive
        b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
result_
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

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

instance O.OverloadedMethodInfo DriveStopFinishMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Interfaces.Drive.driveStopFinish",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Interfaces-Drive.html#v:driveStopFinish"
        }


#endif

-- signal Drive::changed
-- | Emitted when the drive\'s state has changed.
type DriveChangedCallback =
    IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `DriveChangedCallback`@.
noDriveChangedCallback :: Maybe DriveChangedCallback
noDriveChangedCallback :: Maybe (IO ())
noDriveChangedCallback = Maybe (IO ())
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_DriveChangedCallback =
    Ptr () ->                               -- object
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_DriveChangedCallback`.
foreign import ccall "wrapper"
    mk_DriveChangedCallback :: C_DriveChangedCallback -> IO (FunPtr C_DriveChangedCallback)

-- | Wrap the callback into a `GClosure`.
genClosure_DriveChanged :: MonadIO m => DriveChangedCallback -> m (GClosure C_DriveChangedCallback)
genClosure_DriveChanged :: forall (m :: * -> *).
MonadIO m =>
IO () -> m (GClosure C_DriveChangedCallback)
genClosure_DriveChanged IO ()
cb = IO (GClosure C_DriveChangedCallback)
-> m (GClosure C_DriveChangedCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_DriveChangedCallback)
 -> m (GClosure C_DriveChangedCallback))
-> IO (GClosure C_DriveChangedCallback)
-> m (GClosure C_DriveChangedCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_DriveChangedCallback
cb' = IO () -> C_DriveChangedCallback
wrap_DriveChangedCallback IO ()
cb
    C_DriveChangedCallback -> IO (FunPtr C_DriveChangedCallback)
mk_DriveChangedCallback C_DriveChangedCallback
cb' IO (FunPtr C_DriveChangedCallback)
-> (FunPtr C_DriveChangedCallback
    -> IO (GClosure C_DriveChangedCallback))
-> IO (GClosure C_DriveChangedCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_DriveChangedCallback
-> IO (GClosure C_DriveChangedCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `DriveChangedCallback` into a `C_DriveChangedCallback`.
wrap_DriveChangedCallback ::
    DriveChangedCallback ->
    C_DriveChangedCallback
wrap_DriveChangedCallback :: IO () -> C_DriveChangedCallback
wrap_DriveChangedCallback IO ()
_cb Ptr ()
_ Ptr ()
_ = do
    IO ()
_cb 


-- | Connect a signal handler for the [changed](#signal:changed) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' drive #changed callback
-- @
-- 
-- 
onDriveChanged :: (IsDrive a, MonadIO m) => a -> DriveChangedCallback -> m SignalHandlerId
onDriveChanged :: forall a (m :: * -> *).
(IsDrive a, MonadIO m) =>
a -> IO () -> m SignalHandlerId
onDriveChanged a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_DriveChangedCallback
cb' = IO () -> C_DriveChangedCallback
wrap_DriveChangedCallback IO ()
cb
    FunPtr C_DriveChangedCallback
cb'' <- C_DriveChangedCallback -> IO (FunPtr C_DriveChangedCallback)
mk_DriveChangedCallback C_DriveChangedCallback
cb'
    a
-> Text
-> FunPtr C_DriveChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"changed" FunPtr C_DriveChangedCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [changed](#signal:changed) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' drive #changed callback
-- @
-- 
-- 
afterDriveChanged :: (IsDrive a, MonadIO m) => a -> DriveChangedCallback -> m SignalHandlerId
afterDriveChanged :: forall a (m :: * -> *).
(IsDrive a, MonadIO m) =>
a -> IO () -> m SignalHandlerId
afterDriveChanged a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_DriveChangedCallback
cb' = IO () -> C_DriveChangedCallback
wrap_DriveChangedCallback IO ()
cb
    FunPtr C_DriveChangedCallback
cb'' <- C_DriveChangedCallback -> IO (FunPtr C_DriveChangedCallback)
mk_DriveChangedCallback C_DriveChangedCallback
cb'
    a
-> Text
-> FunPtr C_DriveChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"changed" FunPtr C_DriveChangedCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data DriveChangedSignalInfo
instance SignalInfo DriveChangedSignalInfo where
    type HaskellCallbackType DriveChangedSignalInfo = DriveChangedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_DriveChangedCallback cb
        cb'' <- mk_DriveChangedCallback cb'
        connectSignalFunPtr obj "changed" cb'' connectMode detail

#endif

-- signal Drive::disconnected
-- | This signal is emitted when the t'GI.Gio.Interfaces.Drive.Drive' have been
-- disconnected. If the recipient is holding references to the
-- object they should release them so the object can be
-- finalized.
type DriveDisconnectedCallback =
    IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `DriveDisconnectedCallback`@.
noDriveDisconnectedCallback :: Maybe DriveDisconnectedCallback
noDriveDisconnectedCallback :: Maybe (IO ())
noDriveDisconnectedCallback = Maybe (IO ())
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_DriveDisconnectedCallback =
    Ptr () ->                               -- object
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_DriveDisconnectedCallback`.
foreign import ccall "wrapper"
    mk_DriveDisconnectedCallback :: C_DriveDisconnectedCallback -> IO (FunPtr C_DriveDisconnectedCallback)

-- | Wrap the callback into a `GClosure`.
genClosure_DriveDisconnected :: MonadIO m => DriveDisconnectedCallback -> m (GClosure C_DriveDisconnectedCallback)
genClosure_DriveDisconnected :: forall (m :: * -> *).
MonadIO m =>
IO () -> m (GClosure C_DriveChangedCallback)
genClosure_DriveDisconnected IO ()
cb = IO (GClosure C_DriveChangedCallback)
-> m (GClosure C_DriveChangedCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_DriveChangedCallback)
 -> m (GClosure C_DriveChangedCallback))
-> IO (GClosure C_DriveChangedCallback)
-> m (GClosure C_DriveChangedCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_DriveChangedCallback
cb' = IO () -> C_DriveChangedCallback
wrap_DriveDisconnectedCallback IO ()
cb
    C_DriveChangedCallback -> IO (FunPtr C_DriveChangedCallback)
mk_DriveDisconnectedCallback C_DriveChangedCallback
cb' IO (FunPtr C_DriveChangedCallback)
-> (FunPtr C_DriveChangedCallback
    -> IO (GClosure C_DriveChangedCallback))
-> IO (GClosure C_DriveChangedCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_DriveChangedCallback
-> IO (GClosure C_DriveChangedCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `DriveDisconnectedCallback` into a `C_DriveDisconnectedCallback`.
wrap_DriveDisconnectedCallback ::
    DriveDisconnectedCallback ->
    C_DriveDisconnectedCallback
wrap_DriveDisconnectedCallback :: IO () -> C_DriveChangedCallback
wrap_DriveDisconnectedCallback IO ()
_cb Ptr ()
_ Ptr ()
_ = do
    IO ()
_cb 


-- | Connect a signal handler for the [disconnected](#signal:disconnected) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' drive #disconnected callback
-- @
-- 
-- 
onDriveDisconnected :: (IsDrive a, MonadIO m) => a -> DriveDisconnectedCallback -> m SignalHandlerId
onDriveDisconnected :: forall a (m :: * -> *).
(IsDrive a, MonadIO m) =>
a -> IO () -> m SignalHandlerId
onDriveDisconnected a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_DriveChangedCallback
cb' = IO () -> C_DriveChangedCallback
wrap_DriveDisconnectedCallback IO ()
cb
    FunPtr C_DriveChangedCallback
cb'' <- C_DriveChangedCallback -> IO (FunPtr C_DriveChangedCallback)
mk_DriveDisconnectedCallback C_DriveChangedCallback
cb'
    a
-> Text
-> FunPtr C_DriveChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"disconnected" FunPtr C_DriveChangedCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [disconnected](#signal:disconnected) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' drive #disconnected callback
-- @
-- 
-- 
afterDriveDisconnected :: (IsDrive a, MonadIO m) => a -> DriveDisconnectedCallback -> m SignalHandlerId
afterDriveDisconnected :: forall a (m :: * -> *).
(IsDrive a, MonadIO m) =>
a -> IO () -> m SignalHandlerId
afterDriveDisconnected a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_DriveChangedCallback
cb' = IO () -> C_DriveChangedCallback
wrap_DriveDisconnectedCallback IO ()
cb
    FunPtr C_DriveChangedCallback
cb'' <- C_DriveChangedCallback -> IO (FunPtr C_DriveChangedCallback)
mk_DriveDisconnectedCallback C_DriveChangedCallback
cb'
    a
-> Text
-> FunPtr C_DriveChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"disconnected" FunPtr C_DriveChangedCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data DriveDisconnectedSignalInfo
instance SignalInfo DriveDisconnectedSignalInfo where
    type HaskellCallbackType DriveDisconnectedSignalInfo = DriveDisconnectedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_DriveDisconnectedCallback cb
        cb'' <- mk_DriveDisconnectedCallback cb'
        connectSignalFunPtr obj "disconnected" cb'' connectMode detail

#endif

-- signal Drive::eject-button
-- | Emitted when the physical eject button (if any) of a drive has
-- been pressed.
type DriveEjectButtonCallback =
    IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `DriveEjectButtonCallback`@.
noDriveEjectButtonCallback :: Maybe DriveEjectButtonCallback
noDriveEjectButtonCallback :: Maybe (IO ())
noDriveEjectButtonCallback = Maybe (IO ())
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_DriveEjectButtonCallback =
    Ptr () ->                               -- object
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_DriveEjectButtonCallback`.
foreign import ccall "wrapper"
    mk_DriveEjectButtonCallback :: C_DriveEjectButtonCallback -> IO (FunPtr C_DriveEjectButtonCallback)

-- | Wrap the callback into a `GClosure`.
genClosure_DriveEjectButton :: MonadIO m => DriveEjectButtonCallback -> m (GClosure C_DriveEjectButtonCallback)
genClosure_DriveEjectButton :: forall (m :: * -> *).
MonadIO m =>
IO () -> m (GClosure C_DriveChangedCallback)
genClosure_DriveEjectButton IO ()
cb = IO (GClosure C_DriveChangedCallback)
-> m (GClosure C_DriveChangedCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_DriveChangedCallback)
 -> m (GClosure C_DriveChangedCallback))
-> IO (GClosure C_DriveChangedCallback)
-> m (GClosure C_DriveChangedCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_DriveChangedCallback
cb' = IO () -> C_DriveChangedCallback
wrap_DriveEjectButtonCallback IO ()
cb
    C_DriveChangedCallback -> IO (FunPtr C_DriveChangedCallback)
mk_DriveEjectButtonCallback C_DriveChangedCallback
cb' IO (FunPtr C_DriveChangedCallback)
-> (FunPtr C_DriveChangedCallback
    -> IO (GClosure C_DriveChangedCallback))
-> IO (GClosure C_DriveChangedCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_DriveChangedCallback
-> IO (GClosure C_DriveChangedCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `DriveEjectButtonCallback` into a `C_DriveEjectButtonCallback`.
wrap_DriveEjectButtonCallback ::
    DriveEjectButtonCallback ->
    C_DriveEjectButtonCallback
wrap_DriveEjectButtonCallback :: IO () -> C_DriveChangedCallback
wrap_DriveEjectButtonCallback IO ()
_cb Ptr ()
_ Ptr ()
_ = do
    IO ()
_cb 


-- | Connect a signal handler for the [ejectButton](#signal:ejectButton) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' drive #ejectButton callback
-- @
-- 
-- 
onDriveEjectButton :: (IsDrive a, MonadIO m) => a -> DriveEjectButtonCallback -> m SignalHandlerId
onDriveEjectButton :: forall a (m :: * -> *).
(IsDrive a, MonadIO m) =>
a -> IO () -> m SignalHandlerId
onDriveEjectButton a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_DriveChangedCallback
cb' = IO () -> C_DriveChangedCallback
wrap_DriveEjectButtonCallback IO ()
cb
    FunPtr C_DriveChangedCallback
cb'' <- C_DriveChangedCallback -> IO (FunPtr C_DriveChangedCallback)
mk_DriveEjectButtonCallback C_DriveChangedCallback
cb'
    a
-> Text
-> FunPtr C_DriveChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"eject-button" FunPtr C_DriveChangedCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [ejectButton](#signal:ejectButton) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' drive #ejectButton callback
-- @
-- 
-- 
afterDriveEjectButton :: (IsDrive a, MonadIO m) => a -> DriveEjectButtonCallback -> m SignalHandlerId
afterDriveEjectButton :: forall a (m :: * -> *).
(IsDrive a, MonadIO m) =>
a -> IO () -> m SignalHandlerId
afterDriveEjectButton a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_DriveChangedCallback
cb' = IO () -> C_DriveChangedCallback
wrap_DriveEjectButtonCallback IO ()
cb
    FunPtr C_DriveChangedCallback
cb'' <- C_DriveChangedCallback -> IO (FunPtr C_DriveChangedCallback)
mk_DriveEjectButtonCallback C_DriveChangedCallback
cb'
    a
-> Text
-> FunPtr C_DriveChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"eject-button" FunPtr C_DriveChangedCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data DriveEjectButtonSignalInfo
instance SignalInfo DriveEjectButtonSignalInfo where
    type HaskellCallbackType DriveEjectButtonSignalInfo = DriveEjectButtonCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_DriveEjectButtonCallback cb
        cb'' <- mk_DriveEjectButtonCallback cb'
        connectSignalFunPtr obj "eject-button" cb'' connectMode detail

#endif

-- signal Drive::stop-button
-- | Emitted when the physical stop button (if any) of a drive has
-- been pressed.
-- 
-- /Since: 2.22/
type DriveStopButtonCallback =
    IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `DriveStopButtonCallback`@.
noDriveStopButtonCallback :: Maybe DriveStopButtonCallback
noDriveStopButtonCallback :: Maybe (IO ())
noDriveStopButtonCallback = Maybe (IO ())
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_DriveStopButtonCallback =
    Ptr () ->                               -- object
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_DriveStopButtonCallback`.
foreign import ccall "wrapper"
    mk_DriveStopButtonCallback :: C_DriveStopButtonCallback -> IO (FunPtr C_DriveStopButtonCallback)

-- | Wrap the callback into a `GClosure`.
genClosure_DriveStopButton :: MonadIO m => DriveStopButtonCallback -> m (GClosure C_DriveStopButtonCallback)
genClosure_DriveStopButton :: forall (m :: * -> *).
MonadIO m =>
IO () -> m (GClosure C_DriveChangedCallback)
genClosure_DriveStopButton IO ()
cb = IO (GClosure C_DriveChangedCallback)
-> m (GClosure C_DriveChangedCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_DriveChangedCallback)
 -> m (GClosure C_DriveChangedCallback))
-> IO (GClosure C_DriveChangedCallback)
-> m (GClosure C_DriveChangedCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_DriveChangedCallback
cb' = IO () -> C_DriveChangedCallback
wrap_DriveStopButtonCallback IO ()
cb
    C_DriveChangedCallback -> IO (FunPtr C_DriveChangedCallback)
mk_DriveStopButtonCallback C_DriveChangedCallback
cb' IO (FunPtr C_DriveChangedCallback)
-> (FunPtr C_DriveChangedCallback
    -> IO (GClosure C_DriveChangedCallback))
-> IO (GClosure C_DriveChangedCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_DriveChangedCallback
-> IO (GClosure C_DriveChangedCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `DriveStopButtonCallback` into a `C_DriveStopButtonCallback`.
wrap_DriveStopButtonCallback ::
    DriveStopButtonCallback ->
    C_DriveStopButtonCallback
wrap_DriveStopButtonCallback :: IO () -> C_DriveChangedCallback
wrap_DriveStopButtonCallback IO ()
_cb Ptr ()
_ Ptr ()
_ = do
    IO ()
_cb 


-- | Connect a signal handler for the [stopButton](#signal:stopButton) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' drive #stopButton callback
-- @
-- 
-- 
onDriveStopButton :: (IsDrive a, MonadIO m) => a -> DriveStopButtonCallback -> m SignalHandlerId
onDriveStopButton :: forall a (m :: * -> *).
(IsDrive a, MonadIO m) =>
a -> IO () -> m SignalHandlerId
onDriveStopButton a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_DriveChangedCallback
cb' = IO () -> C_DriveChangedCallback
wrap_DriveStopButtonCallback IO ()
cb
    FunPtr C_DriveChangedCallback
cb'' <- C_DriveChangedCallback -> IO (FunPtr C_DriveChangedCallback)
mk_DriveStopButtonCallback C_DriveChangedCallback
cb'
    a
-> Text
-> FunPtr C_DriveChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"stop-button" FunPtr C_DriveChangedCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [stopButton](#signal:stopButton) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' drive #stopButton callback
-- @
-- 
-- 
afterDriveStopButton :: (IsDrive a, MonadIO m) => a -> DriveStopButtonCallback -> m SignalHandlerId
afterDriveStopButton :: forall a (m :: * -> *).
(IsDrive a, MonadIO m) =>
a -> IO () -> m SignalHandlerId
afterDriveStopButton a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_DriveChangedCallback
cb' = IO () -> C_DriveChangedCallback
wrap_DriveStopButtonCallback IO ()
cb
    FunPtr C_DriveChangedCallback
cb'' <- C_DriveChangedCallback -> IO (FunPtr C_DriveChangedCallback)
mk_DriveStopButtonCallback C_DriveChangedCallback
cb'
    a
-> Text
-> FunPtr C_DriveChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"stop-button" FunPtr C_DriveChangedCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data DriveStopButtonSignalInfo
instance SignalInfo DriveStopButtonSignalInfo where
    type HaskellCallbackType DriveStopButtonSignalInfo = DriveStopButtonCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_DriveStopButtonCallback cb
        cb'' <- mk_DriveStopButtonCallback cb'
        connectSignalFunPtr obj "stop-button" cb'' connectMode detail

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Drive = DriveSignalList
type DriveSignalList = ('[ '("changed", DriveChangedSignalInfo), '("disconnected", DriveDisconnectedSignalInfo), '("ejectButton", DriveEjectButtonSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("stopButton", DriveStopButtonSignalInfo)] :: [(Symbol, *)])

#endif