Add setConfig/getConfig API (#95)
This commit is contained in:
parent
0cda51804b
commit
d0ddd7f057
30
examples/GetConfig.hs
Executable file
30
examples/GetConfig.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 $
|
||||
getConfig
|
||||
print res
|
||||
32
examples/SetConfig.hs
Executable file
32
examples/SetConfig.hs
Executable file
@ -0,0 +1,32 @@
|
||||
#!/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
|
||||
let config = "{\"version\":\"25\",\"credential\":{\"accessKey\":\"minio\",\"secretKey\":\"minio123\"},\"region\":\"\",\"browser\":\"on\",\"worm\":\"off\",\"domain\":\"\",\"storageclass\":{\"standard\":\"\",\"rrs\":\"\"},\"cache\":{\"drives\":[],\"expiry\":90,\"exclude\":[]},\"notify\":{\"amqp\":{\"2\":{\"enable\":false,\"url\":\"amqp://guest:guest@localhost:5672/\",\"exchange\":\"minio\",\"routingKey\":\"minio\",\"exchangeType\":\"direct\",\"deliveryMode\":0,\"mandatory\":false,\"immediate\":false,\"durable\":false,\"internal\":false,\"noWait\":false,\"autoDeleted\":false}},\"elasticsearch\":{\"1\":{\"enable\":false,\"format\":\"namespace\",\"url\":\"http://localhost:9200\",\"index\":\"minio_events\"}},\"kafka\":{\"1\":{\"enable\":false,\"brokers\":null,\"topic\":\"\"}},\"mqtt\":{\"1\":{\"enable\":false,\"broker\":\"\",\"topic\":\"\",\"qos\":0,\"clientId\":\"\",\"username\":\"\",\"password\":\"\",\"reconnectInterval\":0,\"keepAliveInterval\":0}},\"mysql\":{\"1\":{\"enable\":false,\"format\":\"namespace\",\"dsnString\":\"\",\"table\":\"\",\"host\":\"\",\"port\":\"\",\"user\":\"\",\"password\":\"\",\"database\":\"\"}},\"nats\":{\"1\":{\"enable\":false,\"address\":\"\",\"subject\":\"\",\"username\":\"\",\"password\":\"\",\"token\":\"\",\"secure\":false,\"pingInterval\":0,\"streaming\":{\"enable\":false,\"clusterID\":\"\",\"clientID\":\"\",\"async\":false,\"maxPubAcksInflight\":0}}},\"postgresql\":{\"1\":{\"enable\":false,\"format\":\"namespace\",\"connectionString\":\"\",\"table\":\"\",\"host\":\"\",\"port\":\"\",\"user\":\"\",\"password\":\"\",\"database\":\"\"}},\"redis\":{\"test1\":{\"enable\":true,\"format\":\"namespace\",\"address\":\"127.0.0.1:6379\",\"password\":\"\",\"key\":\"bucketevents_ns\"},\"test2\":{\"enable\":true,\"format\":\"access\",\"address\":\"127.0.0.1:6379\",\"password\":\"\",\"key\":\"bucketevents_log\"}},\"webhook\":{\"1\":{\"enable\":true,\"endpoint\":\"http://localhost:3000\"},\"2\":{\"enable\":true,\"endpoint\":\"http://localhost:3001\"}}}}"
|
||||
setConfig config
|
||||
print res
|
||||
@ -45,6 +45,7 @@ library
|
||||
, Network.Minio.Utils
|
||||
, Network.Minio.XmlGenerator
|
||||
, Network.Minio.XmlParser
|
||||
, Network.Minio.JsonParser
|
||||
build-depends: base >= 4.7 && < 5
|
||||
, protolude >= 0.2 && < 0.3
|
||||
, aeson >= 1.2
|
||||
@ -126,6 +127,8 @@ test-suite minio-hs-live-server-test
|
||||
, Network.Minio.XmlGenerator.Test
|
||||
, Network.Minio.XmlParser
|
||||
, Network.Minio.XmlParser.Test
|
||||
, Network.Minio.JsonParser
|
||||
, Network.Minio.JsonParser.Test
|
||||
build-depends: base
|
||||
, minio-hs
|
||||
, protolude >= 0.1.6
|
||||
@ -232,7 +235,8 @@ test-suite minio-hs-test
|
||||
, Network.Minio.XmlGenerator.Test
|
||||
, Network.Minio.XmlParser
|
||||
, Network.Minio.XmlParser.Test
|
||||
|
||||
, Network.Minio.JsonParser
|
||||
, Network.Minio.JsonParser.Test
|
||||
|
||||
source-repository head
|
||||
type: git
|
||||
|
||||
@ -39,6 +39,11 @@ module Network.Minio.AdminAPI
|
||||
, startHeal
|
||||
, forceStartHeal
|
||||
, getHealStatus
|
||||
|
||||
, SetConfigResult(..)
|
||||
, NodeSummary(..)
|
||||
, setConfig
|
||||
, getConfig
|
||||
) where
|
||||
|
||||
import Data.Aeson (FromJSON, ToJSON, Value (Object),
|
||||
@ -260,6 +265,28 @@ instance FromJSON HealItemType where
|
||||
"bucket-metadata" -> return HealItemBucketMetadata
|
||||
_ -> typeMismatch "HealItemType" (A.String v)
|
||||
|
||||
data NodeSummary = NodeSummary
|
||||
{ nsName :: Text
|
||||
, nsErrSet :: Bool
|
||||
, nsErrMessage :: Text
|
||||
} deriving (Eq, Show)
|
||||
|
||||
instance FromJSON NodeSummary where
|
||||
parseJSON = withObject "NodeSummary" $ \v -> NodeSummary
|
||||
<$> v .: "name"
|
||||
<*> v .: "errSet"
|
||||
<*> v .: "errMsg"
|
||||
|
||||
data SetConfigResult = SetConfigResult
|
||||
{ scrStatus :: Bool
|
||||
, scrNodeSummary :: [NodeSummary]
|
||||
} deriving (Eq, Show)
|
||||
|
||||
instance FromJSON SetConfigResult where
|
||||
parseJSON = withObject "SetConfigResult" $ \v -> SetConfigResult
|
||||
<$> v .: "status"
|
||||
<*> v .: "nodeResults"
|
||||
|
||||
data HealResultItem = HealResultItem
|
||||
{ hriResultIdx :: Int
|
||||
, hriType :: HealItemType
|
||||
@ -317,6 +344,34 @@ healPath bucket prefix = do
|
||||
<> fromMaybe "" prefix
|
||||
else encodeUtf8 $ "v1/heal/"
|
||||
|
||||
-- | Get the current config file from server.
|
||||
getConfig :: Minio ByteString
|
||||
getConfig = do
|
||||
rsp <- executeAdminRequest AdminReqInfo { ariMethod = HT.methodGet
|
||||
, ariPayload = PayloadBS B.empty
|
||||
, ariPayloadHash = Nothing
|
||||
, ariPath = "v1/config"
|
||||
, ariHeaders = []
|
||||
, ariQueryParams = []
|
||||
}
|
||||
return $ LBS.toStrict $ NC.responseBody rsp
|
||||
|
||||
-- | Set a new config to the server.
|
||||
setConfig :: ByteString -> Minio SetConfigResult
|
||||
setConfig config = do
|
||||
rsp <- executeAdminRequest AdminReqInfo { ariMethod = HT.methodPut
|
||||
, ariPayload = PayloadBS config
|
||||
, ariPayloadHash = Nothing
|
||||
, ariPath = "v1/config"
|
||||
, ariHeaders = []
|
||||
, ariQueryParams = []
|
||||
}
|
||||
|
||||
let rspBS = NC.responseBody rsp
|
||||
case eitherDecode rspBS of
|
||||
Right scr -> return scr
|
||||
Left err -> throwIO $ MErrVJsonParse $ T.pack err
|
||||
|
||||
-- | 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.
|
||||
|
||||
42
src/Network/Minio/JsonParser.hs
Normal file
42
src/Network/Minio/JsonParser.hs
Normal file
@ -0,0 +1,42 @@
|
||||
--
|
||||
-- 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.
|
||||
--
|
||||
|
||||
module Network.Minio.JsonParser
|
||||
(
|
||||
parseErrResponseJSON
|
||||
) where
|
||||
|
||||
import Data.Aeson (FromJSON, eitherDecode, parseJSON,
|
||||
withObject, (.:))
|
||||
import qualified Data.Text as T
|
||||
|
||||
import Lib.Prelude
|
||||
|
||||
import Network.Minio.Errors
|
||||
|
||||
data AdminErrJSON = AdminErrJSON { aeCode :: Text
|
||||
, aeMessage :: Text
|
||||
} deriving (Eq, Show)
|
||||
instance FromJSON AdminErrJSON where
|
||||
parseJSON = withObject "AdminErrJSON" $ \v -> AdminErrJSON
|
||||
<$> v .: "Code"
|
||||
<*> v .: "Message"
|
||||
|
||||
parseErrResponseJSON :: (MonadIO m) => LByteString -> m ServiceErr
|
||||
parseErrResponseJSON jsondata =
|
||||
case eitherDecode jsondata of
|
||||
Right (AdminErrJSON code message) -> return $ toServiceErr code message
|
||||
Left err -> throwIO $ MErrVJsonParse $ T.pack err
|
||||
@ -43,6 +43,7 @@ import Lib.Prelude
|
||||
|
||||
import Network.Minio.Data
|
||||
import Network.Minio.Data.ByteString
|
||||
import Network.Minio.JsonParser (parseErrResponseJSON)
|
||||
import Network.Minio.XmlParser (parseErrResponse)
|
||||
|
||||
allocateReadFile :: (MonadUnliftIO m, R.MonadResource m)
|
||||
@ -136,6 +137,9 @@ httpLbs req mgr = do
|
||||
Just "application/xml" -> do
|
||||
sErr <- parseErrResponse $ NC.responseBody resp
|
||||
throwIO sErr
|
||||
Just "application/json" -> do
|
||||
sErr <- parseErrResponseJSON $ NC.responseBody resp
|
||||
throwIO sErr
|
||||
|
||||
_ -> throwIO $ NC.HttpExceptionRequest req $
|
||||
NC.StatusCodeException (void resp) (show resp)
|
||||
|
||||
64
test/Network/Minio/JsonParser/Test.hs
Normal file
64
test/Network/Minio/JsonParser/Test.hs
Normal file
@ -0,0 +1,64 @@
|
||||
--
|
||||
-- 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.
|
||||
--
|
||||
|
||||
module Network.Minio.JsonParser.Test
|
||||
(
|
||||
jsonParserTests
|
||||
) where
|
||||
|
||||
import Test.Tasty
|
||||
import Test.Tasty.HUnit
|
||||
import UnliftIO (MonadUnliftIO)
|
||||
|
||||
import Lib.Prelude
|
||||
|
||||
import Network.Minio.Errors
|
||||
import Network.Minio.JsonParser
|
||||
|
||||
jsonParserTests :: TestTree
|
||||
jsonParserTests = testGroup "JSON Parser Tests"
|
||||
[ testCase "Test parseErrResponseJSON" testParseErrResponseJSON
|
||||
]
|
||||
|
||||
tryValidationErr :: (MonadUnliftIO m) => m a -> m (Either MErrV a)
|
||||
tryValidationErr act = try act
|
||||
|
||||
assertValidationErr :: MErrV -> Assertion
|
||||
assertValidationErr e = assertFailure $ "Failed due to validation error => " ++ show e
|
||||
|
||||
testParseErrResponseJSON :: Assertion
|
||||
testParseErrResponseJSON = do
|
||||
-- 1. Test parsing of an invalid error json.
|
||||
parseResE <- tryValidationErr $ parseErrResponseJSON "ClearlyInvalidJSON"
|
||||
when (isRight parseResE) $
|
||||
assertFailure $ "Parsing should have failed => " ++ show parseResE
|
||||
|
||||
forM_ cases $ \(jsondata, sErr) -> do
|
||||
parseErr <- tryValidationErr $ parseErrResponseJSON jsondata
|
||||
either assertValidationErr (@?= sErr) parseErr
|
||||
|
||||
where
|
||||
cases = [
|
||||
-- 2. Test parsing of a valid error json.
|
||||
("{\"Code\":\"InvalidAccessKeyId\",\"Message\":\"The access key ID you provided does not exist in our records.\",\"Key\":\"\",\"BucketName\":\"\",\"Resource\":\"/minio/admin/v1/info\",\"RequestId\":\"3L137\",\"HostId\":\"3L137\"}",
|
||||
ServiceErr "InvalidAccessKeyId" "The access key ID you provided does not exist in our records."
|
||||
)
|
||||
,
|
||||
-- 3. Test parsing of a valid, empty Resource.
|
||||
("{\"Code\":\"SignatureDoesNotMatch\",\"Message\":\"The request signature we calculated does not match the signature you provided. Check your key and signing method.\",\"Key\":\"\",\"BucketName\":\"\",\"Resource\":\"/minio/admin/v1/info\",\"RequestId\":\"3L137\",\"HostId\":\"3L137\"}",
|
||||
ServiceErr "SignatureDoesNotMatch" "The request signature we calculated does not match the signature you provided. Check your key and signing method."
|
||||
)
|
||||
]
|
||||
Loading…
Reference in New Issue
Block a user