{-# LINE 2 "./System/GIO/Volumes/VolumeMonitor.chs" #-}
module System.GIO.Volumes.VolumeMonitor (
VolumeMonitor(..),
VolumeMonitorClass,
volumeMonitorGet,
volumeMonitorGetConnectedDrives,
volumeMonitorGetVolumes,
volumeMonitorGetMounts,
volumeMonitorGetMountForUUID,
volumeMonitorGetVolumeForUUID,
vmDriveChanged,
vmDriveConnected,
vmDriveDisconnected,
vmDriveEjectButton,
vmDriveStopButton,
vmMountAdded,
vmMountChanged,
vmMountPreUnmount,
vmMountRemoved,
vmVolumeAdded,
vmVolumeChanged,
vmVolumeRemoved,
) where
import Control.Monad
import System.GIO.Enums
import System.Glib.Attributes
import System.Glib.FFI
import System.Glib.Flags
import System.Glib.GError
import System.Glib.GList
import System.Glib.GObject
import System.Glib.Properties
import System.Glib.Signals
import System.Glib.UTFString
import System.GIO.Signals
{-# LINE 82 "./System/GIO/Volumes/VolumeMonitor.chs" #-}
import System.GIO.Types
{-# LINE 83 "./System/GIO/Volumes/VolumeMonitor.chs" #-}
{-# LINE 85 "./System/GIO/Volumes/VolumeMonitor.chs" #-}
volumeMonitorGet :: IO VolumeMonitor
volumeMonitorGet :: IO VolumeMonitor
volumeMonitorGet =
(ForeignPtr VolumeMonitor -> VolumeMonitor,
FinalizerPtr VolumeMonitor)
-> IO (Ptr VolumeMonitor) -> IO VolumeMonitor
forall obj.
GObjectClass obj =>
(ForeignPtr obj -> obj, FinalizerPtr obj) -> IO (Ptr obj) -> IO obj
wrapNewGObject (ForeignPtr VolumeMonitor -> VolumeMonitor,
FinalizerPtr VolumeMonitor)
forall {a}.
(ForeignPtr VolumeMonitor -> VolumeMonitor, FinalizerPtr a)
mkVolumeMonitor (IO (Ptr VolumeMonitor) -> IO VolumeMonitor)
-> IO (Ptr VolumeMonitor) -> IO VolumeMonitor
forall a b. (a -> b) -> a -> b
$
IO (Ptr VolumeMonitor)
g_volume_monitor_get
{-# LINE 93 "./System/GIO/Volumes/VolumeMonitor.chs" #-}
volumeMonitorGetConnectedDrives :: VolumeMonitorClass monitor => monitor
-> IO [Drive]
volumeMonitorGetConnectedDrives :: forall monitor. VolumeMonitorClass monitor => monitor -> IO [Drive]
volumeMonitorGetConnectedDrives monitor
monitor = do
Ptr ()
glistPtr <- (\(VolumeMonitor ForeignPtr VolumeMonitor
arg1) -> ForeignPtr VolumeMonitor
-> (Ptr VolumeMonitor -> IO (Ptr ())) -> IO (Ptr ())
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr VolumeMonitor
arg1 ((Ptr VolumeMonitor -> IO (Ptr ())) -> IO (Ptr ()))
-> (Ptr VolumeMonitor -> IO (Ptr ())) -> IO (Ptr ())
forall a b. (a -> b) -> a -> b
$ \Ptr VolumeMonitor
argPtr1 ->Ptr VolumeMonitor -> IO (Ptr ())
g_volume_monitor_get_connected_drives Ptr VolumeMonitor
argPtr1) (monitor -> VolumeMonitor
forall o. VolumeMonitorClass o => o -> VolumeMonitor
toVolumeMonitor monitor
monitor)
[Ptr Drive]
drivePtrs <- Ptr () -> IO [Ptr Drive]
forall a. Ptr () -> IO [Ptr a]
fromGList Ptr ()
glistPtr
(Ptr Drive -> IO Drive) -> [Ptr Drive] -> IO [Drive]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM ((ForeignPtr Drive -> Drive, FinalizerPtr Drive)
-> IO (Ptr Drive) -> IO Drive
forall obj.
GObjectClass obj =>
(ForeignPtr obj -> obj, FinalizerPtr obj) -> IO (Ptr obj) -> IO obj
wrapNewGObject (ForeignPtr Drive -> Drive, FinalizerPtr Drive)
forall {a}. (ForeignPtr Drive -> Drive, FinalizerPtr a)
mkDrive (IO (Ptr Drive) -> IO Drive)
-> (Ptr Drive -> IO (Ptr Drive)) -> Ptr Drive -> IO Drive
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr Drive -> IO (Ptr Drive)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return) [Ptr Drive]
drivePtrs
volumeMonitorGetVolumes :: VolumeMonitorClass monitor => monitor
-> IO [Drive]
volumeMonitorGetVolumes :: forall monitor. VolumeMonitorClass monitor => monitor -> IO [Drive]
volumeMonitorGetVolumes monitor
monitor = do
Ptr ()
glistPtr <- (\(VolumeMonitor ForeignPtr VolumeMonitor
arg1) -> ForeignPtr VolumeMonitor
-> (Ptr VolumeMonitor -> IO (Ptr ())) -> IO (Ptr ())
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr VolumeMonitor
arg1 ((Ptr VolumeMonitor -> IO (Ptr ())) -> IO (Ptr ()))
-> (Ptr VolumeMonitor -> IO (Ptr ())) -> IO (Ptr ())
forall a b. (a -> b) -> a -> b
$ \Ptr VolumeMonitor
argPtr1 ->Ptr VolumeMonitor -> IO (Ptr ())
g_volume_monitor_get_volumes Ptr VolumeMonitor
argPtr1) (monitor -> VolumeMonitor
forall o. VolumeMonitorClass o => o -> VolumeMonitor
toVolumeMonitor monitor
monitor)
[Ptr Drive]
volumePtrs <- Ptr () -> IO [Ptr Drive]
forall a. Ptr () -> IO [Ptr a]
fromGList Ptr ()
glistPtr
(Ptr Drive -> IO Drive) -> [Ptr Drive] -> IO [Drive]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM ((ForeignPtr Drive -> Drive, FinalizerPtr Drive)
-> IO (Ptr Drive) -> IO Drive
forall obj.
GObjectClass obj =>
(ForeignPtr obj -> obj, FinalizerPtr obj) -> IO (Ptr obj) -> IO obj
wrapNewGObject (ForeignPtr Drive -> Drive, FinalizerPtr Drive)
forall {a}. (ForeignPtr Drive -> Drive, FinalizerPtr a)
mkDrive (IO (Ptr Drive) -> IO Drive)
-> (Ptr Drive -> IO (Ptr Drive)) -> Ptr Drive -> IO Drive
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr Drive -> IO (Ptr Drive)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return) [Ptr Drive]
volumePtrs
volumeMonitorGetMounts :: VolumeMonitorClass monitor => monitor
-> IO [Drive]
volumeMonitorGetMounts :: forall monitor. VolumeMonitorClass monitor => monitor -> IO [Drive]
volumeMonitorGetMounts monitor
monitor = do
Ptr ()
glistPtr <- (\(VolumeMonitor ForeignPtr VolumeMonitor
arg1) -> ForeignPtr VolumeMonitor
-> (Ptr VolumeMonitor -> IO (Ptr ())) -> IO (Ptr ())
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr VolumeMonitor
arg1 ((Ptr VolumeMonitor -> IO (Ptr ())) -> IO (Ptr ()))
-> (Ptr VolumeMonitor -> IO (Ptr ())) -> IO (Ptr ())
forall a b. (a -> b) -> a -> b
$ \Ptr VolumeMonitor
argPtr1 ->Ptr VolumeMonitor -> IO (Ptr ())
g_volume_monitor_get_mounts Ptr VolumeMonitor
argPtr1) (monitor -> VolumeMonitor
forall o. VolumeMonitorClass o => o -> VolumeMonitor
toVolumeMonitor monitor
monitor)
[Ptr Drive]
mountPtrs <- Ptr () -> IO [Ptr Drive]
forall a. Ptr () -> IO [Ptr a]
fromGList Ptr ()
glistPtr
(Ptr Drive -> IO Drive) -> [Ptr Drive] -> IO [Drive]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM ((ForeignPtr Drive -> Drive, FinalizerPtr Drive)
-> IO (Ptr Drive) -> IO Drive
forall obj.
GObjectClass obj =>
(ForeignPtr obj -> obj, FinalizerPtr obj) -> IO (Ptr obj) -> IO obj
wrapNewGObject (ForeignPtr Drive -> Drive, FinalizerPtr Drive)
forall {a}. (ForeignPtr Drive -> Drive, FinalizerPtr a)
mkDrive (IO (Ptr Drive) -> IO Drive)
-> (Ptr Drive -> IO (Ptr Drive)) -> Ptr Drive -> IO Drive
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr Drive -> IO (Ptr Drive)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return) [Ptr Drive]
mountPtrs
volumeMonitorGetMountForUUID :: (VolumeMonitorClass monitor, GlibString string) => monitor
-> string
-> IO (Maybe Mount)
volumeMonitorGetMountForUUID :: forall monitor string.
(VolumeMonitorClass monitor, GlibString string) =>
monitor -> string -> IO (Maybe Mount)
volumeMonitorGetMountForUUID monitor
monitor string
uuid =
(IO (Ptr Mount) -> IO Mount) -> IO (Ptr Mount) -> IO (Maybe Mount)
forall a. (IO (Ptr a) -> IO a) -> IO (Ptr a) -> IO (Maybe a)
maybeNull ((ForeignPtr Mount -> Mount, FinalizerPtr Mount)
-> IO (Ptr Mount) -> IO Mount
forall obj.
GObjectClass obj =>
(ForeignPtr obj -> obj, FinalizerPtr obj) -> IO (Ptr obj) -> IO obj
wrapNewGObject (ForeignPtr Mount -> Mount, FinalizerPtr Mount)
forall {a}. (ForeignPtr Mount -> Mount, FinalizerPtr a)
mkMount) (IO (Ptr Mount) -> IO (Maybe Mount))
-> IO (Ptr Mount) -> IO (Maybe Mount)
forall a b. (a -> b) -> a -> b
$
string -> (CString -> IO (Ptr Mount)) -> IO (Ptr Mount)
forall a. string -> (CString -> IO a) -> IO a
forall s a. GlibString s => s -> (CString -> IO a) -> IO a
withUTFString string
uuid ((CString -> IO (Ptr Mount)) -> IO (Ptr Mount))
-> (CString -> IO (Ptr Mount)) -> IO (Ptr Mount)
forall a b. (a -> b) -> a -> b
$ \ CString
uuidPtr ->
(\(VolumeMonitor ForeignPtr VolumeMonitor
arg1) CString
arg2 -> ForeignPtr VolumeMonitor
-> (Ptr VolumeMonitor -> IO (Ptr Mount)) -> IO (Ptr Mount)
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr VolumeMonitor
arg1 ((Ptr VolumeMonitor -> IO (Ptr Mount)) -> IO (Ptr Mount))
-> (Ptr VolumeMonitor -> IO (Ptr Mount)) -> IO (Ptr Mount)
forall a b. (a -> b) -> a -> b
$ \Ptr VolumeMonitor
argPtr1 ->Ptr VolumeMonitor -> CString -> IO (Ptr Mount)
g_volume_monitor_get_mount_for_uuid Ptr VolumeMonitor
argPtr1 CString
arg2) (monitor -> VolumeMonitor
forall o. VolumeMonitorClass o => o -> VolumeMonitor
toVolumeMonitor monitor
monitor) CString
uuidPtr
volumeMonitorGetVolumeForUUID :: (VolumeMonitorClass monitor, GlibString string) => monitor
-> string
-> IO (Maybe Volume)
volumeMonitorGetVolumeForUUID :: forall monitor string.
(VolumeMonitorClass monitor, GlibString string) =>
monitor -> string -> IO (Maybe Volume)
volumeMonitorGetVolumeForUUID monitor
monitor string
uuid =
(IO (Ptr Volume) -> IO Volume)
-> IO (Ptr Volume) -> IO (Maybe Volume)
forall a. (IO (Ptr a) -> IO a) -> IO (Ptr a) -> IO (Maybe a)
maybeNull ((ForeignPtr Volume -> Volume, FinalizerPtr Volume)
-> IO (Ptr Volume) -> IO Volume
forall obj.
GObjectClass obj =>
(ForeignPtr obj -> obj, FinalizerPtr obj) -> IO (Ptr obj) -> IO obj
wrapNewGObject (ForeignPtr Volume -> Volume, FinalizerPtr Volume)
forall {a}. (ForeignPtr Volume -> Volume, FinalizerPtr a)
mkVolume) (IO (Ptr Volume) -> IO (Maybe Volume))
-> IO (Ptr Volume) -> IO (Maybe Volume)
forall a b. (a -> b) -> a -> b
$
string -> (CString -> IO (Ptr Volume)) -> IO (Ptr Volume)
forall a. string -> (CString -> IO a) -> IO a
forall s a. GlibString s => s -> (CString -> IO a) -> IO a
withUTFString string
uuid ((CString -> IO (Ptr Volume)) -> IO (Ptr Volume))
-> (CString -> IO (Ptr Volume)) -> IO (Ptr Volume)
forall a b. (a -> b) -> a -> b
$ \ CString
uuidPtr ->
(\(VolumeMonitor ForeignPtr VolumeMonitor
arg1) CString
arg2 -> ForeignPtr VolumeMonitor
-> (Ptr VolumeMonitor -> IO (Ptr Volume)) -> IO (Ptr Volume)
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr VolumeMonitor
arg1 ((Ptr VolumeMonitor -> IO (Ptr Volume)) -> IO (Ptr Volume))
-> (Ptr VolumeMonitor -> IO (Ptr Volume)) -> IO (Ptr Volume)
forall a b. (a -> b) -> a -> b
$ \Ptr VolumeMonitor
argPtr1 ->Ptr VolumeMonitor -> CString -> IO (Ptr Volume)
g_volume_monitor_get_volume_for_uuid Ptr VolumeMonitor
argPtr1 CString
arg2) (monitor -> VolumeMonitor
forall o. VolumeMonitorClass o => o -> VolumeMonitor
toVolumeMonitor monitor
monitor) CString
uuidPtr
vmDriveChanged :: VolumeMonitorClass monitor => Signal monitor (Drive -> IO ())
vmDriveChanged :: forall monitor.
VolumeMonitorClass monitor =>
Signal monitor (Drive -> IO ())
vmDriveChanged = (Bool -> monitor -> (Drive -> IO ()) -> IO (ConnectId monitor))
-> Signal monitor (Drive -> IO ())
forall object handler.
(Bool -> object -> handler -> IO (ConnectId object))
-> Signal object handler
Signal (SignalName
-> Bool -> monitor -> (Drive -> IO ()) -> IO (ConnectId monitor)
forall a' obj.
(GObjectClass a', GObjectClass obj) =>
SignalName -> Bool -> obj -> (a' -> IO ()) -> IO (ConnectId obj)
connect_OBJECT__NONE SignalName
"drive-changed")
vmDriveConnected :: VolumeMonitorClass monitor => Signal monitor (Drive -> IO ())
vmDriveConnected :: forall monitor.
VolumeMonitorClass monitor =>
Signal monitor (Drive -> IO ())
vmDriveConnected = (Bool -> monitor -> (Drive -> IO ()) -> IO (ConnectId monitor))
-> Signal monitor (Drive -> IO ())
forall object handler.
(Bool -> object -> handler -> IO (ConnectId object))
-> Signal object handler
Signal (SignalName
-> Bool -> monitor -> (Drive -> IO ()) -> IO (ConnectId monitor)
forall a' obj.
(GObjectClass a', GObjectClass obj) =>
SignalName -> Bool -> obj -> (a' -> IO ()) -> IO (ConnectId obj)
connect_OBJECT__NONE SignalName
"drive-connected")
vmDriveDisconnected :: VolumeMonitorClass monitor => Signal monitor (Drive -> IO ())
vmDriveDisconnected :: forall monitor.
VolumeMonitorClass monitor =>
Signal monitor (Drive -> IO ())
vmDriveDisconnected = (Bool -> monitor -> (Drive -> IO ()) -> IO (ConnectId monitor))
-> Signal monitor (Drive -> IO ())
forall object handler.
(Bool -> object -> handler -> IO (ConnectId object))
-> Signal object handler
Signal (SignalName
-> Bool -> monitor -> (Drive -> IO ()) -> IO (ConnectId monitor)
forall a' obj.
(GObjectClass a', GObjectClass obj) =>
SignalName -> Bool -> obj -> (a' -> IO ()) -> IO (ConnectId obj)
connect_OBJECT__NONE SignalName
"drive-disconnected")
vmDriveEjectButton :: VolumeMonitorClass monitor => Signal monitor (Drive -> IO ())
vmDriveEjectButton :: forall monitor.
VolumeMonitorClass monitor =>
Signal monitor (Drive -> IO ())
vmDriveEjectButton = (Bool -> monitor -> (Drive -> IO ()) -> IO (ConnectId monitor))
-> Signal monitor (Drive -> IO ())
forall object handler.
(Bool -> object -> handler -> IO (ConnectId object))
-> Signal object handler
Signal (SignalName
-> Bool -> monitor -> (Drive -> IO ()) -> IO (ConnectId monitor)
forall a' obj.
(GObjectClass a', GObjectClass obj) =>
SignalName -> Bool -> obj -> (a' -> IO ()) -> IO (ConnectId obj)
connect_OBJECT__NONE SignalName
"drive-eject-button")
vmDriveStopButton :: VolumeMonitorClass monitor => Signal monitor (Drive -> IO ())
vmDriveStopButton :: forall monitor.
VolumeMonitorClass monitor =>
Signal monitor (Drive -> IO ())
vmDriveStopButton = (Bool -> monitor -> (Drive -> IO ()) -> IO (ConnectId monitor))
-> Signal monitor (Drive -> IO ())
forall object handler.
(Bool -> object -> handler -> IO (ConnectId object))
-> Signal object handler
Signal (SignalName
-> Bool -> monitor -> (Drive -> IO ()) -> IO (ConnectId monitor)
forall a' obj.
(GObjectClass a', GObjectClass obj) =>
SignalName -> Bool -> obj -> (a' -> IO ()) -> IO (ConnectId obj)
connect_OBJECT__NONE SignalName
"drive-stop-button")
vmMountAdded :: VolumeMonitorClass monitor => Signal monitor (Mount -> IO ())
vmMountAdded :: forall monitor.
VolumeMonitorClass monitor =>
Signal monitor (Mount -> IO ())
vmMountAdded = (Bool -> monitor -> (Mount -> IO ()) -> IO (ConnectId monitor))
-> Signal monitor (Mount -> IO ())
forall object handler.
(Bool -> object -> handler -> IO (ConnectId object))
-> Signal object handler
Signal (SignalName
-> Bool -> monitor -> (Mount -> IO ()) -> IO (ConnectId monitor)
forall a' obj.
(GObjectClass a', GObjectClass obj) =>
SignalName -> Bool -> obj -> (a' -> IO ()) -> IO (ConnectId obj)
connect_OBJECT__NONE SignalName
"mount-added")
vmMountChanged :: VolumeMonitorClass monitor => Signal monitor (Mount -> IO ())
vmMountChanged :: forall monitor.
VolumeMonitorClass monitor =>
Signal monitor (Mount -> IO ())
vmMountChanged = (Bool -> monitor -> (Mount -> IO ()) -> IO (ConnectId monitor))
-> Signal monitor (Mount -> IO ())
forall object handler.
(Bool -> object -> handler -> IO (ConnectId object))
-> Signal object handler
Signal (SignalName
-> Bool -> monitor -> (Mount -> IO ()) -> IO (ConnectId monitor)
forall a' obj.
(GObjectClass a', GObjectClass obj) =>
SignalName -> Bool -> obj -> (a' -> IO ()) -> IO (ConnectId obj)
connect_OBJECT__NONE SignalName
"mount-changed")
vmMountPreUnmount :: VolumeMonitorClass monitor => Signal monitor (Mount -> IO ())
vmMountPreUnmount :: forall monitor.
VolumeMonitorClass monitor =>
Signal monitor (Mount -> IO ())
vmMountPreUnmount = (Bool -> monitor -> (Mount -> IO ()) -> IO (ConnectId monitor))
-> Signal monitor (Mount -> IO ())
forall object handler.
(Bool -> object -> handler -> IO (ConnectId object))
-> Signal object handler
Signal (SignalName
-> Bool -> monitor -> (Mount -> IO ()) -> IO (ConnectId monitor)
forall a' obj.
(GObjectClass a', GObjectClass obj) =>
SignalName -> Bool -> obj -> (a' -> IO ()) -> IO (ConnectId obj)
connect_OBJECT__NONE SignalName
"mount-pre-unmount")
vmMountRemoved :: VolumeMonitorClass monitor => Signal monitor (Mount -> IO ())
vmMountRemoved :: forall monitor.
VolumeMonitorClass monitor =>
Signal monitor (Mount -> IO ())
vmMountRemoved = (Bool -> monitor -> (Mount -> IO ()) -> IO (ConnectId monitor))
-> Signal monitor (Mount -> IO ())
forall object handler.
(Bool -> object -> handler -> IO (ConnectId object))
-> Signal object handler
Signal (SignalName
-> Bool -> monitor -> (Mount -> IO ()) -> IO (ConnectId monitor)
forall a' obj.
(GObjectClass a', GObjectClass obj) =>
SignalName -> Bool -> obj -> (a' -> IO ()) -> IO (ConnectId obj)
connect_OBJECT__NONE SignalName
"mount-removed")
vmVolumeAdded :: VolumeMonitorClass monitor => Signal monitor (Volume -> IO ())
vmVolumeAdded :: forall monitor.
VolumeMonitorClass monitor =>
Signal monitor (Volume -> IO ())
vmVolumeAdded = (Bool -> monitor -> (Volume -> IO ()) -> IO (ConnectId monitor))
-> Signal monitor (Volume -> IO ())
forall object handler.
(Bool -> object -> handler -> IO (ConnectId object))
-> Signal object handler
Signal (SignalName
-> Bool -> monitor -> (Volume -> IO ()) -> IO (ConnectId monitor)
forall a' obj.
(GObjectClass a', GObjectClass obj) =>
SignalName -> Bool -> obj -> (a' -> IO ()) -> IO (ConnectId obj)
connect_OBJECT__NONE SignalName
"volume-added")
vmVolumeChanged :: VolumeMonitorClass monitor => Signal monitor (Volume -> IO ())
vmVolumeChanged :: forall monitor.
VolumeMonitorClass monitor =>
Signal monitor (Volume -> IO ())
vmVolumeChanged = (Bool -> monitor -> (Volume -> IO ()) -> IO (ConnectId monitor))
-> Signal monitor (Volume -> IO ())
forall object handler.
(Bool -> object -> handler -> IO (ConnectId object))
-> Signal object handler
Signal (SignalName
-> Bool -> monitor -> (Volume -> IO ()) -> IO (ConnectId monitor)
forall a' obj.
(GObjectClass a', GObjectClass obj) =>
SignalName -> Bool -> obj -> (a' -> IO ()) -> IO (ConnectId obj)
connect_OBJECT__NONE SignalName
"volume-changed")
vmVolumeRemoved :: VolumeMonitorClass monitor => Signal monitor (Volume -> IO ())
vmVolumeRemoved :: forall monitor.
VolumeMonitorClass monitor =>
Signal monitor (Volume -> IO ())
vmVolumeRemoved = (Bool -> monitor -> (Volume -> IO ()) -> IO (ConnectId monitor))
-> Signal monitor (Volume -> IO ())
forall object handler.
(Bool -> object -> handler -> IO (ConnectId object))
-> Signal object handler
Signal (SignalName
-> Bool -> monitor -> (Volume -> IO ()) -> IO (ConnectId monitor)
forall a' obj.
(GObjectClass a', GObjectClass obj) =>
SignalName -> Bool -> obj -> (a' -> IO ()) -> IO (ConnectId obj)
connect_OBJECT__NONE SignalName
"volume-removed")
foreign import ccall safe "g_volume_monitor_get"
g_volume_monitor_get :: (IO (Ptr VolumeMonitor))
foreign import ccall safe "g_volume_monitor_get_connected_drives"
g_volume_monitor_get_connected_drives :: ((Ptr VolumeMonitor) -> (IO (Ptr ())))
foreign import ccall safe "g_volume_monitor_get_volumes"
g_volume_monitor_get_volumes :: ((Ptr VolumeMonitor) -> (IO (Ptr ())))
foreign import ccall safe "g_volume_monitor_get_mounts"
g_volume_monitor_get_mounts :: ((Ptr VolumeMonitor) -> (IO (Ptr ())))
foreign import ccall safe "g_volume_monitor_get_mount_for_uuid"
g_volume_monitor_get_mount_for_uuid :: ((Ptr VolumeMonitor) -> ((Ptr CChar) -> (IO (Ptr Mount))))
foreign import ccall safe "g_volume_monitor_get_volume_for_uuid"
g_volume_monitor_get_volume_for_uuid :: ((Ptr VolumeMonitor) -> ((Ptr CChar) -> (IO (Ptr Volume))))