File: VolumeMonitor.chs

package info (click to toggle)
haskell-gio 0.13.11.0-1
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 432 kB
  • sloc: haskell: 169; makefile: 10
file content (189 lines) | stat: -rw-r--r-- 7,230 bytes parent folder | download | duplicates (5)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
{-# LANGUAGE CPP #-}
--  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://www.gnu.org/licenses/>.
--
--  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,
#if GLIB_CHECK_VERSION(2,18,0)
    vmDriveEjectButton,
#endif
#if GLIB_CHECK_VERSION(2,22,0)
    vmDriveStopButton,
#endif
    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#}
{#import System.GIO.Types#}

{# context lib = "gio" prefix = "g" #}

--------------------
-- Methods
-- | Gets the volume monitor used by gio.
volumeMonitorGet :: IO VolumeMonitor
volumeMonitorGet =
  wrapNewGObject mkVolumeMonitor $
  {#call g_volume_monitor_get #}

-- | Gets a list of drives connected to the system.
volumeMonitorGetConnectedDrives :: VolumeMonitorClass monitor => monitor
 -> IO [Drive]
volumeMonitorGetConnectedDrives monitor = do
  glistPtr <- {#call g_volume_monitor_get_connected_drives #} (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 <- {#call g_volume_monitor_get_volumes #} (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 <- {#call g_volume_monitor_get_mounts #} (toVolumeMonitor monitor)
  mountPtrs <- fromGList glistPtr
  mapM (wrapNewGObject mkDrive . return) 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 monitor uuid =
  maybeNull (wrapNewGObject mkMount) $
  withUTFString uuid $ \ uuidPtr ->
  {#call g_volume_monitor_get_mount_for_uuid#} (toVolumeMonitor monitor) 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 monitor uuid =
  maybeNull (wrapNewGObject mkVolume) $
  withUTFString uuid $ \ uuidPtr ->
  {#call g_volume_monitor_get_volume_for_uuid#} (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")

#if GLIB_CHECK_VERSION(2,18,0)
-- | Emitted when the eject button is pressed on drive.
vmDriveEjectButton :: VolumeMonitorClass monitor => Signal monitor (Drive -> IO ())
vmDriveEjectButton = Signal (connect_OBJECT__NONE "drive-eject-button")
#endif

#if GLIB_CHECK_VERSION(2,22,0)
-- | Emitted when the stop button is pressed on drive.
vmDriveStopButton :: VolumeMonitorClass monitor => Signal monitor (Drive -> IO ())
vmDriveStopButton = Signal (connect_OBJECT__NONE "drive-stop-button")
#endif

-- | 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")