Rename directory 'Block' to 'Storage'
[ganeti-local] / src / Ganeti / Storage / 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.Storage.Drbd.Types
28   ( DRBDStatus(..)
29   , VersionInfo(..)
30   , DeviceInfo(..)
31   , ConnState(..)
32   , LocalRemote(..)
33   , Role(..)
34   , DiskState(..)
35   , PerfIndicators(..)
36   , SyncStatus(..)
37   , SizeUnit(..)
38   , Time(..)
39   , TimeUnit(..)
40   , AdditionalInfo(..)
41   , DrbdInstMinor(..)
42   ) where
43
44 import Control.Monad
45 import Text.JSON
46 import Text.Printf
47
48 import Ganeti.JSON
49
50 --TODO: consider turning deviceInfos into an IntMap
51 -- | Data type contaning all the data about the status of DRBD.
52 data DRBDStatus =
53   DRBDStatus
54   { versionInfo :: VersionInfo  -- ^ Version information about DRBD
55   , deviceInfos :: [DeviceInfo] -- ^ Per-minor information
56   } deriving (Eq, Show)
57
58 -- | The DRBDStatus instance of JSON.
59 instance JSON DRBDStatus where
60   showJSON d = makeObj
61     [ ("versionInfo", showJSON $ versionInfo d)
62     , ("deviceInfos", showJSONs $ deviceInfos d)
63     ]
64
65   readJSON = error "JSON read instance not implemented for type DRBDStatus"
66
67 -- | Data type describing the DRBD version.
68 data VersionInfo =
69   VersionInfo
70   { version    :: Maybe String -- ^ DRBD driver version
71   , api        :: Maybe String -- ^ The api version
72   , proto      :: Maybe String -- ^ The protocol version
73   , srcversion :: Maybe String -- ^ The version of the source files
74   , gitHash    :: Maybe String -- ^ Git hash of the source files
75   , buildBy    :: Maybe String -- ^ Who built the binary (and,
76                                -- optionally, when)
77   } deriving (Eq, Show)
78
79 -- | The VersionInfo instance of JSON.
80 instance JSON VersionInfo where
81   showJSON (VersionInfo versionF apiF protoF srcversionF gitHashF buildByF) =
82     optFieldsToObj
83       [ optionalJSField "version" versionF
84       , optionalJSField "api" apiF
85       , optionalJSField "proto" protoF
86       , optionalJSField "srcversion" srcversionF
87       , optionalJSField "gitHash" gitHashF
88       , optionalJSField "buildBy" buildByF
89       ]
90
91   readJSON = error "JSON read instance not implemented for type VersionInfo"
92
93 -- | Data type describing a device.
94 data DeviceInfo =
95   UnconfiguredDevice Int -- ^ An DRBD minor marked as unconfigured
96   | -- | A configured DRBD minor
97     DeviceInfo
98       { minorNumber :: Int                  -- ^ The minor index of the device
99       , connectionState :: ConnState        -- ^ State of the connection
100       , resourceRoles :: LocalRemote Role   -- ^ Roles of the resources
101       , diskStates :: LocalRemote DiskState -- ^ Status of the disks
102       , replicationProtocol :: Char         -- ^ The replication protocol
103                                             -- being used
104       , ioFlags :: String                   -- ^ The input/output flags
105       , perfIndicators :: PerfIndicators    -- ^ Performance indicators
106       , syncStatus :: Maybe SyncStatus      -- ^ The status of the
107                                             -- syncronization of the disk
108                                             -- (only if it is happening)
109       , resync :: Maybe AdditionalInfo      -- ^ Additional info by DRBD 8.0
110       , actLog :: Maybe AdditionalInfo      -- ^ Additional info by DRBD 8.0
111       , instName :: Maybe String            -- ^ The name of the associated
112                                             -- instance
113       } deriving (Eq, Show)
114
115 -- | The DeviceInfo instance of JSON.
116 instance JSON DeviceInfo where
117   showJSON (UnconfiguredDevice num) = makeObj
118     [ ("minor", showJSON num)
119     , ("connectionState", showJSON Unconfigured)
120     ]
121   showJSON (DeviceInfo minorNumberF connectionStateF (LocalRemote
122     localRole remoteRole) (LocalRemote localState remoteState)
123     replicProtocolF ioFlagsF perfIndicatorsF syncStatusF _ _ instNameF) =
124     optFieldsToObj
125     [ Just ("minor", showJSON minorNumberF)
126     , Just ("connectionState", showJSON connectionStateF)
127     , Just ("localRole", showJSON localRole)
128     , Just ("remoteRole", showJSON remoteRole)
129     , Just ("localState", showJSON localState)
130     , Just ("remoteState", showJSON remoteState)
131     , Just ("replicationProtocol", showJSON replicProtocolF)
132     , Just ("ioFlags", showJSON ioFlagsF)
133     , Just ("perfIndicators", showJSON perfIndicatorsF)
134     , optionalJSField "syncStatus" syncStatusF
135     , Just ("instance", maybe JSNull showJSON instNameF)
136     ]
137
138   readJSON = error "JSON read instance not implemented for type DeviceInfo"
139
140 -- | Data type describing the state of the connection.
141 data ConnState
142   = StandAlone     -- ^  No network configuration available
143   | Disconnecting  -- ^ Temporary state during disconnection
144   | Unconnected    -- ^ Prior to a connection attempt
145   | Timeout        -- ^ Following a timeout in the communication
146   | BrokenPipe     -- ^ After the connection to the peer was lost
147   | NetworkFailure -- ^ After the connection to the partner was lost
148   | ProtocolError  -- ^ After the connection to the partner was lost
149   | TearDown       -- ^ The peer is closing the connection
150   | WFConnection   -- ^ Waiting for the peer to become visible
151   | WFReportParams -- ^ Waiting for first packet from peer
152   | Connected      -- ^ Connected, data mirroring active
153   | StartingSyncS  -- ^ Source of a full sync started by admin
154   | StartingSyncT  -- ^ Target of a full sync started by admin
155   | WFBitMapS      -- ^ Source of a just starting partial sync
156   | WFBitMapT      -- ^ Target of a just starting partial sync
157   | WFSyncUUID     -- ^ Synchronization is about to begin
158   | SyncSource     -- ^ Source of a running synchronization
159   | SyncTarget     -- ^ Target of a running synchronization
160   | PausedSyncS    -- ^ Source of a paused synchronization
161   | PausedSyncT    -- ^ Target of a paused synchronization
162   | VerifyS        -- ^ Source of a running verification
163   | VerifyT        -- ^ Target of a running verification
164   | Unconfigured   -- ^ The device is not configured
165     deriving (Show, Eq)
166
167 -- | The ConnState instance of JSON.
168 instance JSON ConnState where
169   showJSON = showJSON . show
170
171   readJSON = error "JSON read instance not implemented for type ConnState"
172
173 -- | Algebraic data type describing something that has a local and a remote
174 -- value.
175 data LocalRemote a =
176   LocalRemote
177   { local  :: a -- ^ The local value
178   , remote :: a -- ^ The remote value
179   } deriving (Eq, Show)
180
181 -- | Data type describing.
182 data Role = Primary   -- ^ The device role is primary
183           | Secondary -- ^ The device role is secondary
184           | Unknown   -- ^ The device role is unknown
185             deriving (Eq, Show)
186
187 -- | The Role instance of JSON.
188 instance JSON Role where
189   showJSON = showJSON . show
190
191   readJSON = error "JSON read instance not implemented for type Role"
192
193 -- | Data type describing disk states.
194 data DiskState
195   = Diskless     -- ^ No local block device assigned to the DRBD driver
196   | Attaching    -- ^ Reading meta data
197   | Failed       -- ^ I/O failure
198   | Negotiating  -- ^ "Attach" on an already-connected device
199   | Inconsistent -- ^ The data is inconsistent between nodes.
200   | Outdated     -- ^ Data consistent but outdated
201   | DUnknown     -- ^ No network connection available
202   | Consistent   -- ^ Consistent data, but without network connection
203   | UpToDate     -- ^ Consistent, up-to-date. This is the normal state
204     deriving (Eq, Show)
205
206 -- | The DiskState instance of JSON.
207 instance JSON DiskState where
208   showJSON = showJSON . show
209
210   readJSON = error "JSON read instance not implemented for type DiskState"
211
212 -- | Data type containing data about performance indicators.
213 data PerfIndicators = PerfIndicators
214   { networkSend :: Int -- ^ KiB of data sent on the network
215   , networkReceive :: Int -- ^ KiB of data received from the network
216   , diskWrite :: Int -- ^ KiB of data written on local disk
217   , diskRead :: Int -- ^ KiB of data read from local disk
218   , activityLog :: Int -- ^ Number of updates of the activity log
219   , bitMap :: Int -- ^ Number of updates to the bitmap area of the metadata
220   , localCount :: Int -- ^ Number of open requests to the local I/O subsystem
221   , pending :: Int -- ^ Num of requests sent to the partner but not yet answered
222   , unacknowledged :: Int -- ^ Num of requests received by the partner but still
223                         -- to be answered
224   , applicationPending :: Int -- ^ Num of block I/O requests forwarded
225                               -- to DRBD but that have not yet been
226                               -- answered
227   , epochs :: Maybe Int -- ^ Number of epoch objects
228   , writeOrder :: Maybe Char -- ^ Currently used write ordering method
229   , outOfSync :: Maybe Int -- ^ KiB of storage currently out of sync
230   } deriving (Eq, Show)
231
232 -- | The PerfIndicators instance of JSON.
233 instance JSON PerfIndicators where
234   showJSON p = optFieldsToObj
235     [ Just ("networkSend", showJSON $ networkSend p)
236     , Just ("networkReceive", showJSON $ networkReceive p)
237     , Just ("diskWrite", showJSON $ diskWrite p)
238     , Just ("diskRead", showJSON $ diskRead p)
239     , Just ("activityLog", showJSON $ activityLog p)
240     , Just ("bitMap", showJSON $ bitMap p)
241     , Just ("localCount", showJSON $ localCount p)
242     , Just ("pending", showJSON $ pending p)
243     , Just ("unacknowledged", showJSON $ unacknowledged p)
244     , Just ("applicationPending", showJSON $ applicationPending p)
245     , optionalJSField "epochs" $ epochs p
246     , optionalJSField "writeOrder" $ writeOrder p
247     , optionalJSField "outOfSync" $ outOfSync p
248     ]
249
250   readJSON = error "JSON read instance not implemented for type PerfIndicators"
251
252 -- | Data type containing data about the synchronization status of a device.
253 data SyncStatus =
254   SyncStatus
255   { percentage      :: Double    -- ^ Percentage of syncronized data
256   , partialSyncSize :: Int       -- ^ Numerator of the fraction of synced data
257   , totalSyncSize   :: Int       -- ^ Denominator of the fraction of
258                                  -- synced data
259   , syncUnit        :: SizeUnit  -- ^ Measurement unit of the previous
260                                  -- fraction
261   , timeToFinish    :: Time      -- ^ Expected time before finishing
262                                  -- the syncronization
263   , speed           :: Int       -- ^ Speed of the syncronization
264   , want            :: Maybe Int -- ^ Want of the syncronization
265   , speedSizeUnit   :: SizeUnit  -- ^ Size unit of the speed
266   , speedTimeUnit   :: TimeUnit  -- ^ Time unit of the speed
267   } deriving (Eq, Show)
268
269 -- | The SyncStatus instance of JSON.
270 instance JSON SyncStatus where
271   showJSON s = optFieldsToObj
272     [ Just ("percentage", showJSON $ percentage s)
273     , Just ("progress", showJSON $ show (partialSyncSize s) ++ "/" ++
274         show (totalSyncSize s))
275     , Just ("progressUnit", showJSON $ syncUnit s)
276     , Just ("timeToFinish", showJSON $ timeToFinish s)
277     , Just ("speed", showJSON $ speed s)
278     , optionalJSField "want" $ want s
279     , Just ("speedUnit", showJSON $ show (speedSizeUnit s) ++ "/" ++
280         show (speedTimeUnit s))
281     ]
282
283   readJSON = error "JSON read instance not implemented for type SyncStatus"
284
285 -- | Data type describing a size unit for memory.
286 data SizeUnit = KiloByte | MegaByte deriving (Eq, Show)
287
288 -- | The SizeUnit instance of JSON.
289 instance JSON SizeUnit where
290   showJSON = showJSON . show
291
292   readJSON = error "JSON read instance not implemented for type SizeUnit"
293
294 -- | Data type describing a time (hh:mm:ss).
295 data Time = Time
296   { hour :: Int
297   , min  :: Int
298   , sec  :: Int
299   } deriving (Eq, Show)
300
301 -- | The Time instance of JSON.
302 instance JSON Time where
303   showJSON (Time h m s) = showJSON (printf "%02d:%02d:%02d" h m s :: String)
304
305   readJSON = error "JSON read instance not implemented for type Time"
306
307 -- | Data type describing a time unit.
308 data TimeUnit = Second deriving (Eq, Show)
309
310 -- | The TimeUnit instance of JSON.
311 instance JSON TimeUnit where
312   showJSON Second = showJSON "Second"
313
314   readJSON = error "JSON read instance not implemented for type TimeUnit"
315
316 -- | Additional device-specific cache-like information produced by
317 -- drbd <= 8.0.
318 --
319 -- Internal debug information exported by old DRBD versions.
320 -- Undocumented both in DRBD and here.
321 data AdditionalInfo = AdditionalInfo
322   { partialUsed :: Int
323   , totalUsed   :: Int
324   , hits        :: Int
325   , misses      :: Int
326   , starving    :: Int
327   , dirty       :: Int
328   , changed     :: Int
329   } deriving (Eq, Show)
330
331 -- | Data type representing the pairing of a DRBD minor with an instance.
332 data DrbdInstMinor = DrbdInstMinor
333   { dimNode :: String
334   , dimMinor :: Int
335   , dimInstName :: String
336   , dimDiskIdx :: String
337   , dimRole :: String
338   , dimPeer :: String
339   } deriving (Show)
340
341 -- | The DrbdInstMinor instance of JSON.
342 instance JSON DrbdInstMinor where
343   showJSON (DrbdInstMinor a b c d e f) =
344     JSArray
345       [ showJSON a
346       , showJSON b
347       , showJSON c
348       , showJSON d
349       , showJSON e
350       , showJSON f
351       ]
352   readJSON (JSArray [a, b, c, d, e, f]) =
353     DrbdInstMinor
354       `fmap` readJSON a
355       `ap` readJSON b
356       `ap` readJSON c
357       `ap` readJSON d
358       `ap` readJSON e
359       `ap` readJSON f
360   readJSON _ = fail "Unable to read a DrbdInstMinor"