Skip to content

Commit

Permalink
Add simple TLS helpers: (#121)
Browse files Browse the repository at this point in the history
- Check if ConnectInfo is secure

- Option to disable TLS certificate validation (to make testing
  easier).
  • Loading branch information
donatello authored and krisis committed May 13, 2019
1 parent 663015f commit 76e5651
Show file tree
Hide file tree
Showing 4 changed files with 56 additions and 29 deletions.
10 changes: 5 additions & 5 deletions examples/BucketExists.hs
Original file line number Diff line number Diff line change
Expand Up @@ -17,11 +17,11 @@
-- limitations under the License.
--

{-# Language OverloadedStrings #-}
import Network.Minio
{-# LANGUAGE OverloadedStrings #-}
import Network.Minio

import Control.Monad.IO.Class (liftIO)
import Prelude
import Control.Monad.IO.Class (liftIO)
import Prelude

-- | The following example uses minio's play server at
-- https://play.min.io:9000. The endpoint and associated
Expand All @@ -39,5 +39,5 @@ main = do
liftIO $ putStrLn $ "Does " ++ show bucket ++ " exist? - " ++ show foundBucket

case res1 of
Left e -> putStrLn $ "bucketExists failed." ++ show e
Left e -> putStrLn $ "bucketExists failed." ++ show e
Right () -> return ()
12 changes: 9 additions & 3 deletions minio-hs.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -56,6 +56,7 @@ library
, case-insensitive >= 1.2
, conduit >= 1.3
, conduit-extra >= 1.3
, connection
, containers >= 0.5
, cryptonite >= 0.25
, cryptonite-conduit >= 0.2
Expand All @@ -64,6 +65,7 @@ library
, exceptions
, filepath >= 1.4
, http-client >= 0.5
, http-client-tls
, http-conduit >= 2.3
, http-types >= 0.12
, ini
Expand Down Expand Up @@ -142,13 +144,15 @@ test-suite minio-hs-live-server-test
build-depends: base >= 4.7 && < 5
, minio-hs
, protolude >= 0.1.6
, QuickCheck
, aeson
, base64-bytestring
, binary
, bytestring
, case-insensitive
, conduit
, conduit-extra
, connection
, containers
, cryptonite
, cryptonite-conduit
Expand All @@ -157,11 +161,11 @@ test-suite minio-hs-live-server-test
, exceptions
, filepath
, http-client
, http-client-tls
, http-conduit
, http-types
, ini
, memory
, QuickCheck
, raw-strings-qq >= 1
, resourcet
, retry
Expand All @@ -187,26 +191,28 @@ test-suite minio-hs-test
build-depends: base >= 4.7 && < 5
, minio-hs
, protolude >= 0.1.6
, QuickCheck
, aeson
, base64-bytestring
, binary
, bytestring
, case-insensitive
, conduit
, conduit-extra
, connection
, containers
, cryptonite
, cryptonite-conduit
, filepath
, digest
, directory
, exceptions
, filepath
, http-client
, http-client-tls
, http-conduit
, http-types
, ini
, memory
, QuickCheck
, raw-strings-qq >= 1
, resourcet
, retry
Expand Down
2 changes: 2 additions & 0 deletions src/Network/Minio.hs
Original file line number Diff line number Diff line change
Expand Up @@ -39,6 +39,8 @@ module Network.Minio
, setRegion
, setCreds
, setCredsFrom
, isConnectInfoSecure
, disableTLSCertValidation
, MinioConn
, mkMinioConn

Expand Down
61 changes: 40 additions & 21 deletions src/Network/Minio/Data.hs
Original file line number Diff line number Diff line change
Expand Up @@ -37,7 +37,9 @@ import qualified Data.Text as T
import qualified Data.Text.Encoding as TE
import Data.Time (defaultTimeLocale, formatTime)
import GHC.Show (Show (show))
import qualified Network.Connection as Conn
import Network.HTTP.Client (defaultManagerSettings)
import qualified Network.HTTP.Client.TLS as TLS
import qualified Network.HTTP.Conduit as NC
import Network.HTTP.Types (ByteRange, Header, Method, Query,
hRange)
Expand Down Expand Up @@ -94,28 +96,30 @@ awsRegionMap = Map.fromList [
-- `IsString` instance to provide a URL, for example:
--
-- > let c :: ConnectInfo = "https://play.min.io:9000"
data ConnectInfo = ConnectInfo {
connectHost :: Text
, connectPort :: Int
, connectAccessKey :: Text
, connectSecretKey :: Text
, connectIsSecure :: Bool
, connectRegion :: Region
, connectAutoDiscoverRegion :: Bool
} deriving (Eq, Show)

data ConnectInfo =
ConnectInfo { connectHost :: Text
, connectPort :: Int
, connectAccessKey :: Text
, connectSecretKey :: Text
, connectIsSecure :: Bool
, connectRegion :: Region
, connectAutoDiscoverRegion :: Bool
, connectDisableTLSCertValidation :: Bool
} deriving (Eq, Show)

instance IsString ConnectInfo where
fromString str = let req = NC.parseRequest_ str
in ConnectInfo
{ connectHost = TE.decodeUtf8 $ NC.host req
, connectPort = NC.port req
, connectAccessKey = ""
, connectSecretKey = ""
, connectIsSecure = NC.secure req
, connectRegion = ""
, connectAutoDiscoverRegion = True
}
fromString str =
let req = NC.parseRequest_ str
in ConnectInfo
{ connectHost = TE.decodeUtf8 $ NC.host req
, connectPort = NC.port req
, connectAccessKey = ""
, connectSecretKey = ""
, connectIsSecure = NC.secure req
, connectRegion = ""
, connectAutoDiscoverRegion = True
, connectDisableTLSCertValidation = False
}

-- | Contains access key and secret key to access object storage.
data Credentials = Credentials { cAccessKey :: Text
Expand Down Expand Up @@ -187,6 +191,18 @@ setRegion r connInfo = connInfo { connectRegion = r
, connectAutoDiscoverRegion = False
}

-- | Check if the connection to object storage server is secure
-- (i.e. uses TLS)
isConnectInfoSecure :: ConnectInfo -> Bool
isConnectInfoSecure = connectIsSecure

-- | Disable TLS certificate validation completely! This makes TLS
-- insecure! Use only for testing with self-signed or temporary
-- certificates. Note that this option has no effect, if you provide
-- your own Manager in `mkMinioConn`.
disableTLSCertValidation :: ConnectInfo -> ConnectInfo
disableTLSCertValidation c = c { connectDisableTLSCertValidation = True }

getHostAddr :: ConnectInfo -> ByteString
getHostAddr ci = if | port == 80 || port == 443 -> toS host
| otherwise -> toS $
Expand Down Expand Up @@ -955,7 +971,10 @@ instance HasSvcNamespace MinioConn where
-- object storage is accessed.
connect :: ConnectInfo -> IO MinioConn
connect ci = do
let settings | connectIsSecure ci = NC.tlsManagerSettings
let settings | connectIsSecure ci && connectDisableTLSCertValidation ci =
let badTlsSettings = Conn.TLSSettingsSimple True False False
in TLS.mkManagerSettings badTlsSettings Nothing
| connectIsSecure ci = NC.tlsManagerSettings
| otherwise = defaultManagerSettings
mgr <- NC.newManager settings
mkMinioConn ci mgr
Expand Down

0 comments on commit 76e5651

Please sign in to comment.