Add admin heal API (#94)
This commit is contained in:
parent
161c9726b9
commit
0cda51804b
34
examples/Heal.hs
Executable file
34
examples/Heal.hs
Executable file
@ -0,0 +1,34 @@
|
||||
#!/usr/bin/env stack
|
||||
-- stack --resolver lts-11.1 runghc --package minio-hs
|
||||
|
||||
--
|
||||
-- Minio Haskell SDK, (C) 2018 Minio, Inc.
|
||||
--
|
||||
-- Licensed under the Apache License, Version 2.0 (the "License");
|
||||
-- you may not use this file except in compliance with the License.
|
||||
-- You may obtain a copy of the License at
|
||||
--
|
||||
-- http://www.apache.org/licenses/LICENSE-2.0
|
||||
--
|
||||
-- Unless required by applicable law or agreed to in writing, software
|
||||
-- distributed under the License is distributed on an "AS IS" BASIS,
|
||||
-- WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
|
||||
-- See the License for the specific language governing permissions and
|
||||
-- limitations under the License.
|
||||
--
|
||||
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
import Network.Minio
|
||||
import Network.Minio.AdminAPI
|
||||
|
||||
import Prelude
|
||||
|
||||
main :: IO ()
|
||||
main = do
|
||||
res <- runMinio def $
|
||||
do
|
||||
hsr <- startHeal Nothing Nothing HealOpts { hoRecursive = True
|
||||
, hoDryRun = False
|
||||
}
|
||||
getHealStatus Nothing Nothing (hsrClientToken hsr)
|
||||
print res
|
||||
30
examples/ServerInfo.hs
Executable file
30
examples/ServerInfo.hs
Executable file
@ -0,0 +1,30 @@
|
||||
#!/usr/bin/env stack
|
||||
-- stack --resolver lts-11.1 runghc --package minio-hs
|
||||
|
||||
--
|
||||
-- Minio Haskell SDK, (C) 2018 Minio, Inc.
|
||||
--
|
||||
-- Licensed under the Apache License, Version 2.0 (the "License");
|
||||
-- you may not use this file except in compliance with the License.
|
||||
-- You may obtain a copy of the License at
|
||||
--
|
||||
-- http://www.apache.org/licenses/LICENSE-2.0
|
||||
--
|
||||
-- Unless required by applicable law or agreed to in writing, software
|
||||
-- distributed under the License is distributed on an "AS IS" BASIS,
|
||||
-- WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
|
||||
-- See the License for the specific language governing permissions and
|
||||
-- limitations under the License.
|
||||
--
|
||||
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
import Network.Minio
|
||||
import Network.Minio.AdminAPI
|
||||
|
||||
import Prelude
|
||||
|
||||
main :: IO ()
|
||||
main = do
|
||||
res <- runMinio def $
|
||||
getServerInfo
|
||||
print res
|
||||
@ -19,7 +19,7 @@ module Network.Minio.AdminAPI
|
||||
--------------------
|
||||
-- | Provides Minio admin API and related types. It is in
|
||||
-- experimental state.
|
||||
ErasureSets(..)
|
||||
DriveInfo(..)
|
||||
, ErasureInfo(..)
|
||||
, Backend(..)
|
||||
, ConnStats(..)
|
||||
@ -31,13 +31,25 @@ module Network.Minio.AdminAPI
|
||||
, SIData(..)
|
||||
, ServerInfo(..)
|
||||
, getServerInfo
|
||||
|
||||
, HealOpts(..)
|
||||
, HealResultItem(..)
|
||||
, HealStatus(..)
|
||||
, HealStartResp(..)
|
||||
, startHeal
|
||||
, forceStartHeal
|
||||
, getHealStatus
|
||||
) where
|
||||
|
||||
import Data.Aeson (FromJSON, Value (Object),
|
||||
eitherDecode, parseJSON, withObject,
|
||||
(.:))
|
||||
import Data.Aeson (FromJSON, ToJSON, Value (Object),
|
||||
eitherDecode, object, pairs,
|
||||
parseJSON, toEncoding, toJSON,
|
||||
withObject, withText, (.:), (.:?),
|
||||
(.=))
|
||||
import qualified Data.Aeson as A
|
||||
import Data.Aeson.Types (typeMismatch)
|
||||
import qualified Data.ByteString as B
|
||||
import qualified Data.ByteString.Lazy as LBS
|
||||
import qualified Data.Text as T
|
||||
import Data.Time (NominalDiffTime, getCurrentTime)
|
||||
import Network.HTTP.Conduit (Response)
|
||||
@ -53,14 +65,14 @@ import Network.Minio.Errors
|
||||
import Network.Minio.Sign.V4
|
||||
import Network.Minio.Utils
|
||||
|
||||
data ErasureSets = ErasureSets
|
||||
{ esUuid :: Text
|
||||
, esEndpoint :: Text
|
||||
, esState :: Text
|
||||
} deriving (Eq, Show)
|
||||
data DriveInfo = DriveInfo
|
||||
{ diUuid :: Text
|
||||
, diEndpoint :: Text
|
||||
, diState :: Text
|
||||
} deriving (Eq, Show)
|
||||
|
||||
instance FromJSON ErasureSets where
|
||||
parseJSON = withObject "ErasureSets" $ \v -> ErasureSets
|
||||
instance FromJSON DriveInfo where
|
||||
parseJSON = withObject "DriveInfo" $ \v -> DriveInfo
|
||||
<$> v .: "uuid"
|
||||
<*> v .: "endpoint"
|
||||
<*> v .: "state"
|
||||
@ -75,7 +87,7 @@ data ErasureInfo = ErasureInfo
|
||||
, eiOfflineDisks :: Int
|
||||
, eiStandard :: StorageClass
|
||||
, eiReducedRedundancy :: StorageClass
|
||||
, eiSets :: [[ErasureSets]]
|
||||
, eiSets :: [[DriveInfo]]
|
||||
} deriving (Eq, Show)
|
||||
|
||||
instance FromJSON ErasureInfo where
|
||||
@ -198,18 +210,170 @@ data ServerInfo = ServerInfo
|
||||
} deriving (Eq, Show)
|
||||
|
||||
instance FromJSON ServerInfo where
|
||||
parseJSON = withObject "ServerInfo" $ \v -> do
|
||||
err <- v .: "error"
|
||||
addr <- v .: "addr"
|
||||
d <- v .: "data"
|
||||
return $ ServerInfo err addr d
|
||||
parseJSON = withObject "ServerInfo" $ \v -> ServerInfo
|
||||
<$> v .: "error"
|
||||
<*> v .: "addr"
|
||||
<*> v .: "data"
|
||||
|
||||
adminPath :: ByteString
|
||||
adminPath = "/minio/admin"
|
||||
|
||||
data HealStartResp = HealStartResp
|
||||
{ hsrClientToken :: Text
|
||||
, hsrClientAddr :: Text
|
||||
, hsrStartTime :: UTCTime
|
||||
} deriving (Eq, Show)
|
||||
|
||||
instance FromJSON HealStartResp where
|
||||
parseJSON = withObject "HealStartResp" $ \v -> HealStartResp
|
||||
<$> v .: "clientToken"
|
||||
<*> v .: "clientAddress"
|
||||
<*> v .: "startTime"
|
||||
|
||||
data HealOpts = HealOpts
|
||||
{ hoRecursive :: Bool
|
||||
, hoDryRun :: Bool
|
||||
} deriving (Eq, Show)
|
||||
|
||||
instance ToJSON HealOpts where
|
||||
toJSON (HealOpts r d) =
|
||||
object ["recursive" .= r, "dryRun" .= d]
|
||||
toEncoding (HealOpts r d) =
|
||||
pairs ("recursive" .= r <> "dryRun" .= d)
|
||||
|
||||
instance FromJSON HealOpts where
|
||||
parseJSON = withObject "HealOpts" $ \v -> HealOpts
|
||||
<$> v .: "recursive"
|
||||
<*> v .: "dryRun"
|
||||
|
||||
data HealItemType = HealItemMetadata
|
||||
| HealItemBucket
|
||||
| HealItemBucketMetadata
|
||||
| HealItemObject
|
||||
deriving (Eq, Show)
|
||||
|
||||
instance FromJSON HealItemType where
|
||||
parseJSON = withText "HealItemType" $ \v -> case v of
|
||||
"metadata" -> return HealItemMetadata
|
||||
"bucket" -> return HealItemBucket
|
||||
"object" -> return HealItemObject
|
||||
"bucket-metadata" -> return HealItemBucketMetadata
|
||||
_ -> typeMismatch "HealItemType" (A.String v)
|
||||
|
||||
data HealResultItem = HealResultItem
|
||||
{ hriResultIdx :: Int
|
||||
, hriType :: HealItemType
|
||||
, hriBucket :: Bucket
|
||||
, hriObject :: Object
|
||||
, hriDetail :: Text
|
||||
, hriParityBlocks :: Maybe Int
|
||||
, hriDataBlocks :: Maybe Int
|
||||
, hriDiskCount :: Int
|
||||
, hriSetCount :: Int
|
||||
, hriObjectSize :: Int
|
||||
, hriBefore :: [DriveInfo]
|
||||
, hriAfter :: [DriveInfo]
|
||||
} deriving (Eq, Show)
|
||||
|
||||
instance FromJSON HealResultItem where
|
||||
parseJSON = withObject "HealResultItem" $ \v -> HealResultItem
|
||||
<$> v .: "resultId"
|
||||
<*> v .: "type"
|
||||
<*> v .: "bucket"
|
||||
<*> v .: "object"
|
||||
<*> v .: "detail"
|
||||
<*> v .:? "parityBlocks"
|
||||
<*> v .:? "dataBlocks"
|
||||
<*> v .: "diskCount"
|
||||
<*> v .: "setCount"
|
||||
<*> v .: "objectSize"
|
||||
<*> (do before <- v .: "before"
|
||||
before .: "drives")
|
||||
<*> (do after <- v .: "after"
|
||||
after .: "drives")
|
||||
|
||||
data HealStatus = HealStatus
|
||||
{ hsSummary :: Text
|
||||
, hsStartTime :: UTCTime
|
||||
, hsSettings :: HealOpts
|
||||
, hsNumDisks :: Int
|
||||
, hsFailureDetail :: Maybe Text
|
||||
, hsItems :: Maybe [HealResultItem]
|
||||
} deriving (Eq, Show)
|
||||
|
||||
instance FromJSON HealStatus where
|
||||
parseJSON = withObject "HealStatus" $ \v -> HealStatus
|
||||
<$> v .: "Summary"
|
||||
<*> v .: "StartTime"
|
||||
<*> v .: "Settings"
|
||||
<*> v .: "NumDisks"
|
||||
<*> v .:? "Detail"
|
||||
<*> v .: "Items"
|
||||
|
||||
healPath :: Maybe Bucket -> Maybe Text -> ByteString
|
||||
healPath bucket prefix = do
|
||||
if (isJust bucket)
|
||||
then encodeUtf8 $ "v1/heal/" <> fromMaybe "" bucket <> "/"
|
||||
<> fromMaybe "" prefix
|
||||
else encodeUtf8 $ "v1/heal/"
|
||||
|
||||
-- | Get the progress of currently running heal task, this API should be
|
||||
-- invoked right after `startHeal`. `token` is obtained after `startHeal`
|
||||
-- which should be used to get the heal status.
|
||||
getHealStatus :: Maybe Bucket -> Maybe Text -> Text -> Minio HealStatus
|
||||
getHealStatus bucket prefix token = do
|
||||
when (isNothing bucket && isJust prefix) $ throwIO MErrVInvalidHealPath
|
||||
let qparams = HT.queryTextToQuery [("clientToken", Just token)]
|
||||
rsp <- executeAdminRequest AdminReqInfo { ariMethod = HT.methodPost
|
||||
, ariPayload = PayloadBS B.empty
|
||||
, ariPayloadHash = Nothing
|
||||
, ariPath = healPath bucket prefix
|
||||
, ariHeaders = []
|
||||
, ariQueryParams = qparams
|
||||
}
|
||||
let rspBS = NC.responseBody rsp
|
||||
case eitherDecode rspBS of
|
||||
Right hs -> return hs
|
||||
Left err -> throwIO $ MErrVJsonParse $ T.pack err
|
||||
|
||||
doHeal :: Maybe Bucket -> Maybe Text -> HealOpts -> Bool -> Minio HealStartResp
|
||||
doHeal bucket prefix opts forceStart = do
|
||||
when (isNothing bucket && isJust prefix) $ throwIO MErrVInvalidHealPath
|
||||
let payload = PayloadBS $ LBS.toStrict $ A.encode opts
|
||||
let qparams = bool [] (HT.queryTextToQuery [("forceStart", Just "true")])
|
||||
forceStart
|
||||
|
||||
rsp <- executeAdminRequest AdminReqInfo { ariMethod = HT.methodPost
|
||||
, ariPayload = payload
|
||||
, ariPayloadHash = Nothing
|
||||
, ariPath = healPath bucket prefix
|
||||
, ariHeaders = []
|
||||
, ariQueryParams = qparams
|
||||
}
|
||||
|
||||
let rspBS = NC.responseBody rsp
|
||||
case eitherDecode rspBS of
|
||||
Right hsr -> return hsr
|
||||
Left err -> throwIO $ MErrVJsonParse $ T.pack err
|
||||
|
||||
-- | Start a heal sequence that scans data under given (possible empty)
|
||||
-- `bucket` and `prefix`. The `recursive` bool turns on recursive
|
||||
-- traversal under the given path. `dryRun` does not mutate on-disk data,
|
||||
-- but performs data validation. Two heal sequences on overlapping paths
|
||||
-- may not be initiated. The progress of a heal should be followed using
|
||||
-- the `HealStatus` API. The server accumulates results of the heal
|
||||
-- traversal and waits for the client to receive and acknowledge
|
||||
-- them using the status API
|
||||
startHeal :: Maybe Bucket -> Maybe Text -> HealOpts -> Minio HealStartResp
|
||||
startHeal bucket prefix opts = doHeal bucket prefix opts False
|
||||
|
||||
-- | Similar to start a heal sequence, but force start a new heal sequence
|
||||
-- even if an active heal is under progress.
|
||||
forceStartHeal :: Maybe Bucket -> Maybe Text -> HealOpts -> Minio HealStartResp
|
||||
forceStartHeal bucket prefix opts = doHeal bucket prefix opts True
|
||||
|
||||
-- | Fetches information for all cluster nodes, such as server
|
||||
-- properties, storage information, network statistics, etc.
|
||||
|
||||
getServerInfo :: Minio [ServerInfo]
|
||||
getServerInfo = do
|
||||
rsp <- executeAdminRequest AdminReqInfo { ariMethod = HT.methodGet
|
||||
|
||||
@ -39,6 +39,7 @@ data MErrV = MErrVSinglePUTSizeExceeded Int64
|
||||
| MErrVInvalidObjectName Text
|
||||
| MErrVInvalidUrlExpiry Int
|
||||
| MErrVJsonParse Text
|
||||
| MErrVInvalidHealPath
|
||||
deriving (Show, Eq)
|
||||
|
||||
instance Exception MErrV
|
||||
|
||||
@ -17,7 +17,9 @@
|
||||
module Network.Minio.API.Test
|
||||
( bucketNameValidityTests
|
||||
, objectNameValidityTests
|
||||
, parseJSONTests
|
||||
, parseServerInfoJSONTest
|
||||
, parseHealStatusTest
|
||||
, parseHealStartRespTest
|
||||
) where
|
||||
|
||||
import Data.Aeson (eitherDecode)
|
||||
@ -53,8 +55,8 @@ objectNameValidityTests = testGroup "Object Name Validity Tests"
|
||||
, testCase "Has unicode characters" $ assertBool' $ isValidObjectName "日本国"
|
||||
]
|
||||
|
||||
parseJSONTests :: TestTree
|
||||
parseJSONTests = testGroup "Parse Minio Admin API JSON parser Tests" $
|
||||
parseServerInfoJSONTest :: TestTree
|
||||
parseServerInfoJSONTest = testGroup "Parse Minio Admin API ServerInfo JSON test" $
|
||||
map (\(tName, tDesc, tfn, tVal) -> testCase tName $ assertBool tDesc $
|
||||
tfn (eitherDecode tVal :: Either [Char] [ServerInfo])) testCases
|
||||
where
|
||||
@ -67,3 +69,34 @@ parseJSONTests = testGroup "Parse Minio Admin API JSON parser Tests" $
|
||||
erasureJSON = "[{\"error\":\"\",\"addr\":\"192.168.1.218:9000\",\"data\":{\"storage\":{\"Used\":83084,\"Backend\":{\"Type\":2,\"OnlineDisks\":4,\"OfflineDisks\":0,\"StandardSCData\":2,\"StandardSCParity\":2,\"RRSCData\":2,\"RRSCParity\":2,\"Sets\":[[{\"uuid\":\"16ec6f2c-9197-4787-904a-36bb2c2683f8\",\"endpoint\":\"/tmp/1\",\"state\":\"ok\"},{\"uuid\":\"4052e086-ef99-4aa5-ae2b-8e27559432f6\",\"endpoint\":\"/tmp/2\",\"state\":\"ok\"},{\"uuid\":\"d0639950-ddd3-45b0-93ca-fd86f5d79f72\",\"endpoint\":\"/tmp/3\",\"state\":\"ok\"},{\"uuid\":\"30ec68c0-37e1-4592-82c1-26b143c0ac10\",\"endpoint\":\"/tmp/4\",\"state\":\"ok\"}]]}},\"network\":{\"transferred\":404,\"received\":0},\"http\":{\"totalHEADs\":{\"count\":0,\"avgDuration\":\"0s\"},\"successHEADs\":{\"count\":0,\"avgDuration\":\"0s\"},\"totalGETs\":{\"count\":0,\"avgDuration\":\"0s\"},\"successGETs\":{\"count\":0,\"avgDuration\":\"0s\"},\"totalPUTs\":{\"count\":0,\"avgDuration\":\"0s\"},\"successPUTs\":{\"count\":0,\"avgDuration\":\"0s\"},\"totalPOSTs\":{\"count\":0,\"avgDuration\":\"0s\"},\"successPOSTs\":{\"count\":0,\"avgDuration\":\"0s\"},\"totalDELETEs\":{\"count\":0,\"avgDuration\":\"0s\"},\"successDELETEs\":{\"count\":0,\"avgDuration\":\"0s\"}},\"server\":{\"uptime\":2738903073,\"version\":\"DEVELOPMENT.GOGET\",\"commitID\":\"DEVELOPMENT.GOGET\",\"region\":\"\",\"sqsARN\":[]}}}]"
|
||||
|
||||
invalidJSON = "[{\"error\":\"\",\"addr\":\"192.168.1.218:9000\",\"data\":{\"storage\":{\"Used\":83084,\"Backend\":{\"Type\":42,\"OnlineDisks\":4,\"OfflineDisks\":0,\"StandardSCData\":2,\"StandardSCParity\":2,\"RRSCData\":2,\"RRSCParity\":2,\"Sets\":[[{\"uuid\":\"16ec6f2c-9197-4787-904a-36bb2c2683f8\",\"endpoint\":\"/tmp/1\",\"state\":\"ok\"},{\"uuid\":\"4052e086-ef99-4aa5-ae2b-8e27559432f6\",\"endpoint\":\"/tmp/2\",\"state\":\"ok\"},{\"uuid\":\"d0639950-ddd3-45b0-93ca-fd86f5d79f72\",\"endpoint\":\"/tmp/3\",\"state\":\"ok\"},{\"uuid\":\"30ec68c0-37e1-4592-82c1-26b143c0ac10\",\"endpoint\":\"/tmp/4\",\"state\":\"ok\"}]]}},\"network\":{\"transferred\":404,\"received\":0},\"http\":{\"totalHEADs\":{\"count\":0,\"avgDuration\":\"0s\"},\"successHEADs\":{\"count\":0,\"avgDuration\":\"0s\"},\"totalGETs\":{\"count\":0,\"avgDuration\":\"0s\"},\"successGETs\":{\"count\":0,\"avgDuration\":\"0s\"},\"totalPUTs\":{\"count\":0,\"avgDuration\":\"0s\"},\"successPUTs\":{\"count\":0,\"avgDuration\":\"0s\"},\"totalPOSTs\":{\"count\":0,\"avgDuration\":\"0s\"},\"successPOSTs\":{\"count\":0,\"avgDuration\":\"0s\"},\"totalDELETEs\":{\"count\":0,\"avgDuration\":\"0s\"},\"successDELETEs\":{\"count\":0,\"avgDuration\":\"0s\"}},\"server\":{\"uptime\":2738903073,\"version\":\"DEVELOPMENT.GOGET\",\"commitID\":\"DEVELOPMENT.GOGET\",\"region\":\"\",\"sqsARN\":[]}}}]"
|
||||
|
||||
parseHealStatusTest :: TestTree
|
||||
parseHealStatusTest = testGroup "Parse Minio Admin API HealStatus JSON test" $
|
||||
map (\(tName, tDesc, tfn, tVal) -> testCase tName $ assertBool tDesc $
|
||||
tfn (eitherDecode tVal :: Either [Char] HealStatus)) testCases
|
||||
|
||||
where
|
||||
testCases = [ ("Good", "Verify heal result item for erasure backend", isRight, erasureJSON')
|
||||
, ("Corrupted", "Verify heal result item for erasure backend", isLeft, invalidJSON')
|
||||
, ("Incorrect Value", "Verify heal result item for erasure backend", isLeft, invalidItemType)
|
||||
]
|
||||
|
||||
erasureJSON' = "{\"Summary\":\"finished\",\"StartTime\":\"2018-06-05T08:09:47.644465513Z\",\"NumDisks\":4,\"Settings\":{\"recursive\":false,\"dryRun\":false},\"Items\":[{\"resultId\":1,\"type\":\"metadata\",\"bucket\":\"\",\"object\":\"\",\"detail\":\"disk-format\",\"diskCount\":4,\"setCount\":1,\"before\":{\"drives\":[{\"uuid\":\"c3487166-b8a4-481a-b1e7-fb9b249e2500\",\"endpoint\":\"/tmp/1\",\"state\":\"ok\"},{\"uuid\":\"55a6e787-184f-4e4c-bf09-03dcada658a9\",\"endpoint\":\"/tmp/2\",\"state\":\"ok\"},{\"uuid\":\"f035d8c3-fca1-4407-b89c-38c2bcf4a641\",\"endpoint\":\"/tmp/3\",\"state\":\"ok\"},{\"uuid\":\"4f8b79d3-db90-4c1d-87c2-35a28b0d9a13\",\"endpoint\":\"/tmp/4\",\"state\":\"ok\"}]},\"after\":{\"drives\":[{\"uuid\":\"c3487166-b8a4-481a-b1e7-fb9b249e2500\",\"endpoint\":\"/tmp/1\",\"state\":\"ok\"},{\"uuid\":\"55a6e787-184f-4e4c-bf09-03dcada658a9\",\"endpoint\":\"/tmp/2\",\"state\":\"ok\"},{\"uuid\":\"f035d8c3-fca1-4407-b89c-38c2bcf4a641\",\"endpoint\":\"/tmp/3\",\"state\":\"ok\"},{\"uuid\":\"4f8b79d3-db90-4c1d-87c2-35a28b0d9a13\",\"endpoint\":\"/tmp/4\",\"state\":\"ok\"}]},\"objectSize\":0}]}"
|
||||
|
||||
invalidJSON' = "{\"Summary\":\"finished\",\"StartTime\":\"2018-06-05T08:09:47.644465513Z\",\"NumDisks\":4,\"Settings\":{\"recursive\":false,\"dryRun\":false},\"Items\":[{\"resultId\":1,\"type\":\"metadata\",\"bucket\":\"\",\"object\":\"\",\"detail\":\"disk-format\",\"diskCount\":4,\"setCount\":1,\"before\":{\"drives\":[{\"uuid\":\"c3487166-b8a4-481a-b1e7-fb9b249e2500\",\"endpoint\":\"/tmp/1\",\"state\":\"ok\"},{\"uuid\":\"55a6e787-184f-4e4c-bf09-03dcada658a9\",\"endpoint\":\"/tmp/2\",\"state\":\"ok\"},{\"uuid\":\"f035d8c3-fca1-4407-b89c-38c2bcf4a641\",\"endpoint\":\"/tmp/3\",\"state\":\"ok\"},{\"uuid\":\"4f8b79d3-db90-4c1d-87c2-35a28b0d9a13\",\"endpoint\":\"/tmp/4\",\"state\":\"ok\"}]},\"after\":{\"drives\":[{\"uuid\":\"c3487166-b8a4-481a-b1e7-fb9b249e2500\",\"endpoint\":\"/tmp/1\",\"state\":\"ok\"},{\"uuid\":\"55a6e787-184f-4e4c-bf09-03dcada658a9\",\"endpoint\":\"/tmp/2\",\"state\":\"ok\"},{\"uuid\":\"f035d8c3-fca1-4407-b89c-38c2bcf4a641\",\"endpoint\":\"/tmp/3\",\"state\":\"ok\"},{\"uuid\":\"4f8b79d3-db90-4c1d-87c2-35a28b0d9a13\",\"endpoint\":\"/tmp/4\",\"state\":\"ok\"}]},\"objectSize\":0}]"
|
||||
|
||||
invalidItemType = "{\"Summary\":\"finished\",\"StartTime\":\"2018-06-05T08:09:47.644465513Z\",\"NumDisks\":4,\"Settings\":{\"recursive\":false,\"dryRun\":false},\"Items\":[{\"resultId\":1,\"type\":\"hello\",\"bucket\":\"\",\"object\":\"\",\"detail\":\"disk-format\",\"diskCount\":4,\"setCount\":1,\"before\":{\"drives\":[{\"uuid\":\"c3487166-b8a4-481a-b1e7-fb9b249e2500\",\"endpoint\":\"/tmp/1\",\"state\":\"ok\"},{\"uuid\":\"55a6e787-184f-4e4c-bf09-03dcada658a9\",\"endpoint\":\"/tmp/2\",\"state\":\"ok\"},{\"uuid\":\"f035d8c3-fca1-4407-b89c-38c2bcf4a641\",\"endpoint\":\"/tmp/3\",\"state\":\"ok\"},{\"uuid\":\"4f8b79d3-db90-4c1d-87c2-35a28b0d9a13\",\"endpoint\":\"/tmp/4\",\"state\":\"ok\"}]},\"after\":{\"drives\":[{\"uuid\":\"c3487166-b8a4-481a-b1e7-fb9b249e2500\",\"endpoint\":\"/tmp/1\",\"state\":\"ok\"},{\"uuid\":\"55a6e787-184f-4e4c-bf09-03dcada658a9\",\"endpoint\":\"/tmp/2\",\"state\":\"ok\"},{\"uuid\":\"f035d8c3-fca1-4407-b89c-38c2bcf4a641\",\"endpoint\":\"/tmp/3\",\"state\":\"ok\"},{\"uuid\":\"4f8b79d3-db90-4c1d-87c2-35a28b0d9a13\",\"endpoint\":\"/tmp/4\",\"state\":\"ok\"}]},\"objectSize\":0}]}"
|
||||
|
||||
parseHealStartRespTest :: TestTree
|
||||
parseHealStartRespTest = testGroup "Parse Minio Admin API HealStartResp JSON test" $
|
||||
map (\(tName, tDesc, tfn, tVal) -> testCase tName $ assertBool tDesc $
|
||||
tfn (eitherDecode tVal :: Either [Char] HealStartResp)) testCases
|
||||
|
||||
where
|
||||
testCases = [ ("Good", "Verify heal start response for erasure backend", isRight, hsrJSON)
|
||||
, ("Missing Token", "Verify heal start response for erasure backend", isLeft, missingTokenJSON)
|
||||
]
|
||||
|
||||
hsrJSON = "{\"clientToken\":\"3a3aca49-77dd-4b78-bba7-0978f119b23e\",\"clientAddress\":\"127.0.0.1\",\"startTime\":\"2018-06-05T08:09:47.644394493Z\"}"
|
||||
|
||||
missingTokenJSON = "{\"clientAddress\":\"127.0.0.1\",\"startTime\":\"2018-06-05T08:09:47.644394493Z\"}"
|
||||
|
||||
@ -117,6 +117,8 @@ unitTests :: TestTree
|
||||
unitTests = testGroup "Unit tests" [ xmlGeneratorTests, xmlParserTests
|
||||
, bucketNameValidityTests
|
||||
, objectNameValidityTests
|
||||
, parseJSONTests
|
||||
, parseServerInfoJSONTest
|
||||
, parseHealStatusTest
|
||||
, parseHealStartRespTest
|
||||
, limitedMapConcurrentlyTests
|
||||
]
|
||||
|
||||
Loading…
Reference in New Issue
Block a user