{-# LANGUAGE ImplicitParams, RankNTypes, TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gio.Interfaces.Drive
(
Drive(..) ,
IsDrive ,
toDrive ,
#if defined(ENABLE_OVERLOADING)
ResolveDriveMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
DriveCanEjectMethodInfo ,
#endif
driveCanEject ,
#if defined(ENABLE_OVERLOADING)
DriveCanPollForMediaMethodInfo ,
#endif
driveCanPollForMedia ,
#if defined(ENABLE_OVERLOADING)
DriveCanStartMethodInfo ,
#endif
driveCanStart ,
#if defined(ENABLE_OVERLOADING)
DriveCanStartDegradedMethodInfo ,
#endif
driveCanStartDegraded ,
#if defined(ENABLE_OVERLOADING)
DriveCanStopMethodInfo ,
#endif
driveCanStop ,
#if defined(ENABLE_OVERLOADING)
DriveEjectMethodInfo ,
#endif
driveEject ,
#if defined(ENABLE_OVERLOADING)
DriveEjectFinishMethodInfo ,
#endif
driveEjectFinish ,
#if defined(ENABLE_OVERLOADING)
DriveEjectWithOperationMethodInfo ,
#endif
driveEjectWithOperation ,
#if defined(ENABLE_OVERLOADING)
DriveEjectWithOperationFinishMethodInfo ,
#endif
driveEjectWithOperationFinish ,
#if defined(ENABLE_OVERLOADING)
DriveEnumerateIdentifiersMethodInfo ,
#endif
driveEnumerateIdentifiers ,
#if defined(ENABLE_OVERLOADING)
DriveGetIconMethodInfo ,
#endif
driveGetIcon ,
#if defined(ENABLE_OVERLOADING)
DriveGetIdentifierMethodInfo ,
#endif
driveGetIdentifier ,
#if defined(ENABLE_OVERLOADING)
DriveGetNameMethodInfo ,
#endif
driveGetName ,
#if defined(ENABLE_OVERLOADING)
DriveGetSortKeyMethodInfo ,
#endif
driveGetSortKey ,
#if defined(ENABLE_OVERLOADING)
DriveGetStartStopTypeMethodInfo ,
#endif
driveGetStartStopType ,
#if defined(ENABLE_OVERLOADING)
DriveGetSymbolicIconMethodInfo ,
#endif
driveGetSymbolicIcon ,
#if defined(ENABLE_OVERLOADING)
DriveGetVolumesMethodInfo ,
#endif
driveGetVolumes ,
#if defined(ENABLE_OVERLOADING)
DriveHasMediaMethodInfo ,
#endif
driveHasMedia ,
#if defined(ENABLE_OVERLOADING)
DriveHasVolumesMethodInfo ,
#endif
driveHasVolumes ,
#if defined(ENABLE_OVERLOADING)
DriveIsMediaCheckAutomaticMethodInfo ,
#endif
driveIsMediaCheckAutomatic ,
#if defined(ENABLE_OVERLOADING)
DriveIsMediaRemovableMethodInfo ,
#endif
driveIsMediaRemovable ,
#if defined(ENABLE_OVERLOADING)
DriveIsRemovableMethodInfo ,
#endif
driveIsRemovable ,
#if defined(ENABLE_OVERLOADING)
DrivePollForMediaMethodInfo ,
#endif
drivePollForMedia ,
#if defined(ENABLE_OVERLOADING)
DrivePollForMediaFinishMethodInfo ,
#endif
drivePollForMediaFinish ,
#if defined(ENABLE_OVERLOADING)
DriveStartMethodInfo ,
#endif
driveStart ,
#if defined(ENABLE_OVERLOADING)
DriveStartFinishMethodInfo ,
#endif
driveStartFinish ,
#if defined(ENABLE_OVERLOADING)
DriveStopMethodInfo ,
#endif
driveStop ,
#if defined(ENABLE_OVERLOADING)
DriveStopFinishMethodInfo ,
#endif
driveStopFinish ,
DriveChangedCallback ,
#if defined(ENABLE_OVERLOADING)
DriveChangedSignalInfo ,
#endif
afterDriveChanged ,
onDriveChanged ,
DriveDisconnectedCallback ,
#if defined(ENABLE_OVERLOADING)
DriveDisconnectedSignalInfo ,
#endif
afterDriveDisconnected ,
onDriveDisconnected ,
DriveEjectButtonCallback ,
#if defined(ENABLE_OVERLOADING)
DriveEjectButtonSignalInfo ,
#endif
afterDriveEjectButton ,
onDriveEjectButton ,
DriveStopButtonCallback ,
#if defined(ENABLE_OVERLOADING)
DriveStopButtonSignalInfo ,
#endif
afterDriveStopButton ,
onDriveStopButton ,
) where
import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P
import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.Kind as DK
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R
import qualified Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT
#if MIN_VERSION_base(4,18,0)
import qualified GI.GLib.Callbacks as GLib.Callbacks
import qualified GI.GLib.Enums as GLib.Enums
import qualified GI.GLib.Structs.Bytes as GLib.Bytes
import qualified GI.GLib.Structs.DateTime as GLib.DateTime
import qualified GI.GLib.Structs.PollFD as GLib.PollFD
import qualified GI.GLib.Structs.Source as GLib.Source
import qualified GI.GLib.Structs.TimeVal as GLib.TimeVal
import qualified GI.GObject.Callbacks as GObject.Callbacks
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.AppInfo as Gio.AppInfo
import {-# SOURCE #-} qualified GI.Gio.Interfaces.AsyncResult as Gio.AsyncResult
import {-# SOURCE #-} qualified GI.Gio.Interfaces.File as Gio.File
import {-# SOURCE #-} qualified GI.Gio.Interfaces.Icon as Gio.Icon
import {-# SOURCE #-} qualified GI.Gio.Interfaces.Mount as Gio.Mount
import {-# SOURCE #-} qualified GI.Gio.Interfaces.Seekable as Gio.Seekable
import {-# SOURCE #-} qualified GI.Gio.Interfaces.Volume as Gio.Volume
import {-# SOURCE #-} qualified GI.Gio.Objects.AppLaunchContext as Gio.AppLaunchContext
import {-# SOURCE #-} qualified GI.Gio.Objects.Cancellable as Gio.Cancellable
import {-# SOURCE #-} qualified GI.Gio.Objects.FileEnumerator as Gio.FileEnumerator
import {-# SOURCE #-} qualified GI.Gio.Objects.FileIOStream as Gio.FileIOStream
import {-# SOURCE #-} qualified GI.Gio.Objects.FileInfo as Gio.FileInfo
import {-# SOURCE #-} qualified GI.Gio.Objects.FileInputStream as Gio.FileInputStream
import {-# SOURCE #-} qualified GI.Gio.Objects.FileMonitor as Gio.FileMonitor
import {-# SOURCE #-} qualified GI.Gio.Objects.FileOutputStream as Gio.FileOutputStream
import {-# SOURCE #-} qualified GI.Gio.Objects.IOStream as Gio.IOStream
import {-# SOURCE #-} qualified GI.Gio.Objects.InputStream as Gio.InputStream
import {-# SOURCE #-} qualified GI.Gio.Objects.MountOperation as Gio.MountOperation
import {-# SOURCE #-} qualified GI.Gio.Objects.OutputStream as Gio.OutputStream
import {-# SOURCE #-} qualified GI.Gio.Structs.FileAttributeInfo as Gio.FileAttributeInfo
import {-# SOURCE #-} qualified GI.Gio.Structs.FileAttributeInfoList as Gio.FileAttributeInfoList
import {-# SOURCE #-} qualified GI.Gio.Structs.FileAttributeMatcher as Gio.FileAttributeMatcher
import {-# SOURCE #-} qualified GI.Gio.Structs.OutputVector as Gio.OutputVector
#else
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
#endif
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
$c== :: Drive -> Drive -> Bool
== :: Drive -> Drive -> Bool
$c/= :: Drive -> Drive -> Bool
/= :: 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
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]
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 a. IO a -> m a
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
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 a. a -> IO a
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, DK.Type)])
#endif
#if defined(ENABLE_OVERLOADING)
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveDriveMethod (t :: Symbol) (o :: DK.Type) :: DK.Type 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
foreign import ccall "g_drive_can_eject" g_drive_can_eject ::
Ptr Drive ->
IO CInt
driveCanEject ::
(B.CallStack.HasCallStack, MonadIO m, IsDrive a) =>
a
-> m Bool
driveCanEject :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDrive a) =>
a -> m Bool
driveCanEject a
drive = IO Bool -> m Bool
forall a. IO a -> m a
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 a. a -> IO a
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 = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gio.Interfaces.Drive.driveCanEject",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.34/docs/GI-Gio-Interfaces-Drive.html#v:driveCanEject"
})
#endif
foreign import ccall "g_drive_can_poll_for_media" g_drive_can_poll_for_media ::
Ptr Drive ->
IO CInt
driveCanPollForMedia ::
(B.CallStack.HasCallStack, MonadIO m, IsDrive a) =>
a
-> m Bool
driveCanPollForMedia :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDrive a) =>
a -> m Bool
driveCanPollForMedia a
drive = IO Bool -> m Bool
forall a. IO a -> m a
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 a. a -> IO a
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 = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gio.Interfaces.Drive.driveCanPollForMedia",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.34/docs/GI-Gio-Interfaces-Drive.html#v:driveCanPollForMedia"
})
#endif
foreign import ccall "g_drive_can_start" g_drive_can_start ::
Ptr Drive ->
IO CInt
driveCanStart ::
(B.CallStack.HasCallStack, MonadIO m, IsDrive a) =>
a
-> m Bool
driveCanStart :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDrive a) =>
a -> m Bool
driveCanStart a
drive = IO Bool -> m Bool
forall a. IO a -> m a
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 a. a -> IO a
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 = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gio.Interfaces.Drive.driveCanStart",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.34/docs/GI-Gio-Interfaces-Drive.html#v:driveCanStart"
})
#endif
foreign import ccall "g_drive_can_start_degraded" g_drive_can_start_degraded ::
Ptr Drive ->
IO CInt
driveCanStartDegraded ::
(B.CallStack.HasCallStack, MonadIO m, IsDrive a) =>
a
-> m Bool
driveCanStartDegraded :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDrive a) =>
a -> m Bool
driveCanStartDegraded a
drive = IO Bool -> m Bool
forall a. IO a -> m a
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 a. a -> IO a
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 = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gio.Interfaces.Drive.driveCanStartDegraded",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.34/docs/GI-Gio-Interfaces-Drive.html#v:driveCanStartDegraded"
})
#endif
foreign import ccall "g_drive_can_stop" g_drive_can_stop ::
Ptr Drive ->
IO CInt
driveCanStop ::
(B.CallStack.HasCallStack, MonadIO m, IsDrive a) =>
a
-> m Bool
driveCanStop :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDrive a) =>
a -> m Bool
driveCanStop a
drive = IO Bool -> m Bool
forall a. IO a -> m a
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 a. a -> IO a
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 = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gio.Interfaces.Drive.driveCanStop",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.34/docs/GI-Gio-Interfaces-Drive.html#v:driveCanStop"
})
#endif
foreign import ccall "g_drive_eject" g_drive_eject ::
Ptr Drive ->
CUInt ->
Ptr Gio.Cancellable.Cancellable ->
FunPtr Gio.Callbacks.C_AsyncReadyCallback ->
Ptr () ->
IO ()
{-# DEPRECATED driveEject ["(Since version 2.22)","Use 'GI.Gio.Interfaces.Drive.driveEjectWithOperation' instead."] #-}
driveEject ::
(B.CallStack.HasCallStack, MonadIO m, IsDrive a, Gio.Cancellable.IsCancellable b) =>
a
-> [Gio.Flags.MountUnmountFlags]
-> Maybe (b)
-> Maybe (Gio.Callbacks.AsyncReadyCallback)
-> 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 a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr 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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
FP.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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
FunPtr C_AsyncReadyCallback
maybeCallback <- case Maybe AsyncReadyCallback
callback of
Maybe AsyncReadyCallback
Nothing -> FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_AsyncReadyCallback
forall a. FunPtr a
FP.nullFunPtr
Just AsyncReadyCallback
jCallback -> do
Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback <- IO (Ptr (FunPtr C_AsyncReadyCallback))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr Gio.Callbacks.C_AsyncReadyCallback))
FunPtr C_AsyncReadyCallback
jCallback' <- C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
Gio.Callbacks.mk_AsyncReadyCallback (Maybe (Ptr (FunPtr C_AsyncReadyCallback))
-> AsyncReadyCallback_WithClosures -> C_AsyncReadyCallback
Gio.Callbacks.wrap_AsyncReadyCallback (Ptr (FunPtr C_AsyncReadyCallback)
-> Maybe (Ptr (FunPtr C_AsyncReadyCallback))
forall a. a -> Maybe a
Just Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback) (AsyncReadyCallback -> AsyncReadyCallback_WithClosures
Gio.Callbacks.drop_closures_AsyncReadyCallback AsyncReadyCallback
jCallback))
Ptr (FunPtr C_AsyncReadyCallback)
-> FunPtr C_AsyncReadyCallback -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback FunPtr C_AsyncReadyCallback
jCallback'
FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_AsyncReadyCallback
jCallback'
let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
Ptr 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 a. a -> IO a
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 = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gio.Interfaces.Drive.driveEject",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.34/docs/GI-Gio-Interfaces-Drive.html#v:driveEject"
})
#endif
foreign import ccall "g_drive_eject_finish" g_drive_eject_finish ::
Ptr Drive ->
Ptr Gio.AsyncResult.AsyncResult ->
Ptr (Ptr GError) ->
IO CInt
{-# DEPRECATED driveEjectFinish ["(Since version 2.22)","Use 'GI.Gio.Interfaces.Drive.driveEjectWithOperationFinish' instead."] #-}
driveEjectFinish ::
(B.CallStack.HasCallStack, MonadIO m, IsDrive a, Gio.AsyncResult.IsAsyncResult b) =>
a
-> b
-> m ()
driveEjectFinish :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDrive a, IsAsyncResult b) =>
a -> b -> m ()
driveEjectFinish a
drive b
result_ = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr 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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
) (do
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
)
#if defined(ENABLE_OVERLOADING)
data 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 = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gio.Interfaces.Drive.driveEjectFinish",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.34/docs/GI-Gio-Interfaces-Drive.html#v:driveEjectFinish"
})
#endif
foreign import ccall "g_drive_eject_with_operation" g_drive_eject_with_operation ::
Ptr Drive ->
CUInt ->
Ptr Gio.MountOperation.MountOperation ->
Ptr Gio.Cancellable.Cancellable ->
FunPtr Gio.Callbacks.C_AsyncReadyCallback ->
Ptr () ->
IO ()
driveEjectWithOperation ::
(B.CallStack.HasCallStack, MonadIO m, IsDrive a, Gio.MountOperation.IsMountOperation b, Gio.Cancellable.IsCancellable c) =>
a
-> [Gio.Flags.MountUnmountFlags]
-> Maybe (b)
-> Maybe (c)
-> Maybe (Gio.Callbacks.AsyncReadyCallback)
-> 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 a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr 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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr MountOperation
forall a. Ptr a
FP.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 a. a -> IO a
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
FP.nullPtr
Just c
jCancellable -> do
Ptr Cancellable
jCancellable' <- c -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr c
jCancellable
Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
FunPtr C_AsyncReadyCallback
maybeCallback <- case Maybe AsyncReadyCallback
callback of
Maybe AsyncReadyCallback
Nothing -> FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_AsyncReadyCallback
forall a. FunPtr a
FP.nullFunPtr
Just AsyncReadyCallback
jCallback -> do
Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback <- IO (Ptr (FunPtr C_AsyncReadyCallback))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr Gio.Callbacks.C_AsyncReadyCallback))
FunPtr C_AsyncReadyCallback
jCallback' <- C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
Gio.Callbacks.mk_AsyncReadyCallback (Maybe (Ptr (FunPtr C_AsyncReadyCallback))
-> AsyncReadyCallback_WithClosures -> C_AsyncReadyCallback
Gio.Callbacks.wrap_AsyncReadyCallback (Ptr (FunPtr C_AsyncReadyCallback)
-> Maybe (Ptr (FunPtr C_AsyncReadyCallback))
forall a. a -> Maybe a
Just Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback) (AsyncReadyCallback -> AsyncReadyCallback_WithClosures
Gio.Callbacks.drop_closures_AsyncReadyCallback AsyncReadyCallback
jCallback))
Ptr (FunPtr C_AsyncReadyCallback)
-> FunPtr C_AsyncReadyCallback -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback FunPtr C_AsyncReadyCallback
jCallback'
FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_AsyncReadyCallback
jCallback'
let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
Ptr 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 a. a -> IO a
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 = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gio.Interfaces.Drive.driveEjectWithOperation",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.34/docs/GI-Gio-Interfaces-Drive.html#v:driveEjectWithOperation"
})
#endif
foreign import ccall "g_drive_eject_with_operation_finish" g_drive_eject_with_operation_finish ::
Ptr Drive ->
Ptr Gio.AsyncResult.AsyncResult ->
Ptr (Ptr GError) ->
IO CInt
driveEjectWithOperationFinish ::
(B.CallStack.HasCallStack, MonadIO m, IsDrive a, Gio.AsyncResult.IsAsyncResult b) =>
a
-> b
-> m ()
driveEjectWithOperationFinish :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDrive a, IsAsyncResult b) =>
a -> b -> m ()
driveEjectWithOperationFinish a
drive b
result_ = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr 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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
) (do
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
)
#if defined(ENABLE_OVERLOADING)
data 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 = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gio.Interfaces.Drive.driveEjectWithOperationFinish",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.34/docs/GI-Gio-Interfaces-Drive.html#v:driveEjectWithOperationFinish"
})
#endif
foreign import ccall "g_drive_enumerate_identifiers" g_drive_enumerate_identifiers ::
Ptr Drive ->
IO (Ptr CString)
driveEnumerateIdentifiers ::
(B.CallStack.HasCallStack, MonadIO m, IsDrive a) =>
a
-> m [T.Text]
driveEnumerateIdentifiers :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDrive a) =>
a -> m [Text]
driveEnumerateIdentifiers a
drive = IO [Text] -> m [Text]
forall a. IO a -> m a
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 a. a -> IO a
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 = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gio.Interfaces.Drive.driveEnumerateIdentifiers",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.34/docs/GI-Gio-Interfaces-Drive.html#v:driveEnumerateIdentifiers"
})
#endif
foreign import ccall "g_drive_get_icon" g_drive_get_icon ::
Ptr Drive ->
IO (Ptr Gio.Icon.Icon)
driveGetIcon ::
(B.CallStack.HasCallStack, MonadIO m, IsDrive a) =>
a
-> m Gio.Icon.Icon
driveGetIcon :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDrive a) =>
a -> m Icon
driveGetIcon a
drive = IO Icon -> m Icon
forall a. IO a -> m a
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 a. a -> IO a
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 = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gio.Interfaces.Drive.driveGetIcon",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.34/docs/GI-Gio-Interfaces-Drive.html#v:driveGetIcon"
})
#endif
foreign import ccall "g_drive_get_identifier" g_drive_get_identifier ::
Ptr Drive ->
CString ->
IO CString
driveGetIdentifier ::
(B.CallStack.HasCallStack, MonadIO m, IsDrive a) =>
a
-> T.Text
-> m (Maybe T.Text)
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 a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ do
Ptr 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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
drive
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
kind'
Maybe Text -> IO (Maybe Text)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult
#if defined(ENABLE_OVERLOADING)
data 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 = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gio.Interfaces.Drive.driveGetIdentifier",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.34/docs/GI-Gio-Interfaces-Drive.html#v:driveGetIdentifier"
})
#endif
foreign import ccall "g_drive_get_name" g_drive_get_name ::
Ptr Drive ->
IO CString
driveGetName ::
(B.CallStack.HasCallStack, MonadIO m, IsDrive a) =>
a
-> m T.Text
driveGetName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDrive a) =>
a -> m Text
driveGetName a
drive = IO Text -> m Text
forall a. IO a -> m a
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 a. a -> IO a
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 = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gio.Interfaces.Drive.driveGetName",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.34/docs/GI-Gio-Interfaces-Drive.html#v:driveGetName"
})
#endif
foreign import ccall "g_drive_get_sort_key" g_drive_get_sort_key ::
Ptr Drive ->
IO CString
driveGetSortKey ::
(B.CallStack.HasCallStack, MonadIO m, IsDrive a) =>
a
-> m (Maybe T.Text)
driveGetSortKey :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDrive a) =>
a -> m (Maybe Text)
driveGetSortKey a
drive = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ do
Ptr 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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
drive
Maybe Text -> IO (Maybe Text)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult
#if defined(ENABLE_OVERLOADING)
data 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 = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gio.Interfaces.Drive.driveGetSortKey",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.34/docs/GI-Gio-Interfaces-Drive.html#v:driveGetSortKey"
})
#endif
foreign import ccall "g_drive_get_start_stop_type" g_drive_get_start_stop_type ::
Ptr Drive ->
IO CUInt
driveGetStartStopType ::
(B.CallStack.HasCallStack, MonadIO m, IsDrive a) =>
a
-> m Gio.Enums.DriveStartStopType
driveGetStartStopType :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDrive a) =>
a -> m DriveStartStopType
driveGetStartStopType a
drive = IO DriveStartStopType -> m DriveStartStopType
forall a. IO a -> m a
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 a. a -> IO a
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 = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gio.Interfaces.Drive.driveGetStartStopType",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.34/docs/GI-Gio-Interfaces-Drive.html#v:driveGetStartStopType"
})
#endif
foreign import ccall "g_drive_get_symbolic_icon" g_drive_get_symbolic_icon ::
Ptr Drive ->
IO (Ptr Gio.Icon.Icon)
driveGetSymbolicIcon ::
(B.CallStack.HasCallStack, MonadIO m, IsDrive a) =>
a
-> m Gio.Icon.Icon
driveGetSymbolicIcon :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDrive a) =>
a -> m Icon
driveGetSymbolicIcon a
drive = IO Icon -> m Icon
forall a. IO a -> m a
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 a. a -> IO a
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 = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gio.Interfaces.Drive.driveGetSymbolicIcon",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.34/docs/GI-Gio-Interfaces-Drive.html#v:driveGetSymbolicIcon"
})
#endif
foreign import ccall "g_drive_get_volumes" g_drive_get_volumes ::
Ptr Drive ->
IO (Ptr (GList (Ptr Gio.Volume.Volume)))
driveGetVolumes ::
(B.CallStack.HasCallStack, MonadIO m, IsDrive a) =>
a
-> m [Gio.Volume.Volume]
driveGetVolumes :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDrive a) =>
a -> m [Volume]
driveGetVolumes a
drive = IO [Volume] -> m [Volume]
forall a. IO a -> m a
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)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [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 a. a -> IO a
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 = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gio.Interfaces.Drive.driveGetVolumes",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.34/docs/GI-Gio-Interfaces-Drive.html#v:driveGetVolumes"
})
#endif
foreign import ccall "g_drive_has_media" g_drive_has_media ::
Ptr Drive ->
IO CInt
driveHasMedia ::
(B.CallStack.HasCallStack, MonadIO m, IsDrive a) =>
a
-> m Bool
driveHasMedia :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDrive a) =>
a -> m Bool
driveHasMedia a
drive = IO Bool -> m Bool
forall a. IO a -> m a
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 a. a -> IO a
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 = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gio.Interfaces.Drive.driveHasMedia",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.34/docs/GI-Gio-Interfaces-Drive.html#v:driveHasMedia"
})
#endif
foreign import ccall "g_drive_has_volumes" g_drive_has_volumes ::
Ptr Drive ->
IO CInt
driveHasVolumes ::
(B.CallStack.HasCallStack, MonadIO m, IsDrive a) =>
a
-> m Bool
driveHasVolumes :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDrive a) =>
a -> m Bool
driveHasVolumes a
drive = IO Bool -> m Bool
forall a. IO a -> m a
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 a. a -> IO a
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 = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gio.Interfaces.Drive.driveHasVolumes",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.34/docs/GI-Gio-Interfaces-Drive.html#v:driveHasVolumes"
})
#endif
foreign import ccall "g_drive_is_media_check_automatic" g_drive_is_media_check_automatic ::
Ptr Drive ->
IO CInt
driveIsMediaCheckAutomatic ::
(B.CallStack.HasCallStack, MonadIO m, IsDrive a) =>
a
-> m Bool
driveIsMediaCheckAutomatic :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDrive a) =>
a -> m Bool
driveIsMediaCheckAutomatic a
drive = IO Bool -> m Bool
forall a. IO a -> m a
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 a. a -> IO a
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 = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gio.Interfaces.Drive.driveIsMediaCheckAutomatic",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.34/docs/GI-Gio-Interfaces-Drive.html#v:driveIsMediaCheckAutomatic"
})
#endif
foreign import ccall "g_drive_is_media_removable" g_drive_is_media_removable ::
Ptr Drive ->
IO CInt
driveIsMediaRemovable ::
(B.CallStack.HasCallStack, MonadIO m, IsDrive a) =>
a
-> m Bool
driveIsMediaRemovable :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDrive a) =>
a -> m Bool
driveIsMediaRemovable a
drive = IO Bool -> m Bool
forall a. IO a -> m a
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 a. a -> IO a
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 = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gio.Interfaces.Drive.driveIsMediaRemovable",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.34/docs/GI-Gio-Interfaces-Drive.html#v:driveIsMediaRemovable"
})
#endif
foreign import ccall "g_drive_is_removable" g_drive_is_removable ::
Ptr Drive ->
IO CInt
driveIsRemovable ::
(B.CallStack.HasCallStack, MonadIO m, IsDrive a) =>
a
-> m Bool
driveIsRemovable :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDrive a) =>
a -> m Bool
driveIsRemovable a
drive = IO Bool -> m Bool
forall a. IO a -> m a
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 a. a -> IO a
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 = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gio.Interfaces.Drive.driveIsRemovable",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.34/docs/GI-Gio-Interfaces-Drive.html#v:driveIsRemovable"
})
#endif
foreign import ccall "g_drive_poll_for_media" g_drive_poll_for_media ::
Ptr Drive ->
Ptr Gio.Cancellable.Cancellable ->
FunPtr Gio.Callbacks.C_AsyncReadyCallback ->
Ptr () ->
IO ()
drivePollForMedia ::
(B.CallStack.HasCallStack, MonadIO m, IsDrive a, Gio.Cancellable.IsCancellable b) =>
a
-> Maybe (b)
-> Maybe (Gio.Callbacks.AsyncReadyCallback)
-> 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 a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr 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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
FP.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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
FunPtr C_AsyncReadyCallback
maybeCallback <- case Maybe AsyncReadyCallback
callback of
Maybe AsyncReadyCallback
Nothing -> FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_AsyncReadyCallback
forall a. FunPtr a
FP.nullFunPtr
Just AsyncReadyCallback
jCallback -> do
Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback <- IO (Ptr (FunPtr C_AsyncReadyCallback))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr Gio.Callbacks.C_AsyncReadyCallback))
FunPtr C_AsyncReadyCallback
jCallback' <- C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
Gio.Callbacks.mk_AsyncReadyCallback (Maybe (Ptr (FunPtr C_AsyncReadyCallback))
-> AsyncReadyCallback_WithClosures -> C_AsyncReadyCallback
Gio.Callbacks.wrap_AsyncReadyCallback (Ptr (FunPtr C_AsyncReadyCallback)
-> Maybe (Ptr (FunPtr C_AsyncReadyCallback))
forall a. a -> Maybe a
Just Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback) (AsyncReadyCallback -> AsyncReadyCallback_WithClosures
Gio.Callbacks.drop_closures_AsyncReadyCallback AsyncReadyCallback
jCallback))
Ptr (FunPtr C_AsyncReadyCallback)
-> FunPtr C_AsyncReadyCallback -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback FunPtr C_AsyncReadyCallback
jCallback'
FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_AsyncReadyCallback
jCallback'
let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
Ptr 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 a. a -> IO a
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 = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gio.Interfaces.Drive.drivePollForMedia",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.34/docs/GI-Gio-Interfaces-Drive.html#v:drivePollForMedia"
})
#endif
foreign import ccall "g_drive_poll_for_media_finish" g_drive_poll_for_media_finish ::
Ptr Drive ->
Ptr Gio.AsyncResult.AsyncResult ->
Ptr (Ptr GError) ->
IO CInt
drivePollForMediaFinish ::
(B.CallStack.HasCallStack, MonadIO m, IsDrive a, Gio.AsyncResult.IsAsyncResult b) =>
a
-> b
-> m ()
drivePollForMediaFinish :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDrive a, IsAsyncResult b) =>
a -> b -> m ()
drivePollForMediaFinish a
drive b
result_ = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr 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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
) (do
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
)
#if defined(ENABLE_OVERLOADING)
data 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 = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gio.Interfaces.Drive.drivePollForMediaFinish",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.34/docs/GI-Gio-Interfaces-Drive.html#v:drivePollForMediaFinish"
})
#endif
foreign import ccall "g_drive_start" g_drive_start ::
Ptr Drive ->
CUInt ->
Ptr Gio.MountOperation.MountOperation ->
Ptr Gio.Cancellable.Cancellable ->
FunPtr Gio.Callbacks.C_AsyncReadyCallback ->
Ptr () ->
IO ()
driveStart ::
(B.CallStack.HasCallStack, MonadIO m, IsDrive a, Gio.MountOperation.IsMountOperation b, Gio.Cancellable.IsCancellable c) =>
a
-> [Gio.Flags.DriveStartFlags]
-> Maybe (b)
-> Maybe (c)
-> Maybe (Gio.Callbacks.AsyncReadyCallback)
-> 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 a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr 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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr MountOperation
forall a. Ptr a
FP.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 a. a -> IO a
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
FP.nullPtr
Just c
jCancellable -> do
Ptr Cancellable
jCancellable' <- c -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr c
jCancellable
Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
FunPtr C_AsyncReadyCallback
maybeCallback <- case Maybe AsyncReadyCallback
callback of
Maybe AsyncReadyCallback
Nothing -> FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_AsyncReadyCallback
forall a. FunPtr a
FP.nullFunPtr
Just AsyncReadyCallback
jCallback -> do
Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback <- IO (Ptr (FunPtr C_AsyncReadyCallback))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr Gio.Callbacks.C_AsyncReadyCallback))
FunPtr C_AsyncReadyCallback
jCallback' <- C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
Gio.Callbacks.mk_AsyncReadyCallback (Maybe (Ptr (FunPtr C_AsyncReadyCallback))
-> AsyncReadyCallback_WithClosures -> C_AsyncReadyCallback
Gio.Callbacks.wrap_AsyncReadyCallback (Ptr (FunPtr C_AsyncReadyCallback)
-> Maybe (Ptr (FunPtr C_AsyncReadyCallback))
forall a. a -> Maybe a
Just Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback) (AsyncReadyCallback -> AsyncReadyCallback_WithClosures
Gio.Callbacks.drop_closures_AsyncReadyCallback AsyncReadyCallback
jCallback))
Ptr (FunPtr C_AsyncReadyCallback)
-> FunPtr C_AsyncReadyCallback -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback FunPtr C_AsyncReadyCallback
jCallback'
FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_AsyncReadyCallback
jCallback'
let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
Ptr 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 a. a -> IO a
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 = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gio.Interfaces.Drive.driveStart",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.34/docs/GI-Gio-Interfaces-Drive.html#v:driveStart"
})
#endif
foreign import ccall "g_drive_start_finish" g_drive_start_finish ::
Ptr Drive ->
Ptr Gio.AsyncResult.AsyncResult ->
Ptr (Ptr GError) ->
IO CInt
driveStartFinish ::
(B.CallStack.HasCallStack, MonadIO m, IsDrive a, Gio.AsyncResult.IsAsyncResult b) =>
a
-> b
-> m ()
driveStartFinish :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDrive a, IsAsyncResult b) =>
a -> b -> m ()
driveStartFinish a
drive b
result_ = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr 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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
) (do
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
)
#if defined(ENABLE_OVERLOADING)
data 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 = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gio.Interfaces.Drive.driveStartFinish",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.34/docs/GI-Gio-Interfaces-Drive.html#v:driveStartFinish"
})
#endif
foreign import ccall "g_drive_stop" g_drive_stop ::
Ptr Drive ->
CUInt ->
Ptr Gio.MountOperation.MountOperation ->
Ptr Gio.Cancellable.Cancellable ->
FunPtr Gio.Callbacks.C_AsyncReadyCallback ->
Ptr () ->
IO ()
driveStop ::
(B.CallStack.HasCallStack, MonadIO m, IsDrive a, Gio.MountOperation.IsMountOperation b, Gio.Cancellable.IsCancellable c) =>
a
-> [Gio.Flags.MountUnmountFlags]
-> Maybe (b)
-> Maybe (c)
-> Maybe (Gio.Callbacks.AsyncReadyCallback)
-> 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 a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr 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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr MountOperation
forall a. Ptr a
FP.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 a. a -> IO a
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
FP.nullPtr
Just c
jCancellable -> do
Ptr Cancellable
jCancellable' <- c -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr c
jCancellable
Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
FunPtr C_AsyncReadyCallback
maybeCallback <- case Maybe AsyncReadyCallback
callback of
Maybe AsyncReadyCallback
Nothing -> FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_AsyncReadyCallback
forall a. FunPtr a
FP.nullFunPtr
Just AsyncReadyCallback
jCallback -> do
Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback <- IO (Ptr (FunPtr C_AsyncReadyCallback))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr Gio.Callbacks.C_AsyncReadyCallback))
FunPtr C_AsyncReadyCallback
jCallback' <- C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
Gio.Callbacks.mk_AsyncReadyCallback (Maybe (Ptr (FunPtr C_AsyncReadyCallback))
-> AsyncReadyCallback_WithClosures -> C_AsyncReadyCallback
Gio.Callbacks.wrap_AsyncReadyCallback (Ptr (FunPtr C_AsyncReadyCallback)
-> Maybe (Ptr (FunPtr C_AsyncReadyCallback))
forall a. a -> Maybe a
Just Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback) (AsyncReadyCallback -> AsyncReadyCallback_WithClosures
Gio.Callbacks.drop_closures_AsyncReadyCallback AsyncReadyCallback
jCallback))
Ptr (FunPtr C_AsyncReadyCallback)
-> FunPtr C_AsyncReadyCallback -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback FunPtr C_AsyncReadyCallback
jCallback'
FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_AsyncReadyCallback
jCallback'
let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
Ptr 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 a. a -> IO a
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 = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gio.Interfaces.Drive.driveStop",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.34/docs/GI-Gio-Interfaces-Drive.html#v:driveStop"
})
#endif
foreign import ccall "g_drive_stop_finish" g_drive_stop_finish ::
Ptr Drive ->
Ptr Gio.AsyncResult.AsyncResult ->
Ptr (Ptr GError) ->
IO CInt
driveStopFinish ::
(B.CallStack.HasCallStack, MonadIO m, IsDrive a, Gio.AsyncResult.IsAsyncResult b) =>
a
-> b
-> m ()
driveStopFinish :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDrive a, IsAsyncResult b) =>
a -> b -> m ()
driveStopFinish a
drive b
result_ = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr 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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
) (do
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
)
#if defined(ENABLE_OVERLOADING)
data 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 = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gio.Interfaces.Drive.driveStopFinish",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.34/docs/GI-Gio-Interfaces-Drive.html#v:driveStopFinish"
})
#endif
type DriveChangedCallback =
IO ()
type C_DriveChangedCallback =
Ptr Drive ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_DriveChangedCallback :: C_DriveChangedCallback -> IO (FunPtr C_DriveChangedCallback)
wrap_DriveChangedCallback ::
GObject a => (a -> DriveChangedCallback) ->
C_DriveChangedCallback
wrap_DriveChangedCallback :: forall a. GObject a => (a -> IO ()) -> C_DriveChangedCallback
wrap_DriveChangedCallback a -> IO ()
gi'cb Ptr Drive
gi'selfPtr Ptr ()
_ = do
Ptr Drive -> (Drive -> IO ()) -> IO ()
forall o b.
(HasCallStack, GObject o) =>
Ptr o -> (o -> IO b) -> IO b
B.ManagedPtr.withNewObject Ptr Drive
gi'selfPtr ((Drive -> IO ()) -> IO ()) -> (Drive -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Drive
gi'self -> a -> IO ()
gi'cb (Drive -> a
forall a b. Coercible a b => a -> b
Coerce.coerce Drive
gi'self)
onDriveChanged :: (IsDrive a, MonadIO m) => a -> ((?self :: a) => DriveChangedCallback) -> m SignalHandlerId
onDriveChanged :: forall a (m :: * -> *).
(IsDrive a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
onDriveChanged a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
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 wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
let wrapped' :: C_DriveChangedCallback
wrapped' = (a -> IO ()) -> C_DriveChangedCallback
forall a. GObject a => (a -> IO ()) -> C_DriveChangedCallback
wrap_DriveChangedCallback a -> IO ()
wrapped
FunPtr C_DriveChangedCallback
wrapped'' <- C_DriveChangedCallback -> IO (FunPtr C_DriveChangedCallback)
mk_DriveChangedCallback C_DriveChangedCallback
wrapped'
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
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterDriveChanged :: (IsDrive a, MonadIO m) => a -> ((?self :: a) => DriveChangedCallback) -> m SignalHandlerId
afterDriveChanged :: forall a (m :: * -> *).
(IsDrive a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
afterDriveChanged a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
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 wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
let wrapped' :: C_DriveChangedCallback
wrapped' = (a -> IO ()) -> C_DriveChangedCallback
forall a. GObject a => (a -> IO ()) -> C_DriveChangedCallback
wrap_DriveChangedCallback a -> IO ()
wrapped
FunPtr C_DriveChangedCallback
wrapped'' <- C_DriveChangedCallback -> IO (FunPtr C_DriveChangedCallback)
mk_DriveChangedCallback C_DriveChangedCallback
wrapped'
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
wrapped'' 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
dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gio.Interfaces.Drive::changed"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.34/docs/GI-Gio-Interfaces-Drive.html#g:signal:changed"})
#endif
type DriveDisconnectedCallback =
IO ()
type C_DriveDisconnectedCallback =
Ptr Drive ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_DriveDisconnectedCallback :: C_DriveDisconnectedCallback -> IO (FunPtr C_DriveDisconnectedCallback)
wrap_DriveDisconnectedCallback ::
GObject a => (a -> DriveDisconnectedCallback) ->
C_DriveDisconnectedCallback
wrap_DriveDisconnectedCallback :: forall a. GObject a => (a -> IO ()) -> C_DriveChangedCallback
wrap_DriveDisconnectedCallback a -> IO ()
gi'cb Ptr Drive
gi'selfPtr Ptr ()
_ = do
Ptr Drive -> (Drive -> IO ()) -> IO ()
forall o b.
(HasCallStack, GObject o) =>
Ptr o -> (o -> IO b) -> IO b
B.ManagedPtr.withNewObject Ptr Drive
gi'selfPtr ((Drive -> IO ()) -> IO ()) -> (Drive -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Drive
gi'self -> a -> IO ()
gi'cb (Drive -> a
forall a b. Coercible a b => a -> b
Coerce.coerce Drive
gi'self)
onDriveDisconnected :: (IsDrive a, MonadIO m) => a -> ((?self :: a) => DriveDisconnectedCallback) -> m SignalHandlerId
onDriveDisconnected :: forall a (m :: * -> *).
(IsDrive a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
onDriveDisconnected a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
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 wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
let wrapped' :: C_DriveChangedCallback
wrapped' = (a -> IO ()) -> C_DriveChangedCallback
forall a. GObject a => (a -> IO ()) -> C_DriveChangedCallback
wrap_DriveDisconnectedCallback a -> IO ()
wrapped
FunPtr C_DriveChangedCallback
wrapped'' <- C_DriveChangedCallback -> IO (FunPtr C_DriveChangedCallback)
mk_DriveDisconnectedCallback C_DriveChangedCallback
wrapped'
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
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterDriveDisconnected :: (IsDrive a, MonadIO m) => a -> ((?self :: a) => DriveDisconnectedCallback) -> m SignalHandlerId
afterDriveDisconnected :: forall a (m :: * -> *).
(IsDrive a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
afterDriveDisconnected a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
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 wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
let wrapped' :: C_DriveChangedCallback
wrapped' = (a -> IO ()) -> C_DriveChangedCallback
forall a. GObject a => (a -> IO ()) -> C_DriveChangedCallback
wrap_DriveDisconnectedCallback a -> IO ()
wrapped
FunPtr C_DriveChangedCallback
wrapped'' <- C_DriveChangedCallback -> IO (FunPtr C_DriveChangedCallback)
mk_DriveDisconnectedCallback C_DriveChangedCallback
wrapped'
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
wrapped'' 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
dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gio.Interfaces.Drive::disconnected"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.34/docs/GI-Gio-Interfaces-Drive.html#g:signal:disconnected"})
#endif
type DriveEjectButtonCallback =
IO ()
type C_DriveEjectButtonCallback =
Ptr Drive ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_DriveEjectButtonCallback :: C_DriveEjectButtonCallback -> IO (FunPtr C_DriveEjectButtonCallback)
wrap_DriveEjectButtonCallback ::
GObject a => (a -> DriveEjectButtonCallback) ->
C_DriveEjectButtonCallback
wrap_DriveEjectButtonCallback :: forall a. GObject a => (a -> IO ()) -> C_DriveChangedCallback
wrap_DriveEjectButtonCallback a -> IO ()
gi'cb Ptr Drive
gi'selfPtr Ptr ()
_ = do
Ptr Drive -> (Drive -> IO ()) -> IO ()
forall o b.
(HasCallStack, GObject o) =>
Ptr o -> (o -> IO b) -> IO b
B.ManagedPtr.withNewObject Ptr Drive
gi'selfPtr ((Drive -> IO ()) -> IO ()) -> (Drive -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Drive
gi'self -> a -> IO ()
gi'cb (Drive -> a
forall a b. Coercible a b => a -> b
Coerce.coerce Drive
gi'self)
onDriveEjectButton :: (IsDrive a, MonadIO m) => a -> ((?self :: a) => DriveEjectButtonCallback) -> m SignalHandlerId
onDriveEjectButton :: forall a (m :: * -> *).
(IsDrive a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
onDriveEjectButton a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
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 wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
let wrapped' :: C_DriveChangedCallback
wrapped' = (a -> IO ()) -> C_DriveChangedCallback
forall a. GObject a => (a -> IO ()) -> C_DriveChangedCallback
wrap_DriveEjectButtonCallback a -> IO ()
wrapped
FunPtr C_DriveChangedCallback
wrapped'' <- C_DriveChangedCallback -> IO (FunPtr C_DriveChangedCallback)
mk_DriveEjectButtonCallback C_DriveChangedCallback
wrapped'
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
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterDriveEjectButton :: (IsDrive a, MonadIO m) => a -> ((?self :: a) => DriveEjectButtonCallback) -> m SignalHandlerId
afterDriveEjectButton :: forall a (m :: * -> *).
(IsDrive a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
afterDriveEjectButton a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
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 wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
let wrapped' :: C_DriveChangedCallback
wrapped' = (a -> IO ()) -> C_DriveChangedCallback
forall a. GObject a => (a -> IO ()) -> C_DriveChangedCallback
wrap_DriveEjectButtonCallback a -> IO ()
wrapped
FunPtr C_DriveChangedCallback
wrapped'' <- C_DriveChangedCallback -> IO (FunPtr C_DriveChangedCallback)
mk_DriveEjectButtonCallback C_DriveChangedCallback
wrapped'
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
wrapped'' 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
dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gio.Interfaces.Drive::eject-button"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.34/docs/GI-Gio-Interfaces-Drive.html#g:signal:ejectButton"})
#endif
type DriveStopButtonCallback =
IO ()
type C_DriveStopButtonCallback =
Ptr Drive ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_DriveStopButtonCallback :: C_DriveStopButtonCallback -> IO (FunPtr C_DriveStopButtonCallback)
wrap_DriveStopButtonCallback ::
GObject a => (a -> DriveStopButtonCallback) ->
C_DriveStopButtonCallback
wrap_DriveStopButtonCallback :: forall a. GObject a => (a -> IO ()) -> C_DriveChangedCallback
wrap_DriveStopButtonCallback a -> IO ()
gi'cb Ptr Drive
gi'selfPtr Ptr ()
_ = do
Ptr Drive -> (Drive -> IO ()) -> IO ()
forall o b.
(HasCallStack, GObject o) =>
Ptr o -> (o -> IO b) -> IO b
B.ManagedPtr.withNewObject Ptr Drive
gi'selfPtr ((Drive -> IO ()) -> IO ()) -> (Drive -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Drive
gi'self -> a -> IO ()
gi'cb (Drive -> a
forall a b. Coercible a b => a -> b
Coerce.coerce Drive
gi'self)
onDriveStopButton :: (IsDrive a, MonadIO m) => a -> ((?self :: a) => DriveStopButtonCallback) -> m SignalHandlerId
onDriveStopButton :: forall a (m :: * -> *).
(IsDrive a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
onDriveStopButton a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
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 wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
let wrapped' :: C_DriveChangedCallback
wrapped' = (a -> IO ()) -> C_DriveChangedCallback
forall a. GObject a => (a -> IO ()) -> C_DriveChangedCallback
wrap_DriveStopButtonCallback a -> IO ()
wrapped
FunPtr C_DriveChangedCallback
wrapped'' <- C_DriveChangedCallback -> IO (FunPtr C_DriveChangedCallback)
mk_DriveStopButtonCallback C_DriveChangedCallback
wrapped'
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
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterDriveStopButton :: (IsDrive a, MonadIO m) => a -> ((?self :: a) => DriveStopButtonCallback) -> m SignalHandlerId
afterDriveStopButton :: forall a (m :: * -> *).
(IsDrive a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
afterDriveStopButton a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
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 wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
let wrapped' :: C_DriveChangedCallback
wrapped' = (a -> IO ()) -> C_DriveChangedCallback
forall a. GObject a => (a -> IO ()) -> C_DriveChangedCallback
wrap_DriveStopButtonCallback a -> IO ()
wrapped
FunPtr C_DriveChangedCallback
wrapped'' <- C_DriveChangedCallback -> IO (FunPtr C_DriveChangedCallback)
mk_DriveStopButtonCallback C_DriveChangedCallback
wrapped'
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
wrapped'' 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
dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gio.Interfaces.Drive::stop-button"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.34/docs/GI-Gio-Interfaces-Drive.html#g:signal:stopButton"})
#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, DK.Type)])
#endif