Revision 3c1915df

b/Makefile.am
57 57
HTOOLS_DIRS = \
58 58
	htools \
59 59
	htools/Ganeti \
60
	htools/Ganeti/Block \
61
	htools/Ganeti/Block/Drbd \
60 62
	htools/Ganeti/Confd \
61 63
	htools/Ganeti/HTools \
62 64
	htools/Ganeti/HTools/Backend \
......
108 110
	$(APIDOC_DIR) \
109 111
	$(APIDOC_HS_DIR) \
110 112
	$(APIDOC_HS_DIR)/Ganeti \
113
	$(APIDOC_HS_DIR)/Ganeti/Block \
114
	$(APIDOC_HS_DIR)/Ganeti/Block/Drbd \
111 115
	$(APIDOC_HS_DIR)/Ganeti/Confd \
112 116
	$(APIDOC_HS_DIR)/Ganeti/HTools \
113 117
	$(APIDOC_HS_DIR)/Ganeti/HTools/Backend \
......
426 430
	$(patsubst htools.%,--exclude Test.%,$(subst /,.,$(patsubst %.hs,%, $(HS_LIB_SRCS))))
427 431

  
428 432
HS_LIB_SRCS = \
433
	htools/Ganeti/Block/Drbd/Types.hs \
434
	htools/Ganeti/Block/Drbd/Parser.hs \
429 435
	htools/Ganeti/BasicTypes.hs \
430 436
	htools/Ganeti/Common.hs \
431 437
	htools/Ganeti/Compat.hs \
......
1618 1624
	rm -rf $(APIDOC_HS_DIR)/*
1619 1625
	@mkdir_p@ $(APIDOC_HS_DIR)/Ganeti/HTools/Backend
1620 1626
	@mkdir_p@ $(APIDOC_HS_DIR)/Ganeti/HTools/Program
1627
	@mkdir_p@ $(APIDOC_HS_DIR)/Ganeti/Block
1628
	@mkdir_p@ $(APIDOC_HS_DIR)/Ganeti/Block/Drbd
1621 1629
	@mkdir_p@ $(APIDOC_HS_DIR)/Ganeti/Confd
1622 1630
	@mkdir_p@ $(APIDOC_HS_DIR)/Ganeti/Query
1623 1631
	$(HSCOLOUR) -print-css > $(APIDOC_HS_DIR)/Ganeti/hscolour.css
b/htools/Ganeti/Block/Drbd/Parser.hs
1
{-# LANGUAGE OverloadedStrings #-}
2
{-| DRBD proc file parser
3

  
4
This module holds the definition of the parser that extracts status
5
information from the DRBD proc file.
6

  
7
-}
8
{-
9

  
10
Copyright (C) 2012 Google Inc.
11

  
12
This program is free software; you can redistribute it and/or modify
13
it under the terms of the GNU General Public License as published by
14
the Free Software Foundation; either version 2 of the License, or
15
(at your option) any later version.
16

  
17
This program is distributed in the hope that it will be useful, but
18
WITHOUT ANY WARRANTY; without even the implied warranty of
19
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
20
General Public License for more details.
21

  
22
You should have received a copy of the GNU General Public License
23
along with this program; if not, write to the Free Software
24
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
25
02110-1301, USA.
26

  
27
-}
28
module Ganeti.Block.Drbd.Parser (drbdStatusParser, commaIntParser) where
29

  
30
import Control.Applicative ((<*>), (*>), (<*), (<$>), (<|>), pure)
31
import qualified Data.Attoparsec.Text as A
32
import qualified Data.Attoparsec.Combinator as AC
33
import Data.Attoparsec.Text (Parser)
34
import Data.Text (Text, unpack)
35

  
36
import Ganeti.Block.Drbd.Types
37

  
38
-- | Our own space-skipping function, because A.skipSpace also skips
39
-- newline characters. It skips ZERO or more spaces, so it does not
40
-- fail if there are no spaces.
41
skipSpaces :: Parser ()
42
skipSpaces = A.skipWhile A.isHorizontalSpace
43

  
44
-- | Skips spaces and the given string, then executes a parser and
45
-- returns its result.
46
skipSpacesAndString :: Text -> Parser a -> Parser a
47
skipSpacesAndString s parser =
48
  skipSpaces
49
  *> A.string s
50
  *> parser
51

  
52
-- | Predicate verifying (potentially bad) end of lines
53
isBadEndOfLine :: Char -> Bool
54
isBadEndOfLine c = (c == '\0') || A.isEndOfLine c
55

  
56
-- | Takes a parser and returns it with the content wrapped in a Maybe
57
-- object. The resulting parser never fails, but contains Nothing if
58
-- it couldn't properly parse the string.
59
optional :: Parser a -> Parser (Maybe a)
60
optional parser = (Just <$> parser) <|> pure Nothing
61

  
62
-- | The parser for a whole DRBD status file.
63
drbdStatusParser :: Parser DRBDStatus
64
drbdStatusParser =
65
  DRBDStatus <$> versionInfoParser
66
             <*> deviceParser `AC.manyTill` A.endOfInput
67

  
68
-- | The parser for the version information lines.
69
versionInfoParser :: Parser VersionInfo
70
versionInfoParser =
71
  VersionInfo
72
    <$> optional versionP
73
    <*> optional apiP
74
    <*> optional protoP
75
    <*> optional srcVersion
76
    <*> (fmap unpack <$> optional gh)
77
    <*> (fmap unpack <$> optional builder)
78
    where versionP =
79
            A.string "version:"
80
            *> skipSpaces
81
            *> fmap unpack (A.takeWhile $ not . A.isHorizontalSpace)
82
          apiP =
83
            skipSpacesAndString "(api:" . fmap unpack $ A.takeWhile (/= '/')
84
          protoP =
85
            A.string "/proto:"
86
            *> fmap Data.Text.unpack (A.takeWhile (/= ')'))
87
            <* A.takeTill A.isEndOfLine <* A.endOfLine
88
          srcVersion =
89
            A.string "srcversion:"
90
            *> AC.skipMany1 A.space
91
            *> fmap unpack (A.takeTill A.isEndOfLine)
92
            <* A.endOfLine
93
          gh =
94
            A.string "GIT-hash:"
95
            *> skipSpaces
96
            *> A.takeWhile (not . A.isHorizontalSpace)
97
          builder =
98
            skipSpacesAndString "build by" $
99
              skipSpaces
100
              *> A.takeTill A.isEndOfLine
101
              <* A.endOfLine
102

  
103
-- | The parser for a (multi-line) string representing a device.
104
deviceParser :: Parser DeviceInfo
105
deviceParser = do
106
  deviceNum <- skipSpaces *> A.decimal <* A.char ':'
107
  cs <- skipSpacesAndString "cs:" connectionStateParser
108
  if cs == Unconfigured
109
    then do
110
      _ <- additionalEOL
111
      return $ UnconfiguredDevice deviceNum
112
    else do
113
      ro <- skipSpaces *> skipRoleString *> localRemoteParser roleParser
114
      ds <- skipSpacesAndString "ds:" $ localRemoteParser diskStateParser
115
      replicProtocol <- A.space *> A.anyChar
116
      io <- skipSpaces *> ioFlagsParser <* A.skipWhile isBadEndOfLine
117
      perfIndicators <- performanceIndicatorsParser
118
      syncS <- conditionalSyncStatusParser cs
119
      reS <- optional resyncParser
120
      act <- optional actLogParser
121
      _ <- additionalEOL
122
      return $ DeviceInfo deviceNum cs ro ds replicProtocol io perfIndicators
123
                          syncS reS act
124

  
125
    where conditionalSyncStatusParser SyncSource = Just <$> syncStatusParser
126
          conditionalSyncStatusParser SyncTarget = Just <$> syncStatusParser
127
          conditionalSyncStatusParser _ = pure Nothing
128
          skipRoleString = A.string "ro:" <|> A.string "st:"
129
          resyncParser = skipSpacesAndString "resync:" additionalInfoParser
130
          actLogParser = skipSpacesAndString "act_log:" additionalInfoParser
131
          additionalEOL = A.skipWhile A.isEndOfLine
132

  
133
-- | The parser for the connection state.
134
connectionStateParser :: Parser ConnectionState
135
connectionStateParser =
136
  standAlone
137
  <|> disconnecting
138
  <|> unconnected
139
  <|> timeout
140
  <|> brokenPipe
141
  <|> networkFailure
142
  <|> protocolError
143
  <|> tearDown
144
  <|> wfConnection
145
  <|> wfReportParams
146
  <|> connected
147
  <|> startingSyncS
148
  <|> startingSyncT
149
  <|> wfBitMapS
150
  <|> wfBitMapT
151
  <|> wfSyncUUID
152
  <|> syncSource
153
  <|> syncTarget
154
  <|> pausedSyncS
155
  <|> pausedSyncT
156
  <|> verifyS
157
  <|> verifyT
158
  <|> unconfigured
159
    where standAlone     = A.string "StandAlone"     *> pure StandAlone
160
          disconnecting  = A.string "Disconnectiog"  *> pure Disconnecting
161
          unconnected    = A.string "Unconnected"    *> pure Unconnected
162
          timeout        = A.string "Timeout"        *> pure Timeout
163
          brokenPipe     = A.string "BrokenPipe"     *> pure BrokenPipe
164
          networkFailure = A.string "NetworkFailure" *> pure NetworkFailure
165
          protocolError  = A.string "ProtocolError"  *> pure ProtocolError
166
          tearDown       = A.string "TearDown"       *> pure TearDown
167
          wfConnection   = A.string "WFConnection"   *> pure WFConnection
168
          wfReportParams = A.string "WFReportParams" *> pure WFReportParams
169
          connected      = A.string "Connected"      *> pure Connected
170
          startingSyncS  = A.string "StartingSyncS"  *> pure StartingSyncS
171
          startingSyncT  = A.string "StartingSyncT"  *> pure StartingSyncT
172
          wfBitMapS      = A.string "WFBitMapS"      *> pure WFBitMapS
173
          wfBitMapT      = A.string "WFBitMapT"      *> pure WFBitMapT
174
          wfSyncUUID     = A.string "WFSyncUUID"     *> pure WFSyncUUID
175
          syncSource     = A.string "SyncSource"     *> pure SyncSource
176
          syncTarget     = A.string "SyncTarget"     *> pure SyncTarget
177
          pausedSyncS    = A.string "PausedSyncS"    *> pure PausedSyncS
178
          pausedSyncT    = A.string "PausedSyncT"    *> pure PausedSyncT
179
          verifyS        = A.string "VerifyS"        *> pure VerifyS
180
          verifyT        = A.string "VerifyT"        *> pure VerifyT
181
          unconfigured   = A.string "Unconfigured"   *> pure Unconfigured
182

  
183
-- | Parser for recognizing strings describing two elements of the
184
-- same type separated by a '/'. The first one is considered local,
185
-- the second remote.
186
localRemoteParser :: Parser a -> Parser (LocalRemote a)
187
localRemoteParser parser = LocalRemote <$> parser <*> (A.char '/' *> parser)
188

  
189
-- | The parser for resource roles.
190
roleParser :: Parser Role
191
roleParser =
192
  primary
193
  <|> secondary
194
  <|> unknown
195
    where primary   = A.string "Primary"   *> pure Primary
196
          secondary = A.string "Secondary" *> pure Secondary
197
          unknown   = A.string "Unknown"   *> pure Unknown
198

  
199
-- | The parser for disk states.
200
diskStateParser :: Parser DiskState
201
diskStateParser =
202
  diskless
203
  <|> attaching
204
  <|> failed
205
  <|> negotiating
206
  <|> inconsistent
207
  <|> outdated
208
  <|> dUnknown
209
  <|> consistent
210
  <|> upToDate
211
    where diskless     = A.string "Diskless"     *> pure Diskless
212
          attaching    = A.string "Attaching"    *> pure Attaching
213
          failed       = A.string "Failed"       *> pure Failed
214
          negotiating  = A.string "Negotiating"  *> pure Negotiating
215
          inconsistent = A.string "Inconsistent" *> pure Inconsistent
216
          outdated     = A.string "Outdated"     *> pure Outdated
217
          dUnknown     = A.string "DUnknown"     *> pure DUnknown
218
          consistent   = A.string "Consistent"   *> pure Consistent
219
          upToDate     = A.string "UpToDate"     *> pure UpToDate
220

  
221
-- | The parser for I/O flags.
222
ioFlagsParser :: Parser String
223
ioFlagsParser = fmap unpack . A.takeWhile $ not . isBadEndOfLine
224

  
225
-- | The parser for performance indicators.
226
performanceIndicatorsParser :: Parser PerformanceIndicators
227
performanceIndicatorsParser =
228
  PerformanceIndicators
229
    <$> skipSpacesAndString "ns:" A.decimal
230
    <*> skipSpacesAndString "nr:" A.decimal
231
    <*> skipSpacesAndString "dw:" A.decimal
232
    <*> skipSpacesAndString "dr:" A.decimal
233
    <*> skipSpacesAndString "al:" A.decimal
234
    <*> skipSpacesAndString "bm:" A.decimal
235
    <*> skipSpacesAndString "lo:" A.decimal
236
    <*> skipSpacesAndString "pe:" A.decimal
237
    <*> skipSpacesAndString "ua:" A.decimal
238
    <*> skipSpacesAndString "ap:" A.decimal
239
    <*> optional (skipSpacesAndString "ep:" A.decimal)
240
    <*> optional (skipSpacesAndString "wo:" A.anyChar)
241
    <*> optional (skipSpacesAndString "oos:" A.decimal)
242
    <* skipSpaces <* A.endOfLine
243

  
244
-- | The parser for the syncronization status.
245
syncStatusParser :: Parser SyncStatus
246
syncStatusParser = do
247
  _ <- statusBarParser
248
  percent <-
249
    skipSpacesAndString "sync'ed:" $ skipSpaces *> A.double <* A.char '%'
250
  partSyncSize <- skipSpaces *> A.char '(' *> A.decimal
251
  totSyncSize <- A.char '/' *> A.decimal <* A.char ')'
252
  sizeUnit <- sizeUnitParser <* optional A.endOfLine
253
  timeToEnd <- skipSpacesAndString "finish:" $ skipSpaces *> timeParser
254
  sp <-
255
    skipSpacesAndString "speed:" $
256
      skipSpaces
257
      *> commaIntParser
258
      <* skipSpaces
259
      <* A.char '('
260
      <* commaIntParser
261
      <* A.char ')'
262
  w <- skipSpacesAndString "want:" (
263
         skipSpaces
264
         *> (Just <$> commaIntParser)
265
       )
266
       <|> pure Nothing
267
  sSizeUnit <- skipSpaces *> sizeUnitParser
268
  sTimeUnit <- A.char '/' *> timeUnitParser
269
  _ <- A.endOfLine
270
  return $
271
    SyncStatus percent partSyncSize totSyncSize sizeUnit timeToEnd sp w
272
      sSizeUnit sTimeUnit
273

  
274
-- | The parser for recognizing (and discarding) the sync status bar.
275
statusBarParser :: Parser ()
276
statusBarParser =
277
  skipSpaces
278
  *> A.char '['
279
  *> A.skipWhile (== '=')
280
  *> A.skipWhile (== '>')
281
  *> A.skipWhile (== '.')
282
  *> A.char ']'
283
  *> pure ()
284

  
285
-- | The parser for recognizing data size units (only the ones
286
-- actually found in DRBD files are implemented).
287
sizeUnitParser :: Parser SizeUnit
288
sizeUnitParser =
289
  kilobyte
290
  <|> megabyte
291
    where kilobyte = A.string "K" *> pure KiloByte
292
          megabyte = A.string "M" *> pure MegaByte
293

  
294
-- | The parser for recognizing time (hh:mm:ss).
295
timeParser :: Parser Time
296
timeParser = Time <$> h <*> m <*> s
297
  where h = A.decimal :: Parser Integer
298
        m = A.char ':' *> A.decimal :: Parser Integer
299
        s = A.char ':' *> A.decimal :: Parser Integer
300

  
301
-- | The parser for recognizing time units (only the ones actually
302
-- found in DRBD files are implemented).
303
timeUnitParser :: Parser TimeUnit
304
timeUnitParser = second
305
  where second = A.string "sec" *> pure Second
306

  
307
-- | Haskell does not recognises ',' as the separator every 3 digits
308
-- but DRBD uses it, so we need an ah-hoc parser.
309
commaIntParser :: Parser Int
310
commaIntParser = do
311
  first <- A.decimal
312
  allDigits <- commaIntHelper first
313
  pure allDigits
314

  
315
-- | Helper (triplet parser) for the commaIntParser
316
commaIntHelper :: Int -> Parser Int
317
commaIntHelper acc = nextTriplet <|> end
318
  where nextTriplet = do
319
          _ <- A.char ','
320
          triplet <- AC.count 3 A.digit
321
          commaIntHelper $ acc * 1000 + (read triplet :: Int)
322
        end = pure acc :: Parser Int
323

  
324
-- | Parser for the additional information provided by DRBD <= 8.0.
325
additionalInfoParser::Parser AdditionalInfo
326
additionalInfoParser = AdditionalInfo
327
  <$> skipSpacesAndString "used:" A.decimal
328
  <*> (A.char '/' *> A.decimal)
329
  <*> skipSpacesAndString "hits:" A.decimal
330
  <*> skipSpacesAndString "misses:" A.decimal
331
  <*> skipSpacesAndString "starving:" A.decimal
332
  <*> skipSpacesAndString "dirty:" A.decimal
333
  <*> skipSpacesAndString "changed:" A.decimal
334
  <* A.endOfLine
b/htools/Ganeti/Block/Drbd/Types.hs
1
{-| DRBD Data Types
2

  
3
This module holds the definition of the data types describing the status of
4
DRBD.
5

  
6
-}
7
{-
8

  
9
Copyright (C) 2012 Google Inc.
10

  
11
This program is free software; you can redistribute it and/or modify
12
it under the terms of the GNU General Public License as published by
13
the Free Software Foundation; either version 2 of the License, or
14
(at your option) any later version.
15

  
16
This program is distributed in the hope that it will be useful, but
17
WITHOUT ANY WARRANTY; without even the implied warranty of
18
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
19
General Public License for more details.
20

  
21
You should have received a copy of the GNU General Public License
22
along with this program; if not, write to the Free Software
23
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
24
02110-1301, USA.
25

  
26
-}
27
module Ganeti.Block.Drbd.Types
28
  ( DRBDStatus(..)
29
  , VersionInfo(..)
30
  , DeviceInfo(..)
31
  , ConnectionState(..)
32
  , LocalRemote(..)
33
  , Role(..)
34
  , DiskState(..)
35
  , PerformanceIndicators(..)
36
  , SyncStatus(..)
37
  , SizeUnit(..)
38
  , Time(..)
39
  , TimeUnit(..)
40
  , AdditionalInfo(..)
41
  ) where
42

  
43
--TODO: consider turning deviceInfos into an IntMap
44
-- | Data type contaning all the data about the status of DRBD.
45
data DRBDStatus =
46
  DRBDStatus
47
  { versionInfo :: VersionInfo  -- ^ Version information about DRBD
48
  , deviceInfos :: [DeviceInfo] -- ^ Per-minor information
49
  } deriving (Eq, Show)
50

  
51
-- | Data type describing the DRBD version.
52
data VersionInfo =
53
  VersionInfo
54
  { version    :: Maybe String -- ^ DRBD driver version
55
  , api        :: Maybe String -- ^ The api version
56
  , proto      :: Maybe String -- ^ The protocol version
57
  , srcversion :: Maybe String -- ^ The version of the source files
58
  , gitHash    :: Maybe String -- ^ Git hash of the source files
59
  , buildBy    :: Maybe String -- ^ Who built the binary (and,
60
                               -- optionally, when)
61
  } deriving (Eq, Show)
62

  
63
-- | Data type describing a device.
64
data DeviceInfo =
65
  UnconfiguredDevice Int -- ^ An DRBD minor marked as unconfigured
66
  | -- | A configured DRBD minor
67
    DeviceInfo
68
      { minorNumber :: Int -- ^ The minor index of the device
69
      , connectionState :: ConnectionState -- ^ State of the connection
70
      , resourceRoles :: LocalRemote Role -- ^ Roles of the resources
71
      , diskStates :: LocalRemote DiskState -- ^ Status of the disks
72
      , replicationProtocol :: Char -- ^ The replication protocol being used
73
      , ioFlags :: String -- ^ The input/output flags
74
      , performanceIndicators :: PerformanceIndicators -- ^ Performance indicators
75
      , syncStatus :: Maybe SyncStatus -- ^ The status of the syncronization of
76
                                     -- the disk (only if it is happening)
77
      , resync :: Maybe AdditionalInfo -- ^ Additional info by DRBD 8.0
78
      , actLog :: Maybe AdditionalInfo -- ^ Additional info by DRBD 8.0
79
      } deriving (Eq, Show)
80

  
81
-- | Data type describing the state of the connection.
82
data ConnectionState
83
  = StandAlone     -- ^  No network configuration available
84
  | Disconnecting  -- ^ Temporary state during disconnection
85
  | Unconnected    -- ^ Prior to a connection attempt
86
  | Timeout        -- ^ Following a timeout in the communication
87
  | BrokenPipe     -- ^ After the connection to the peer was lost
88
  | NetworkFailure -- ^ After the connection to the parner was lost
89
  | ProtocolError  -- ^ After the connection to the parner was lost
90
  | TearDown       -- ^ The peer is closing the connection
91
  | WFConnection   -- ^ Waiting for the peer to become visible
92
  | WFReportParams -- ^ Waiting for first packet from peer
93
  | Connected      -- ^ Connected, data mirroring active
94
  | StartingSyncS  -- ^ Source of a full sync started by admin
95
  | StartingSyncT  -- ^ Target of a full sync started by admin
96
  | WFBitMapS      -- ^ Source of a just starting partial sync
97
  | WFBitMapT      -- ^ Target of a just starting partial sync
98
  | WFSyncUUID     -- ^ Synchronization is about to begin
99
  | SyncSource     -- ^ Source of a running synchronization
100
  | SyncTarget     -- ^ Target of a running synchronization
101
  | PausedSyncS    -- ^ Source of a paused synchronization
102
  | PausedSyncT    -- ^ Target of a paused synchronization
103
  | VerifyS        -- ^ Source of an running verification
104
  | VerifyT        -- ^ Target of an running verification
105
  | Unconfigured   -- ^ The device is not configured
106
    deriving (Show, Eq)
107

  
108
-- | Algebraic data type describing something that has a local and a remote
109
-- value.
110
data LocalRemote a =
111
  LocalRemote
112
  { local  :: a -- ^ The local value
113
  , remote :: a -- ^ The remote value
114
  } deriving (Eq, Show)
115

  
116
-- | Data type describing.
117
data Role = Primary   -- ^ The device role is primary
118
          | Secondary -- ^ The device role is secondary
119
          | Unknown   -- ^ The device role is unknown
120
            deriving (Eq, Show)
121

  
122
-- | Data type describing disk states.
123
data DiskState
124
  = Diskless     -- ^ No local block device assigned to the DRBD driver
125
  | Attaching    -- ^ Reading meta data
126
  | Failed       -- ^ I/O failure
127
  | Negotiating  -- ^ "Attach" on an already-connected device
128
  | Inconsistent -- ^ The data is inconsistent between nodes.
129
  | Outdated     -- ^ Data consistent but outdated
130
  | DUnknown     -- ^ No network connection available
131
  | Consistent   -- ^ Consistent data, but without network connection
132
  | UpToDate     -- ^ Consistent, up-to-date. This is the normal state
133
    deriving (Eq, Show)
134

  
135
-- | Data type containing data about performance indicators.
136
data PerformanceIndicators = PerformanceIndicators
137
  { networkSend :: Int -- ^ KiB of data sent on the network
138
  , networkReceive :: Int -- ^ KiB of data received from the network
139
  , diskWrite :: Int -- ^ KiB of data written on local disk
140
  , diskRead :: Int -- ^ KiB of data read from local disk
141
  , activityLog :: Int -- ^ Number of updates of the activity log
142
  , bitMap :: Int -- ^ Number of updates to the bitmap area of the metadata
143
  , localCount :: Int -- ^ Number of open requests to te local I/O subsystem
144
  , pending :: Int -- ^ Num of requests sent to the partner but not yet answered
145
  , unacknowledged :: Int -- ^ Num of requests received by the partner but still
146
                        -- to be answered
147
  , applicationPending :: Int -- ^ Num of block I/O requests forwarded
148
                              -- to DRBD but that have not yet been
149
                              -- answered
150
  , epochs :: Maybe Int -- ^ Number of epoch objects
151
  , writeOrder :: Maybe Char -- ^ Currently used write ordering method
152
  , outOfSync :: Maybe Int -- ^ KiB of storage currently out of sync
153
  } deriving (Eq, Show)
154

  
155
-- | Data type containing data about the synchronization status of a device.
156
data SyncStatus =
157
  SyncStatus
158
  { percentage      :: Double    -- ^ Percentage of syncronized data
159
  , partialSyncSize :: Int       -- ^ Numerator of the fraction of synced data
160
  , totalSyncSize   :: Int       -- ^ Denominator of the fraction of
161
                                 -- synced data
162
  , syncUnit        :: SizeUnit  -- ^ Measurement unit of the previous
163
                                 -- fraction
164
  , timeToFinish    :: Time      -- ^ Expected time before finishing
165
                                 -- the syncronization
166
  , speed           :: Int       -- ^ Speed of the syncronization
167
  , want            :: Maybe Int -- ^ Want of the syncronization
168
  , speedSizeUnit   :: SizeUnit  -- ^ Size unit of the speed
169
  , speedTimeUnit   :: TimeUnit  -- ^ Time unit of the speed
170
  } deriving (Eq, Show)
171

  
172
-- | Data type describing a size unit for memory.
173
data SizeUnit = KiloByte | MegaByte deriving (Eq, Show)
174

  
175
-- | Data type describing a time (hh:mm:ss).
176
data Time = Time
177
  { hour :: Integer
178
  , min  :: Integer
179
  , sec  :: Integer
180
  } deriving (Eq, Show)
181

  
182
-- | Data type describing a time unit.
183
data TimeUnit = Second deriving (Eq, Show)
184

  
185
-- | Additional device-specific cache-like information produced by
186
-- drbd <= 8.0.
187
--
188
-- Internal debug information exported by old DRBD versions.
189
-- Undocumented both in DRBD and here.
190
data AdditionalInfo = AdditionalInfo
191
  { partialUsed :: Int
192
  , totalUsed   :: Int
193
  , hits        :: Int
194
  , misses      :: Int
195
  , starving    :: Int
196
  , dirty       :: Int
197
  , changed     :: Int
198
  } deriving (Eq, Show)

Also available in: Unified diff