Build with GHC 8.8 (#137)
* Fix to build with GHC 8.8 and fix error handling bug To work with the addition of MonadFail constraint to parseTimeM in the time library, the underlying monad was changed from Either to Maybe as it has a MonadFail instance. * Update build to run tests against local minio server
This commit is contained in:
parent
1e6579b02b
commit
410d342cd5
16
.travis.yml
16
.travis.yml
@ -4,7 +4,7 @@ language: haskell
|
||||
git:
|
||||
depth: 5
|
||||
|
||||
cabal: "2.4"
|
||||
cabal: "3.0"
|
||||
|
||||
cache:
|
||||
directories:
|
||||
@ -19,11 +19,21 @@ matrix:
|
||||
- ghc: 8.2.2
|
||||
- ghc: 8.4.4
|
||||
- ghc: 8.6.5
|
||||
- ghc: 8.8.1
|
||||
|
||||
# Stack
|
||||
- ghc: 8.6.5
|
||||
env: STACK_YAML="$TRAVIS_BUILD_DIR/stack.yaml"
|
||||
|
||||
before_install:
|
||||
- sudo apt-get install devscripts
|
||||
- mkdir /tmp/minio /tmp/certs
|
||||
- (cd /tmp/minio; wget https://dl.min.io/server/minio/release/linux-amd64/minio; chmod +x ./minio)
|
||||
- (cd /tmp/certs; openssl req -newkey rsa:2048 -nodes -keyout private.key -x509 -days 36500 -out public.crt -subj "/C=US/ST=NRW/L=Earth/O=CompanyName/OU=IT/CN=localhost/emailAddress=email@example.com")
|
||||
- sudo cp /tmp/certs/public.crt /usr/local/share/ca-certificates/
|
||||
- sudo update-ca-certificates
|
||||
- MINIO_ACCESS_KEY=minio MINIO_SECRET_KEY=minio123 /tmp/minio/minio server --quiet --certs-dir /tmp/certs data 2>&1 > minio.log &
|
||||
|
||||
install:
|
||||
- |
|
||||
if [ -z "$STACK_YAML" ]; then
|
||||
@ -43,9 +53,9 @@ install:
|
||||
script:
|
||||
- |
|
||||
if [ -z "$STACK_YAML" ]; then
|
||||
cabal new-test --enable-tests
|
||||
MINIO_LOCAL=1 MINIO_SECURE=1 cabal new-test --enable-tests
|
||||
else
|
||||
stack test --system-ghc
|
||||
MINIO_LOCAL=1 MINIO_SECURE=1 stack test --system-ghc
|
||||
fi
|
||||
|
||||
notifications:
|
||||
|
||||
@ -21,10 +21,9 @@
|
||||
module Network.Minio.Data where
|
||||
|
||||
import qualified Conduit as C
|
||||
import Control.Concurrent.MVar (MVar)
|
||||
import qualified Control.Concurrent.MVar as M
|
||||
import Control.Monad.IO.Unlift (MonadUnliftIO, UnliftIO (..),
|
||||
askUnliftIO, withUnliftIO)
|
||||
import Control.Monad.IO.Unlift (UnliftIO (..), askUnliftIO,
|
||||
withUnliftIO)
|
||||
import Control.Monad.Trans.Resource
|
||||
import qualified Data.Aeson as A
|
||||
import qualified Data.ByteArray as BA
|
||||
|
||||
@ -26,7 +26,6 @@ import qualified Data.Conduit.Binary as CB
|
||||
import qualified Data.HashMap.Strict as H
|
||||
import qualified Data.List as List
|
||||
import qualified Data.Text as T
|
||||
import Data.Text.Encoding.Error (lenientDecode)
|
||||
import Data.Text.Read (decimal)
|
||||
import Data.Time (defaultTimeLocale, parseTimeM,
|
||||
rfc822DateFormat)
|
||||
|
||||
@ -56,10 +56,10 @@ uncurry6 :: (a -> b -> c -> d -> e -> f -> g) -> (a, b, c, d, e, f) -> g
|
||||
uncurry6 f (a, b, c, d, e, g) = f a b c d e g
|
||||
|
||||
-- | Parse time strings from XML
|
||||
parseS3XMLTime :: (MonadIO m) => Text -> m UTCTime
|
||||
parseS3XMLTime = either (throwIO . MErrVXmlParse) return
|
||||
. parseTimeM True defaultTimeLocale s3TimeFormat
|
||||
. T.unpack
|
||||
parseS3XMLTime :: MonadIO m => Text -> m UTCTime
|
||||
parseS3XMLTime t =
|
||||
maybe (throwIO $ MErrVXmlParse $ "timestamp parse failure: " <> t) return $
|
||||
parseTimeM True defaultTimeLocale s3TimeFormat $ T.unpack t
|
||||
|
||||
parseDecimal :: (MonadIO m, Integral a) => Text -> m a
|
||||
parseDecimal numStr = either (throwIO . MErrVXmlParse . show) return $
|
||||
|
||||
@ -15,7 +15,7 @@
|
||||
# resolver:
|
||||
# name: custom-snapshot
|
||||
# location: "./custom-snapshot.yaml"
|
||||
resolver: lts-13.1
|
||||
resolver: lts-14.6
|
||||
|
||||
# User packages to be built.
|
||||
# Various formats can be used as shown in the example below.
|
||||
|
||||
@ -77,6 +77,15 @@ mkRandFile size = do
|
||||
funTestBucketPrefix :: Text
|
||||
funTestBucketPrefix = "miniohstest-"
|
||||
|
||||
loadTestServer :: IO ConnectInfo
|
||||
loadTestServer = do
|
||||
val <- lookupEnv "MINIO_LOCAL"
|
||||
isSecure <- lookupEnv "MINIO_SECURE"
|
||||
return $ case (val, isSecure) of
|
||||
(Just _, Just _) -> setCreds (Credentials "minio" "minio123") "https://localhost:9000"
|
||||
(Just _, Nothing) -> setCreds (Credentials "minio" "minio123") "http://localhost:9000"
|
||||
(Nothing, _) -> minioPlayCI
|
||||
|
||||
funTestWithBucket :: TestName
|
||||
-> (([Char] -> Minio ()) -> Bucket -> Minio ()) -> TestTree
|
||||
funTestWithBucket t minioTest = testCaseSteps t $ \step -> do
|
||||
@ -84,10 +93,7 @@ funTestWithBucket t minioTest = testCaseSteps t $ \step -> do
|
||||
bktSuffix <- liftIO $ generate $ Q.vectorOf 10 (Q.choose ('a', 'z'))
|
||||
let b = T.concat [funTestBucketPrefix, T.pack bktSuffix]
|
||||
liftStep = liftIO . step
|
||||
connInfo <- ( bool minioPlayCI
|
||||
( setCreds (Credentials "minio" "minio123") "http://localhost:9000" )
|
||||
. isJust
|
||||
) <$> lookupEnv "MINIO_LOCAL"
|
||||
connInfo <- loadTestServer
|
||||
ret <- runMinio connInfo $ do
|
||||
liftStep $ "Creating bucket for test - " ++ t
|
||||
foundBucket <- bucketExists b
|
||||
|
||||
Loading…
Reference in New Issue
Block a user