{-# 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 =
  wrapNewGObject mkVolumeMonitor $
  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 monitor = do
  glistPtr <- (\(VolumeMonitor arg1) -> withForeignPtr arg1 $ \argPtr1 ->g_volume_monitor_get_connected_drives argPtr1) (toVolumeMonitor monitor)
  drivePtrs <- fromGList glistPtr
  mapM (wrapNewGObject mkDrive . return) drivePtrs

-- | Gets a list of the volumes on the system.
volumeMonitorGetVolumes :: VolumeMonitorClass monitor => monitor
 -> IO [Drive]
volumeMonitorGetVolumes monitor = do
  glistPtr <- (\(VolumeMonitor arg1) -> withForeignPtr arg1 $ \argPtr1 ->g_volume_monitor_get_volumes argPtr1) (toVolumeMonitor monitor)
  volumePtrs <- fromGList glistPtr
  mapM (wrapNewGObject mkDrive . return) volumePtrs

-- | Gets a list of the mounts on the system.
volumeMonitorGetMounts :: VolumeMonitorClass monitor => monitor
 -> IO [Drive]
volumeMonitorGetMounts monitor = do
  glistPtr <- (\(VolumeMonitor arg1) -> withForeignPtr arg1 $ \argPtr1 ->g_volume_monitor_get_mounts argPtr1) (toVolumeMonitor monitor)
  mountPtrs <- fromGList glistPtr
  mapM (wrapNewGObject mkDrive . return) mountPtrs

-- | Finds a 'Mount' object by its UUID (see 'mountGetUuid'
volumeMonitorGetMountForUUID :: VolumeMonitorClass monitor => monitor
 -> String -- ^ @uuid@ the UUID to look for
 -> IO (Maybe Mount) -- ^ returns a 'Mount' or 'Nothing' if no such mount is available.
volumeMonitorGetMountForUUID monitor uuid =
  maybeNull (wrapNewGObject mkMount) $
  withUTFString uuid $ \ uuidPtr ->
  (\(VolumeMonitor arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->g_volume_monitor_get_mount_for_uuid argPtr1 arg2) (toVolumeMonitor monitor) uuidPtr

-- | Finds a 'Volume' object by its UUID (see 'volumeGetUuid')
volumeMonitorGetVolumeForUUID :: VolumeMonitorClass monitor => monitor
 -> String -- ^ @uuid@ the UUID to look for
 -> IO (Maybe Volume) -- ^ returns a 'Volume' or 'Nothing' if no such volume is available.
volumeMonitorGetVolumeForUUID monitor uuid =
  maybeNull (wrapNewGObject mkVolume) $
  withUTFString uuid $ \ uuidPtr ->
  (\(VolumeMonitor arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->g_volume_monitor_get_volume_for_uuid argPtr1 arg2) (toVolumeMonitor monitor) uuidPtr

--------------------
-- Signals
-- | Emitted when a drive changes.
vmDriveChanged :: VolumeMonitorClass monitor => Signal monitor (Drive -> IO ())
vmDriveChanged = Signal (connect_OBJECT__NONE "drive-changed")

-- | Emitted when a drive changes.
vmDriveConnected :: VolumeMonitorClass monitor => Signal monitor (Drive -> IO ())
vmDriveConnected = Signal (connect_OBJECT__NONE "drive-connected")

-- | Emitted when a drive changes.
vmDriveDisconnected :: VolumeMonitorClass monitor => Signal monitor (Drive -> IO ())
vmDriveDisconnected = Signal (connect_OBJECT__NONE "drive-disconnected")


-- | Emitted when the eject button is pressed on drive.
vmDriveEjectButton :: VolumeMonitorClass monitor => Signal monitor (Drive -> IO ())
vmDriveEjectButton = Signal (connect_OBJECT__NONE "drive-eject-button")



-- | Emitted when the stop button is pressed on drive.
vmDriveStopButton :: VolumeMonitorClass monitor => Signal monitor (Drive -> IO ())
vmDriveStopButton = Signal (connect_OBJECT__NONE "drive-stop-button")


-- | Emitted when a mount is added.
vmMountAdded :: VolumeMonitorClass monitor => Signal monitor (Mount -> IO ())
vmMountAdded = Signal (connect_OBJECT__NONE "mount-added")

-- | Emitted when a mount is changed.
vmMountChanged :: VolumeMonitorClass monitor => Signal monitor (Mount -> IO ())
vmMountChanged = Signal (connect_OBJECT__NONE "mount-changed")

-- | Emitted when a mount is about to be removed.
vmMountPreUnmount :: VolumeMonitorClass monitor => Signal monitor (Mount -> IO ())
vmMountPreUnmount = Signal (connect_OBJECT__NONE "mount-pre-unmount")

-- | Emitted when a mount is removed.
vmMountRemoved :: VolumeMonitorClass monitor => Signal monitor (Mount -> IO ())
vmMountRemoved = Signal (connect_OBJECT__NONE "mount-removed")

-- | Emitted when a volume is added.
vmVolumeAdded :: VolumeMonitorClass monitor => Signal monitor (Volume -> IO ())
vmVolumeAdded = Signal (connect_OBJECT__NONE "volume-added")

-- | Emitted when a volume is changed.
vmVolumeChanged :: VolumeMonitorClass monitor => Signal monitor (Volume -> IO ())
vmVolumeChanged = Signal (connect_OBJECT__NONE "volume-changed")

-- | Emitted when a volume is removed.
vmVolumeRemoved :: VolumeMonitorClass monitor => Signal monitor (Volume -> IO ())
vmVolumeRemoved = Signal (connect_OBJECT__NONE "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))))