{-# LINE 2 "./System/GIO/Volumes/VolumeMonitor.chs" #-}
-- GIMP Toolkit (GTK) Binding for Haskell: binding to gio -*-haskell-*-
--
-- Author : Andy Stewart
-- Created: 30-Apirl-2010
--
-- Copyright (c) 2010 Andy Stewart
--
-- This library is free software: you can redistribute it and/or
-- modify it under the terms of the GNU Lesser General Public License
-- as published by the Free Software Foundation, either version 3 of
-- the License, or (at your option) any later version.
--
-- This library is distributed in the hope that it will be useful,
-- but WITHOUT ANY WARRANTY; without even the implied warranty of
-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
-- Lesser General Public License for more details.
--
-- You should have received a copy of the GNU Lesser General Public
-- License along with this program. If not, see
-- <http:
--
-- GIO, the C library which this Haskell library depends on, is
-- available under LGPL Version 2. The documentation included with
-- this library is based on the original GIO documentation.
--
-- | Maintainer : gtk2hs-devel@lists.sourceforge.net
-- Stability : alpha
-- Portability : portable (depends on GHC)
module System.GIO.Volumes.VolumeMonitor (
-- * Details
--
-- | 'VolumeMonitor' is for listing the user interesting devices and volumes on the computer. In other
-- words, what a file selector or file manager would show in a sidebar.
--
-- 'VolumeMonitor' is not thread-default-context aware, and so should not be used other than from the
-- main thread, with no thread-default-context active.

-- * Types
    VolumeMonitor(..),
    VolumeMonitorClass,

-- * Methods
    volumeMonitorGet,
    volumeMonitorGetConnectedDrives,
    volumeMonitorGetVolumes,
    volumeMonitorGetMounts,
    volumeMonitorGetMountForUUID,
    volumeMonitorGetVolumeForUUID,

-- * Signals
    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" #-}

--------------------
-- Methods
-- | Gets the volume monitor used by gio.
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" #-}

-- | Gets a list of drives connected to the system.
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

-- | Gets a list of the volumes on the system.
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

-- | Gets a list of the mounts on the system.
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

-- | Finds a 'Mount' object by its UUID (see 'mountGetUuid'
volumeMonitorGetMountForUUID :: (VolumeMonitorClass monitor, GlibString string) => monitor
 -> string -- ^ @uuid@ the UUID to look for
 -> IO (Maybe Mount) -- ^ returns a 'Mount' or 'Nothing' if no such mount is available.
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

-- | Finds a 'Volume' object by its UUID (see 'volumeGetUuid')
volumeMonitorGetVolumeForUUID :: (VolumeMonitorClass monitor, GlibString string) => monitor
 -> string -- ^ @uuid@ the UUID to look for
 -> IO (Maybe Volume) -- ^ returns a 'Volume' or 'Nothing' if no such volume is available.
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

--------------------
-- Signals
-- | Emitted when a drive changes.
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")

-- | Emitted when a drive changes.
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")

-- | Emitted when a drive changes.
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")


-- | Emitted when the eject button is pressed on drive.
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")



-- | Emitted when the stop button is pressed on drive.
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")


-- | Emitted when a mount is added.
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")

-- | Emitted when a mount is changed.
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")

-- | Emitted when a mount is about to be removed.
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")

-- | Emitted when a mount is removed.
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")

-- | Emitted when a volume is added.
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")

-- | Emitted when a volume is changed.
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")

-- | Emitted when a volume is removed.
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))))