Skip to content

Commit

Permalink
Hlint fixes (#173)
Browse files Browse the repository at this point in the history
* Hlint fixes

- Will require major version bump as some types were changed from data
  to newtype

* ormolu fixes after hlint
  • Loading branch information
donatello authored May 27, 2022
1 parent b91a7af commit d59f45f
Show file tree
Hide file tree
Showing 28 changed files with 136 additions and 144 deletions.
2 changes: 1 addition & 1 deletion examples/FileUploader.hs
Original file line number Diff line number Diff line change
Expand Up @@ -70,5 +70,5 @@ main = do
fPutObject bucket object filepath defaultPutObjectOptions

case res of
Left e -> putStrLn $ "file upload failed due to " ++ (show e)
Left e -> putStrLn $ "file upload failed due to " ++ show e
Right () -> putStrLn "file upload succeeded."
4 changes: 2 additions & 2 deletions examples/GetConfig.hs
Original file line number Diff line number Diff line change
Expand Up @@ -16,7 +16,6 @@
-- See the License for the specific language governing permissions and
-- limitations under the License.
--
{-# LANGUAGE OverloadedStrings #-}

import Network.Minio
import Network.Minio.AdminAPI
Expand All @@ -25,6 +24,7 @@ import Prelude
main :: IO ()
main = do
res <-
runMinio minioPlayCI $
runMinio
minioPlayCI
getConfig
print res
2 changes: 1 addition & 1 deletion examples/GetObject.hs
Original file line number Diff line number Diff line change
Expand Up @@ -37,5 +37,5 @@ main = do
C.connect (gorObjectStream src) $ CB.sinkFileCautious "/tmp/my-object"

case res of
Left e -> putStrLn $ "getObject failed." ++ (show e)
Left e -> putStrLn $ "getObject failed." ++ show e
Right _ -> putStrLn "getObject succeeded."
1 change: 0 additions & 1 deletion examples/Heal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -16,7 +16,6 @@
-- See the License for the specific language governing permissions and
-- limitations under the License.
--
{-# LANGUAGE OverloadedStrings #-}

import Network.Minio
import Network.Minio.AdminAPI
Expand Down
2 changes: 1 addition & 1 deletion examples/ListIncompleteUploads.hs
Original file line number Diff line number Diff line change
Expand Up @@ -36,7 +36,7 @@ main = do
res <-
runMinio minioPlayCI $
runConduit $
listIncompleteUploads bucket Nothing True .| mapM_C (\v -> (liftIO $ print v))
listIncompleteUploads bucket Nothing True .| mapM_C (liftIO . print)
print res

{-
Expand Down
2 changes: 1 addition & 1 deletion examples/ListObjects.hs
Original file line number Diff line number Diff line change
Expand Up @@ -36,7 +36,7 @@ main = do
res <-
runMinio minioPlayCI $
runConduit $
listObjects bucket Nothing True .| mapM_C (\v -> (liftIO $ print v))
listObjects bucket Nothing True .| mapM_C (liftIO . print)
print res

{-
Expand Down
2 changes: 1 addition & 1 deletion examples/PresignedGetObject.hs
Original file line number Diff line number Diff line change
Expand Up @@ -46,7 +46,7 @@ main = do
res <- runMinio minioPlayCI $ do
liftIO $ B.putStrLn "Upload a file that we will fetch with a presigned URL..."
putObject bucket object (CC.repeat "a") (Just kb15) defaultPutObjectOptions
liftIO $ putStrLn $ "Done. Object created at: my-bucket/my-object"
liftIO $ putStrLn "Done. Object created at: my-bucket/my-object"

-- Extract Etag of uploaded object
oi <- statObject bucket object defaultGetObjectOptions
Expand Down
9 changes: 5 additions & 4 deletions examples/PresignedPostPolicy.hs
Original file line number Diff line number Diff line change
Expand Up @@ -55,7 +55,7 @@ main = do
]

case policyE of
Left err -> putStrLn $ show err
Left err -> print err
Right policy -> do
res <- runMinio minioPlayCI $ do
(url, formData) <- presignedPostPolicy policy
Expand All @@ -74,13 +74,14 @@ main = do
formOptions = B.intercalate " " $ map formFn $ H.toList formData

return $
B.intercalate " " $
B.intercalate
" "
["curl", formOptions, "-F file=@/tmp/photo.jpg", url]

case res of
Left e -> putStrLn $ "post-policy error: " ++ (show e)
Left e -> putStrLn $ "post-policy error: " ++ show e
Right cmd -> do
putStrLn $ "Put a photo at /tmp/photo.jpg and run command:\n"
putStrLn "Put a photo at /tmp/photo.jpg and run command:\n"

-- print the generated curl command
Char8.putStrLn cmd
4 changes: 2 additions & 2 deletions examples/SelectObject.hs
Original file line number Diff line number Diff line change
Expand Up @@ -19,7 +19,7 @@
{-# LANGUAGE OverloadedStrings #-}

import qualified Conduit as C
import Control.Monad (when)
import Control.Monad (unless)
import Network.Minio
import Prelude

Expand All @@ -35,7 +35,7 @@ main = do

res <- runMinio minioPlayCI $ do
exists <- bucketExists bucket
when (not exists) $
unless exists $
makeBucket bucket Nothing

C.liftIO $ putStrLn "Uploading csv object"
Expand Down
4 changes: 2 additions & 2 deletions examples/ServerInfo.hs
Original file line number Diff line number Diff line change
Expand Up @@ -16,7 +16,6 @@
-- See the License for the specific language governing permissions and
-- limitations under the License.
--
{-# LANGUAGE OverloadedStrings #-}

import Network.Minio
import Network.Minio.AdminAPI
Expand All @@ -25,6 +24,7 @@ import Prelude
main :: IO ()
main = do
res <-
runMinio minioPlayCI $
runMinio
minioPlayCI
getServerInfo
print res
1 change: 0 additions & 1 deletion examples/ServiceSendRestart.hs
Original file line number Diff line number Diff line change
Expand Up @@ -16,7 +16,6 @@
-- See the License for the specific language governing permissions and
-- limitations under the License.
--
{-# LANGUAGE OverloadedStrings #-}

import Network.Minio
import Network.Minio.AdminAPI
Expand Down
1 change: 0 additions & 1 deletion examples/ServiceSendStop.hs
Original file line number Diff line number Diff line change
Expand Up @@ -16,7 +16,6 @@
-- See the License for the specific language governing permissions and
-- limitations under the License.
--
{-# LANGUAGE OverloadedStrings #-}

import Network.Minio
import Network.Minio.AdminAPI
Expand Down
4 changes: 2 additions & 2 deletions examples/ServiceStatus.hs
Original file line number Diff line number Diff line change
Expand Up @@ -16,7 +16,6 @@
-- See the License for the specific language governing permissions and
-- limitations under the License.
--
{-# LANGUAGE OverloadedStrings #-}

import Network.Minio
import Network.Minio.AdminAPI
Expand All @@ -25,6 +24,7 @@ import Prelude
main :: IO ()
main = do
res <-
runMinio minioPlayCI $
runMinio
minioPlayCI
serviceStatus
print res
1 change: 1 addition & 0 deletions minio-hs.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -58,6 +58,7 @@ common base-settings
, DerivingStrategies
, FlexibleContexts
, FlexibleInstances
, LambdaCase
, MultiParamTypeClasses
, MultiWayIf
, OverloadedStrings
Expand Down
45 changes: 23 additions & 22 deletions src/Network/Minio/API.hs
Original file line number Diff line number Diff line change
Expand Up @@ -130,18 +130,18 @@ getHostPathRegion ri = do
regionMay
)
virtualStyle =
( ( bucket <> "." <> regionHost,
encodeUtf8 $ "/" <> fromMaybe "" (riObject ri),
regionMay
)
( bucket <> "." <> regionHost,
encodeUtf8 $ "/" <> fromMaybe "" (riObject ri),
regionMay
)
if
| isAWSConnectInfo ci ->
return $
if bucketHasPeriods bucket
then pathStyle
else virtualStyle
| otherwise -> return pathStyle
( if isAWSConnectInfo ci
then
return $
if bucketHasPeriods bucket
then pathStyle
else virtualStyle
else return pathStyle
)

buildRequest :: S3ReqInfo -> Minio NC.Request
buildRequest ri = do
Expand Down Expand Up @@ -203,7 +203,7 @@ buildRequest ri = do
existingQueryParams = HT.parseQuery (NC.queryString baseRequest)
updatedQueryParams = existingQueryParams ++ qpToAdd
return $ NClient.setQueryString updatedQueryParams baseRequest
| isStreamingPayload (riPayload ri') && (not $ connectIsSecure ci') ->
| isStreamingPayload (riPayload ri') && not (connectIsSecure ci') ->
-- case 2 from above.
do
(pLen, pSrc) <- case riPayload ri of
Expand All @@ -214,15 +214,16 @@ buildRequest ri = do
| otherwise ->
do
sp' <-
if
| connectIsSecure ci' ->
-- case 1 described above.
return sp
| otherwise ->
-- case 3 described above.
( if connectIsSecure ci'
then -- case 1 described above.
return sp
else
( -- case 3 described above.
do
pHash <- getPayloadSHA256Hash $ riPayload ri'
return $ sp {spPayloadHash = Just pHash}
)
)

let signHeaders = signV4 sp' baseRequest
return $
Expand Down Expand Up @@ -285,8 +286,8 @@ isValidBucketName bucket =
not
( or
[ len < 3 || len > 63,
or (map labelCheck labels),
or (map labelCharsCheck labels),
any labelCheck labels,
any labelCharsCheck labels,
isIPCheck
]
)
Expand Down Expand Up @@ -316,7 +317,7 @@ isValidBucketName bucket =
-- Throws exception iff bucket name is invalid according to AWS rules.
checkBucketNameValidity :: MonadIO m => Bucket -> m ()
checkBucketNameValidity bucket =
when (not $ isValidBucketName bucket) $
unless (isValidBucketName bucket) $
throwIO $
MErrVInvalidBucketName bucket

Expand All @@ -326,6 +327,6 @@ isValidObjectName object =

checkObjectNameValidity :: MonadIO m => Object -> m ()
checkObjectNameValidity object =
when (not $ isValidObjectName object) $
unless (isValidObjectName object) $
throwIO $
MErrVInvalidObjectName object
13 changes: 6 additions & 7 deletions src/Network/Minio/AdminAPI.hs
Original file line number Diff line number Diff line change
Expand Up @@ -429,7 +429,7 @@ instance FromJSON HealStatus where

healPath :: Maybe Bucket -> Maybe Text -> ByteString
healPath bucket prefix = do
if (isJust bucket)
if isJust bucket
then
encodeUtf8 $
"v1/heal/"
Expand Down Expand Up @@ -599,12 +599,11 @@ buildAdminRequest :: AdminReqInfo -> Minio NC.Request
buildAdminRequest areq = do
ci <- asks mcConnInfo
sha256Hash <-
if
| connectIsSecure ci ->
-- if secure connection
return "UNSIGNED-PAYLOAD"
-- otherwise compute sha256
| otherwise -> getPayloadSHA256Hash (ariPayload areq)
if connectIsSecure ci
then -- if secure connection
return "UNSIGNED-PAYLOAD"
else -- otherwise compute sha256
getPayloadSHA256Hash (ariPayload areq)

timeStamp <- liftIO getCurrentTime

Expand Down
Loading

0 comments on commit d59f45f

Please sign in to comment.