Add JSON serialization capabilities for DRBD status
authorMichele Tartara <mtartara@google.com>
Mon, 3 Dec 2012 08:45:30 +0000 (09:45 +0100)
committerMichele Tartara <mtartara@google.com>
Mon, 3 Dec 2012 10:45:45 +0000 (11:45 +0100)
The serialized JSON is not a 1:1 dump of the data structures
populated by the parser. This is done intentionally, with the
aim of producing a more stable and more meaningful output to
be used by the (future) monitoring agent and stand-alone data
collectors.

Also:
* shorten the names of some data types.
* change data type for the fields of the Time data structure

Signed-off-by: Michele Tartara <mtartara@google.com>
Reviewed-by: Iustin Pop <iustin@google.com>

htest/Test/Ganeti/Block/Drbd/Parser.hs
htools/Ganeti/Block/Drbd/Parser.hs
htools/Ganeti/Block/Drbd/Types.hs

index a59a77c..17b0988 100644 (file)
@@ -58,7 +58,7 @@ case_drbd80_emptyline = testFile "proc_drbd80-emptyline.txt" $
     )
     [ DeviceInfo 0 Connected (LocalRemote Primary Secondary)
         (LocalRemote UpToDate UpToDate) 'C' "r---"
-        (PerformanceIndicators 78728316 0 77675644 1277039 254 270 0 0 0 0
+        (PerfIndicators 78728316 0 77675644 1277039 254 270 0 0 0 0
           Nothing Nothing Nothing)
         Nothing
         (Just $ AdditionalInfo 0 61 65657 135 0 0 135)
@@ -79,14 +79,14 @@ case_drbd83_sync_krnl2_6_39 = testFile "proc_drbd83_sync_krnl2.6.39.txt" $
     )
     [ DeviceInfo 0 Connected (LocalRemote Primary Secondary)
         (LocalRemote UpToDate UpToDate) 'C' "r----"
-        (PerformanceIndicators 140978 0 9906 131533 27 8 0 0 0 0 (Just 1)
+        (PerfIndicators 140978 0 9906 131533 27 8 0 0 0 0 (Just 1)
           (Just 'b') (Just 0))
         Nothing
         Nothing
         Nothing,
       DeviceInfo 1 Connected (LocalRemote Secondary Primary)
         (LocalRemote UpToDate UpToDate) 'C' "r---"
-        (PerformanceIndicators 0 140980 140980 0 0 8 0 0 0 0 (Just 1) (Just 'f')
+        (PerfIndicators 0 140980 140980 0 0 8 0 0 0 0 (Just 1) (Just 'f')
           (Just 0))
         Nothing
         Nothing
@@ -94,7 +94,7 @@ case_drbd83_sync_krnl2_6_39 = testFile "proc_drbd83_sync_krnl2.6.39.txt" $
       UnconfiguredDevice 2,
       DeviceInfo 3 SyncSource (LocalRemote Primary Secondary)
         (LocalRemote UpToDate Inconsistent) 'A' "r-----"
-        (PerformanceIndicators 373888 0 0 374088 0 22 7 27 7 0 (Just 1)
+        (PerfIndicators 373888 0 0 374088 0 22 7 27 7 0 (Just 1)
           (Just 'f') (Just 15358208))
         (Just $ SyncStatus 2.4 14996 15360 MegaByte (Time 0 4 8) 61736 Nothing
           KiloByte Second)
@@ -102,7 +102,7 @@ case_drbd83_sync_krnl2_6_39 = testFile "proc_drbd83_sync_krnl2.6.39.txt" $
         Nothing,
       DeviceInfo 4 WFConnection (LocalRemote Primary Unknown)
         (LocalRemote UpToDate DUnknown) 'C' "r----"
-        (PerformanceIndicators 140978 0 9906 131534 27 8 0 0 0 0 (Just 1)
+        (PerfIndicators 140978 0 9906 131534 27 8 0 0 0 0 (Just 1)
           (Just 'b') (Just 0))
         Nothing
         Nothing
@@ -119,14 +119,14 @@ case_drbd83_sync = testFile "proc_drbd83_sync.txt" $
     )
     [ DeviceInfo 0 Connected (LocalRemote Primary Secondary)
         (LocalRemote UpToDate UpToDate) 'C' "r----"
-        (PerformanceIndicators 140978 0 9906 131533 27 8 0 0 0 0 (Just 1)
+        (PerfIndicators 140978 0 9906 131533 27 8 0 0 0 0 (Just 1)
           (Just 'b') (Just 0))
         Nothing
         Nothing
         Nothing,
       DeviceInfo 1 Connected (LocalRemote Secondary Primary)
         (LocalRemote UpToDate UpToDate) 'C' "r---"
-        (PerformanceIndicators 0 140980 140980 0 0 8 0 0 0 0 (Just 1) (Just 'f')
+        (PerfIndicators 0 140980 140980 0 0 8 0 0 0 0 (Just 1) (Just 'f')
           (Just 0))
         Nothing
         Nothing
@@ -134,7 +134,7 @@ case_drbd83_sync = testFile "proc_drbd83_sync.txt" $
       UnconfiguredDevice 2,
       DeviceInfo 3 SyncTarget (LocalRemote Primary Secondary)
         (LocalRemote Inconsistent UpToDate) 'C' "r----"
-        (PerformanceIndicators 0 178176 178176 0 104 42 0 0 0 0 (Just 1)
+        (PerfIndicators 0 178176 178176 0 104 42 0 0 0 0 (Just 1)
           (Just 'b') (Just 346112))
         (Just $ SyncStatus 34.9 346112 524288 MegaByte (Time 0 0 5) 59392
           Nothing KiloByte Second)
@@ -142,7 +142,7 @@ case_drbd83_sync = testFile "proc_drbd83_sync.txt" $
         Nothing,
       DeviceInfo 4 WFConnection (LocalRemote Primary Unknown)
         (LocalRemote UpToDate DUnknown) 'C' "r----"
-        (PerformanceIndicators 140978 0 9906 131534 27 8 0 0 0 0 (Just 1)
+        (PerfIndicators 140978 0 9906 131534 27 8 0 0 0 0 (Just 1)
           (Just 'b') (Just 0))
         Nothing
         Nothing
@@ -160,7 +160,7 @@ case_drbd83_sync_want = testFile "proc_drbd83_sync_want.txt" $
     )
     [ DeviceInfo 0 SyncTarget (LocalRemote Secondary Primary)
         (LocalRemote Inconsistent UpToDate) 'C' "r-----"
-        (PerformanceIndicators 0 460288 460160 0 0 28 2 4 1 0 (Just 1)
+        (PerfIndicators 0 460288 460160 0 0 28 2 4 1 0 (Just 1)
           (Just 'f') (Just 588416))
         (Just $ SyncStatus 44.4 588416 1048576 KiloByte (Time 0 0 8) 65736
           (Just 61440) KiloByte Second)
@@ -182,14 +182,14 @@ case_drbd83 = testFile "proc_drbd83.txt" $
     )
     [ DeviceInfo 0 Connected (LocalRemote Primary Secondary)
         (LocalRemote UpToDate UpToDate) 'C' "r----"
-        (PerformanceIndicators 140978 0 9906 131533 27 8 0 0 0 0 (Just 1)
+        (PerfIndicators 140978 0 9906 131533 27 8 0 0 0 0 (Just 1)
           (Just 'b') (Just 0))
         Nothing
         Nothing
         Nothing,
       DeviceInfo 1 Connected (LocalRemote Secondary Primary)
         (LocalRemote UpToDate UpToDate) 'C' "r---"
-        (PerformanceIndicators 0 140980 140980 0 0 8 0 0 0 0 (Just 1) (Just 'f')
+        (PerfIndicators 0 140980 140980 0 0 8 0 0 0 0 (Just 1) (Just 'f')
           (Just 0))
         Nothing
         Nothing
@@ -197,35 +197,35 @@ case_drbd83 = testFile "proc_drbd83.txt" $
       UnconfiguredDevice 2,
       DeviceInfo 4 WFConnection (LocalRemote Primary Unknown)
         (LocalRemote UpToDate DUnknown) 'C' "r----"
-        (PerformanceIndicators 140978 0 9906 131534 27 8 0 0 0 0 (Just 1)
+        (PerfIndicators 140978 0 9906 131534 27 8 0 0 0 0 (Just 1)
           (Just 'b') (Just 0))
         Nothing
         Nothing
         Nothing,
       DeviceInfo 5 Connected (LocalRemote Primary Secondary)
         (LocalRemote UpToDate Diskless) 'C' "r----"
-        (PerformanceIndicators 140978 0 9906 131533 19 8 0 0 0 0 (Just 1)
+        (PerfIndicators 140978 0 9906 131533 19 8 0 0 0 0 (Just 1)
           (Just 'b') (Just 0))
         Nothing
         Nothing
         Nothing,
       DeviceInfo 6 Connected (LocalRemote Secondary Primary)
         (LocalRemote Diskless UpToDate) 'C' "r---"
-        (PerformanceIndicators 0 140978 140978 0 0 8 0 0 0 0 (Just 1) (Just 'f')
+        (PerfIndicators 0 140978 140978 0 0 8 0 0 0 0 (Just 1) (Just 'f')
           (Just 0))
         Nothing
         Nothing
         Nothing,
       DeviceInfo 7 WFConnection (LocalRemote Secondary Unknown)
         (LocalRemote UpToDate DUnknown) 'C' "r---"
-        (PerformanceIndicators 0 140978 140978 0 0 8 0 0 0 0 (Just 1) (Just 'f')
+        (PerfIndicators 0 140978 140978 0 0 8 0 0 0 0 (Just 1) (Just 'f')
           (Just 0))
         Nothing
         Nothing
         Nothing,
       DeviceInfo 8 StandAlone (LocalRemote Secondary Unknown)
         (LocalRemote UpToDate DUnknown) ' ' "r---"
-        (PerformanceIndicators 0 140978 140978 0 0 8 0 0 0 0 (Just 1)
+        (PerfIndicators 0 140978 140978 0 0 8 0 0 0 0 (Just 1)
           (Just 'f') (Just 0))
         Nothing
         Nothing
@@ -242,14 +242,14 @@ case_drbd8 = testFile "proc_drbd8.txt" $
     )
     [ DeviceInfo 0 Connected (LocalRemote Primary Secondary)
         (LocalRemote UpToDate UpToDate) 'C' "r---"
-        (PerformanceIndicators 4375577 0 4446279 674 1067 69 0 0 0 0 Nothing
+        (PerfIndicators 4375577 0 4446279 674 1067 69 0 0 0 0 Nothing
           Nothing Nothing)
         Nothing
         (Just $ AdditionalInfo 0 61 0 0 0 0 0)
         (Just $ AdditionalInfo 0 257 793749 1067 0 0 1067),
       DeviceInfo 1 Connected (LocalRemote Secondary Primary)
         (LocalRemote UpToDate UpToDate) 'C' "r---"
-        (PerformanceIndicators 738320 0 738320 554400 67 0 0 0 0 0 Nothing
+        (PerfIndicators 738320 0 738320 554400 67 0 0 0 0 0 Nothing
           Nothing Nothing)
         Nothing
         (Just $ AdditionalInfo 0 61 0 0 0 0 0)
@@ -257,34 +257,34 @@ case_drbd8 = testFile "proc_drbd8.txt" $
       UnconfiguredDevice 2,
       DeviceInfo 4 WFConnection (LocalRemote Primary Unknown)
         (LocalRemote UpToDate DUnknown) 'C' "r---"
-        (PerformanceIndicators 738320 0 738320 554400 67 0 0 0 0 0 Nothing
+        (PerfIndicators 738320 0 738320 554400 67 0 0 0 0 0 Nothing
           Nothing Nothing)
         Nothing
         (Just $ AdditionalInfo 0 61 0 0 0 0 0)
         (Just $ AdditionalInfo 0 257 92464 67 0 0 67),
       DeviceInfo 5 Connected (LocalRemote Primary Secondary)
         (LocalRemote UpToDate Diskless) 'C' "r---"
-        (PerformanceIndicators 4375581 0 4446283 674 1069 69 0 0 0 0 Nothing
+        (PerfIndicators 4375581 0 4446283 674 1069 69 0 0 0 0 Nothing
           Nothing Nothing)
         Nothing
         (Just $ AdditionalInfo 0 61 0 0 0 0 0)
         (Just $ AdditionalInfo 0 257 793750 1069 0 0 1069),
       DeviceInfo 6 Connected (LocalRemote Secondary Primary)
         (LocalRemote Diskless UpToDate) 'C'  "r---"
-        (PerformanceIndicators 0 4375581 5186925 327 75 214 0 0 0 0 Nothing
+        (PerfIndicators 0 4375581 5186925 327 75 214 0 0 0 0 Nothing
           Nothing Nothing)
         Nothing
         Nothing
         Nothing,
       DeviceInfo 7 WFConnection (LocalRemote Secondary Unknown)
         (LocalRemote UpToDate DUnknown) 'C' "r---"
-        (PerformanceIndicators 0 0 0 0 0 0 0 0 0 0 Nothing Nothing Nothing)
+        (PerfIndicators 0 0 0 0 0 0 0 0 0 0 Nothing Nothing Nothing)
         Nothing
         (Just $ AdditionalInfo 0 61 0 0 0 0 0)
         (Just $ AdditionalInfo 0 257 0 0 0 0 0),
       DeviceInfo 8 StandAlone (LocalRemote Secondary Unknown)
         (LocalRemote UpToDate DUnknown) ' ' "r---"
-        (PerformanceIndicators 0 0 0 0 0 0 0 0 0 0 Nothing Nothing Nothing)
+        (PerfIndicators 0 0 0 0 0 0 0 0 0 0 Nothing Nothing Nothing)
         Nothing
         (Just $ AdditionalInfo 0 61 0 0 0 0 0)
         (Just $ AdditionalInfo 0 257 0 0 0 0 0)
index d20b615..c42b19a 100644 (file)
@@ -105,7 +105,7 @@ versionInfoParser =
 deviceParser :: Parser DeviceInfo
 deviceParser = do
   deviceNum <- skipSpaces *> A.decimal <* A.char ':'
-  cs <- skipSpacesAndString "cs:" connectionStateParser
+  cs <- skipSpacesAndString "cs:" connStateParser
   if cs == Unconfigured
     then do
       _ <- additionalEOL
@@ -115,12 +115,12 @@ deviceParser = do
       ds <- skipSpacesAndString "ds:" $ localRemoteParser diskStateParser
       replicProtocol <- A.space *> A.anyChar
       io <- skipSpaces *> ioFlagsParser <* A.skipWhile isBadEndOfLine
-      perfIndicators <- performanceIndicatorsParser
+      pIndicators <- perfIndicatorsParser
       syncS <- conditionalSyncStatusParser cs
       reS <- optional resyncParser
       act <- optional actLogParser
       _ <- additionalEOL
-      return $ DeviceInfo deviceNum cs ro ds replicProtocol io perfIndicators
+      return $ DeviceInfo deviceNum cs ro ds replicProtocol io pIndicators
                           syncS reS act
 
     where conditionalSyncStatusParser SyncSource = Just <$> syncStatusParser
@@ -132,8 +132,8 @@ deviceParser = do
           additionalEOL = A.skipWhile A.isEndOfLine
 
 -- | The parser for the connection state.
-connectionStateParser :: Parser ConnectionState
-connectionStateParser =
+connStateParser :: Parser ConnState
+connStateParser =
   standAlone
   <|> disconnecting
   <|> unconnected
@@ -224,9 +224,9 @@ ioFlagsParser :: Parser String
 ioFlagsParser = fmap unpack . A.takeWhile $ not . isBadEndOfLine
 
 -- | The parser for performance indicators.
-performanceIndicatorsParser :: Parser PerformanceIndicators
-performanceIndicatorsParser =
-  PerformanceIndicators
+perfIndicatorsParser :: Parser PerfIndicators
+perfIndicatorsParser =
+  PerfIndicators
     <$> skipSpacesAndString "ns:" A.decimal
     <*> skipSpacesAndString "nr:" A.decimal
     <*> skipSpacesAndString "dw:" A.decimal
@@ -295,9 +295,9 @@ sizeUnitParser =
 -- | The parser for recognizing time (hh:mm:ss).
 timeParser :: Parser Time
 timeParser = Time <$> h <*> m <*> s
-  where h = A.decimal :: Parser Integer
-        m = A.char ':' *> A.decimal :: Parser Integer
-        s = A.char ':' *> A.decimal :: Parser Integer
+  where h = A.decimal :: Parser Int
+        m = A.char ':' *> A.decimal :: Parser Int
+        s = A.char ':' *> A.decimal :: Parser Int
 
 -- | The parser for recognizing time units (only the ones actually
 -- found in DRBD files are implemented).
index 79b917f..30ce0c9 100644 (file)
@@ -28,11 +28,11 @@ module Ganeti.Block.Drbd.Types
   ( DRBDStatus(..)
   , VersionInfo(..)
   , DeviceInfo(..)
-  , ConnectionState(..)
+  , ConnState(..)
   , LocalRemote(..)
   , Role(..)
   , DiskState(..)
-  , PerformanceIndicators(..)
+  , PerfIndicators(..)
   , SyncStatus(..)
   , SizeUnit(..)
   , Time(..)
@@ -40,6 +40,11 @@ module Ganeti.Block.Drbd.Types
   , AdditionalInfo(..)
   ) where
 
+import Text.JSON
+import Text.Printf
+
+import Ganeti.JSON
+
 --TODO: consider turning deviceInfos into an IntMap
 -- | Data type contaning all the data about the status of DRBD.
 data DRBDStatus =
@@ -48,6 +53,15 @@ data DRBDStatus =
   , deviceInfos :: [DeviceInfo] -- ^ Per-minor information
   } deriving (Eq, Show)
 
+-- | The DRBDStatus instance of JSON.
+instance JSON DRBDStatus where
+  showJSON d = makeObj
+    [ ("versionInfo", showJSON $ versionInfo d)
+    , ("deviceInfos", showJSONs $ deviceInfos d)
+    ]
+
+  readJSON = error "JSON read instance not implemented for type DRBDStatus"
+
 -- | Data type describing the DRBD version.
 data VersionInfo =
   VersionInfo
@@ -60,26 +74,65 @@ data VersionInfo =
                                -- optionally, when)
   } deriving (Eq, Show)
 
+-- | The VersionInfo instance of JSON.
+instance JSON VersionInfo where
+  showJSON (VersionInfo versionF apiF protoF srcversionF gitHashF buildByF) =
+    optFieldsToObj
+      [ optionalJSField "version" versionF
+      , optionalJSField "api" apiF
+      , optionalJSField "proto" protoF
+      , optionalJSField "srcversion" srcversionF
+      , optionalJSField "gitHash" gitHashF
+      , optionalJSField "buildBy" buildByF
+      ]
+
+  readJSON = error "JSON read instance not implemented for type VersionInfo"
+
 -- | Data type describing a device.
 data DeviceInfo =
   UnconfiguredDevice Int -- ^ An DRBD minor marked as unconfigured
   | -- | A configured DRBD minor
     DeviceInfo
       { minorNumber :: Int -- ^ The minor index of the device
-      , connectionState :: ConnectionState -- ^ State of the connection
+      , connectionState :: ConnState -- ^ State of the connection
       , resourceRoles :: LocalRemote Role -- ^ Roles of the resources
       , diskStates :: LocalRemote DiskState -- ^ Status of the disks
       , replicationProtocol :: Char -- ^ The replication protocol being used
       , ioFlags :: String -- ^ The input/output flags
-      , performanceIndicators :: PerformanceIndicators -- ^ Performance indicators
+      , perfIndicators
+          :: PerfIndicators -- ^ Performance indicators
       , syncStatus :: Maybe SyncStatus -- ^ The status of the syncronization of
-                                     -- the disk (only if it is happening)
+                                       -- the disk (only if it is happening)
       , resync :: Maybe AdditionalInfo -- ^ Additional info by DRBD 8.0
       , actLog :: Maybe AdditionalInfo -- ^ Additional info by DRBD 8.0
       } deriving (Eq, Show)
 
+-- | The DeviceInfo instance of JSON.
+instance JSON DeviceInfo where
+  showJSON (UnconfiguredDevice num) = makeObj
+    [ ("minor", showJSON num)
+    , ("connectionState", showJSON Unconfigured)
+    ]
+  showJSON (DeviceInfo minorNumberF connectionStateF (LocalRemote
+    localRole remoteRole) (LocalRemote localState remoteState)
+    replicProtocolF ioFlagsF perfIndicatorsF syncStatusF _ _) =
+    optFieldsToObj
+    [ Just ("minor", showJSON minorNumberF)
+    , Just ("connectionState", showJSON connectionStateF)
+    , Just ("localRole", showJSON localRole)
+    , Just ("remoteRole", showJSON remoteRole)
+    , Just ("localState", showJSON localState)
+    , Just ("remoteState", showJSON remoteState)
+    , Just ("replicationProtocol", showJSON replicProtocolF)
+    , Just ("ioFlags", showJSON ioFlagsF)
+    , Just ("perfIndicators", showJSON perfIndicatorsF)
+    , optionalJSField "syncStatus" syncStatusF
+    ]
+
+  readJSON = error "JSON read instance not implemented for type DeviceInfo"
+
 -- | Data type describing the state of the connection.
-data ConnectionState
+data ConnState
   = StandAlone     -- ^  No network configuration available
   | Disconnecting  -- ^ Temporary state during disconnection
   | Unconnected    -- ^ Prior to a connection attempt
@@ -105,6 +158,12 @@ data ConnectionState
   | Unconfigured   -- ^ The device is not configured
     deriving (Show, Eq)
 
+-- | The ConnState instance of JSON.
+instance JSON ConnState where
+  showJSON = showJSON . show
+
+  readJSON = error "JSON read instance not implemented for type ConnState"
+
 -- | Algebraic data type describing something that has a local and a remote
 -- value.
 data LocalRemote a =
@@ -119,6 +178,12 @@ data Role = Primary   -- ^ The device role is primary
           | Unknown   -- ^ The device role is unknown
             deriving (Eq, Show)
 
+-- | The Role instance of JSON.
+instance JSON Role where
+  showJSON = showJSON . show
+
+  readJSON = error "JSON read instance not implemented for type Role"
+
 -- | Data type describing disk states.
 data DiskState
   = Diskless     -- ^ No local block device assigned to the DRBD driver
@@ -132,8 +197,14 @@ data DiskState
   | UpToDate     -- ^ Consistent, up-to-date. This is the normal state
     deriving (Eq, Show)
 
+-- | The DiskState instance of JSON.
+instance JSON DiskState where
+  showJSON = showJSON . show
+
+  readJSON = error "JSON read instance not implemented for type DiskState"
+
 -- | Data type containing data about performance indicators.
-data PerformanceIndicators = PerformanceIndicators
+data PerfIndicators = PerfIndicators
   { networkSend :: Int -- ^ KiB of data sent on the network
   , networkReceive :: Int -- ^ KiB of data received from the network
   , diskWrite :: Int -- ^ KiB of data written on local disk
@@ -152,12 +223,32 @@ data PerformanceIndicators = PerformanceIndicators
   , outOfSync :: Maybe Int -- ^ KiB of storage currently out of sync
   } deriving (Eq, Show)
 
+-- | The PerfIndicators instance of JSON.
+instance JSON PerfIndicators where
+  showJSON p = optFieldsToObj
+    [ Just ("networkSend", showJSON $ networkSend p)
+    , Just ("networkReceive", showJSON $ networkReceive p)
+    , Just ("diskWrite", showJSON $ diskWrite p)
+    , Just ("diskRead", showJSON $ diskRead p)
+    , Just ("activityLog", showJSON $ activityLog p)
+    , Just ("bitMap", showJSON $ bitMap p)
+    , Just ("localCount", showJSON $ localCount p)
+    , Just ("pending", showJSON $ pending p)
+    , Just ("unacknowledged", showJSON $ unacknowledged p)
+    , Just ("applicationPending", showJSON $ applicationPending p)
+    , optionalJSField "epochs" $ epochs p
+    , optionalJSField "writeOrder" $ writeOrder p
+    , optionalJSField "outOfSync" $ outOfSync p
+    ]
+
+  readJSON = error "JSON read instance not implemented for type PerfIndicators"
+
 -- | Data type containing data about the synchronization status of a device.
 data SyncStatus =
   SyncStatus
   { percentage      :: Double    -- ^ Percentage of syncronized data
-  , partialSyncSize :: Int       -- ^ Numerator of the fraction of synced data
-  , totalSyncSize   :: Int       -- ^ Denominator of the fraction of
+  , partialSyncSize :: Integer   -- ^ Numerator of the fraction of synced data
+  , totalSyncSize   :: Integer   -- ^ Denominator of the fraction of
                                  -- synced data
   , syncUnit        :: SizeUnit  -- ^ Measurement unit of the previous
                                  -- fraction
@@ -169,19 +260,53 @@ data SyncStatus =
   , speedTimeUnit   :: TimeUnit  -- ^ Time unit of the speed
   } deriving (Eq, Show)
 
+-- | The SyncStatus instance of JSON.
+instance JSON SyncStatus where
+  showJSON s = optFieldsToObj
+    [ Just ("percentage", showJSON $ percentage s)
+    , Just ("progress", showJSON $ show (partialSyncSize s) ++ "/" ++
+        show (totalSyncSize s))
+    , Just ("progressUnit", showJSON $ syncUnit s)
+    , Just ("timeToFinish", showJSON $ timeToFinish s)
+    , Just ("speed", showJSON $ speed s)
+    , optionalJSField "want" $ want s
+    , Just ("speedUnit", showJSON $ show (speedSizeUnit s) ++ "/" ++
+        show (speedTimeUnit s))
+    ]
+
+  readJSON = error "JSON read instance not implemented for type SyncStatus"
+
 -- | Data type describing a size unit for memory.
 data SizeUnit = KiloByte | MegaByte deriving (Eq, Show)
 
+-- | The SizeUnit instance of JSON.
+instance JSON SizeUnit where
+  showJSON = showJSON . show
+
+  readJSON = error "JSON read instance not implemented for type SizeUnit"
+
 -- | Data type describing a time (hh:mm:ss).
 data Time = Time
-  { hour :: Integer
-  , min  :: Integer
-  , sec  :: Integer
+  { hour :: Int
+  , min  :: Int
+  , sec  :: Int
   } deriving (Eq, Show)
 
+-- | The Time instance of JSON.
+instance JSON Time where
+  showJSON (Time h m s) = showJSON (printf "%02d:%02d:%02d" h m s :: String)
+
+  readJSON = error "JSON read instance not implemented for type Time"
+
 -- | Data type describing a time unit.
 data TimeUnit = Second deriving (Eq, Show)
 
+-- | The TimeUnit instance of JSON.
+instance JSON TimeUnit where
+  showJSON Second = showJSON "Second"
+
+  readJSON = error "JSON read instance not implemented for type TimeUnit"
+
 -- | Additional device-specific cache-like information produced by
 -- drbd <= 8.0.
 --