Skip to content

Commit

Permalink
amazonka: splitting prelude (dependencies) vs core (self) imports
Browse files Browse the repository at this point in the history
  • Loading branch information
brendanhay committed Jun 14, 2021
1 parent f63c08d commit f47b960
Show file tree
Hide file tree
Showing 34 changed files with 177 additions and 156 deletions.
14 changes: 8 additions & 6 deletions amazonka-s3-encryption/src/Network/AWS/S3/Encryption.hs
Original file line number Diff line number Diff line change
Expand Up @@ -89,9 +89,9 @@ where

import Control.Lens
import Control.Monad.Reader
import Network.AWS as AWS
import Crypto.PubKey.RSA.Types as RSA
import Crypto.Random
import Network.AWS as AWS
import Network.AWS.S3
import Network.AWS.S3.Encryption.Decrypt
import Network.AWS.S3.Encryption.Encrypt
Expand Down Expand Up @@ -203,7 +203,7 @@ initiateInstructions ::
MonadResource m =>
Key ->
Env ->
CreateMultipartUpload ->
CreateMultipartUpload ->
m
( Either
EncryptionError
Expand Down Expand Up @@ -261,10 +261,12 @@ cleanupInstructions ::
Env ->
a ->
m (AWSResponse a)
cleanupInstructions env x = do
rs <- send env x
_ <- send env (deleteInstructions x)
return rs
cleanupInstructions env x =
do
rs <- send env x
_ <- send env (deleteInstructions x)
return
rs

-- $usage
-- When sending requests that make use of a master key, an extension to the underlying
Expand Down
30 changes: 15 additions & 15 deletions amazonka-s3-encryption/src/Network/AWS/S3/Encryption/Decrypt.hs
Original file line number Diff line number Diff line change
Expand Up @@ -13,10 +13,10 @@
-- Portability : non-portable (GHC extensions)
module Network.AWS.S3.Encryption.Decrypt where

import qualified Control.Monad.Except as Except
import Control.Lens ((%~), (^.))
import qualified Network.AWS as AWS
import qualified Control.Monad.Except as Except
import Data.Coerce (coerce)
import qualified Network.AWS as AWS
import Network.AWS.Core
import qualified Network.AWS.S3 as S3
import Network.AWS.S3.Encryption.Envelope
Expand All @@ -40,20 +40,20 @@ instance AWSRequest (Decrypt S3.GetObject) where
request (Decrypt x) = coerce (request x)

response l s p r =
Except.runExceptT $ do
rs <- Except.ExceptT (response l s (proxy p) r)
Except.runExceptT $ do
rs <- Except.ExceptT (response l s (proxy p) r)

let body = Client.responseBody rs
decrypt =
let body = Client.responseBody rs
decrypt =
Decrypted $ \key env m -> do
encrypted <-
case m of
Nothing -> fromMetadata key env (body ^. S3.getObjectResponse_metadata)
Just e -> pure e

pure (body & S3.getObjectResponse_body %~ bodyDecrypt encrypted)
pure (decrypt <$ rs)
encrypted <-
case m of
Nothing -> fromMetadata key env (body ^. S3.getObjectResponse_metadata)
Just e -> pure e

pure (body & S3.getObjectResponse_body %~ bodyDecrypt encrypted)

pure (decrypt <$ rs)

proxy :: forall a. Proxy (Decrypt a) -> Proxy a
proxy = const Proxy
Original file line number Diff line number Diff line change
Expand Up @@ -16,8 +16,8 @@ module Network.AWS.S3.Encryption.Encrypt where

import Control.Lens ((%~), (<>~), (^.))
import qualified Control.Lens as Lens
import qualified Network.AWS as AWS
import Data.Coerce (coerce)
import qualified Network.AWS as AWS
import Network.AWS.Core
import qualified Network.AWS.S3 as S3
import Network.AWS.S3.Encryption.Envelope
Expand All @@ -30,7 +30,7 @@ import qualified Network.AWS.S3.Lens as S3
-- | Note about how it doesn't attach metadata by default.
-- You can re-set the location and then discard the PutInstructions request.
encrypted ::
( MonadResource m, ToEncrypted a) =>
(MonadResource m, ToEncrypted a) =>
Key ->
AWS.Env ->
a ->
Expand Down
36 changes: 18 additions & 18 deletions amazonka-s3-encryption/src/Network/AWS/S3/Encryption/Envelope.hs
Original file line number Diff line number Diff line change
Expand Up @@ -13,9 +13,9 @@
-- Portability : non-portable (GHC extensions)
module Network.AWS.S3.Encryption.Envelope where

import qualified Control.Exception as Exception
import qualified Conduit
import Control.Lens ( (+~), (?~), (^.))
import qualified Control.Exception as Exception
import Control.Lens ((+~), (?~), (^.))
import qualified Crypto.Cipher.AES as AES
import Crypto.Cipher.Types (BlockCipher, Cipher)
import qualified Crypto.Cipher.Types as Cipher
Expand All @@ -30,9 +30,9 @@ import qualified Data.ByteArray as ByteArray
import qualified Data.CaseInsensitive as CI
import qualified Data.HashMap.Strict as Map
import qualified Network.AWS as AWS
import Network.AWS.Core
import qualified Network.AWS.KMS as KMS
import qualified Network.AWS.KMS.Lens as KMS
import Network.AWS.Core
import Network.AWS.S3.Encryption.Body
import Network.AWS.S3.Encryption.Types

Expand All @@ -50,18 +50,18 @@ data V1Envelope = V1Envelope

newV1 :: MonadIO m => (ByteString -> IO ByteString) -> Description -> m Envelope
newV1 f d =
liftIO $ do
k <- getRandomBytes aesKeySize
c <- createCipher k
ek <- f k
iv <- createIV =<< getRandomBytes aesBlockSize
pure . V1 c $
V1Envelope
{ _v1Key = ek,
_v1IV = iv,
_v1Description = d
}
liftIO $ do
k <- getRandomBytes aesKeySize
c <- createCipher k
ek <- f k
iv <- createIV =<< getRandomBytes aesBlockSize

pure . V1 c $
V1Envelope
{ _v1Key = ek,
_v1IV = iv,
_v1Description = d
}

decodeV1 ::
MonadResource m =>
Expand Down Expand Up @@ -111,7 +111,7 @@ data V2Envelope = V2Envelope
newV2 :: MonadResource m => Text -> AWS.Env -> Description -> m Envelope
newV2 kid env d = do
let ctx = Map.insert "kms_cmk_id" kid (fromDescription d)

rs <-
AWS.send env $
KMS.newGenerateDataKey kid
Expand Down Expand Up @@ -226,8 +226,8 @@ fromMetadata ::
m Envelope
fromMetadata key env =
decodeEnvelope key env
. map (first CI.mk)
. Map.toList
. map (first CI.mk)
. Map.toList

aesKeySize, aesBlockSize :: Int
aesKeySize = 32
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -17,10 +17,10 @@ module Network.AWS.S3.Encryption.Instructions where
import Control.Arrow ((&&&))
import Control.Lens ((%~))
import qualified Control.Lens as Lens
import qualified Network.AWS as AWS
import qualified Data.Aeson.Types as Aeson
import Data.Bifunctor (first)
import Data.Coerce (coerce)
import qualified Network.AWS as AWS
import Network.AWS.Core
import qualified Network.AWS.Response as Response
import qualified Network.AWS.S3 as S3
Expand Down
8 changes: 4 additions & 4 deletions amazonka/amazonka.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -86,11 +86,10 @@ library
Network.AWS.Core
Network.AWS.EC2.Metadata
Network.AWS.Env
Network.AWS.Error
Network.AWS.HTTP
Network.AWS.Lens
Network.AWS.Logger
Network.AWS.Pager
Network.AWS.Prelude
Network.AWS.Presign
Network.AWS.Request
Network.AWS.Response
Expand All @@ -100,7 +99,6 @@ library
Network.AWS.Sign.V4
Network.AWS.Sign.V4.Base
Network.AWS.Sign.V4.Chunked
Network.AWS.Waiter

other-modules:
Network.AWS.Bytes
Expand All @@ -119,8 +117,10 @@ library
Network.AWS.Data.Time
Network.AWS.Data.XML
Network.AWS.Endpoint
Network.AWS.Prelude
Network.AWS.Error
Network.AWS.Pager
Network.AWS.Types
Network.AWS.Waiter

build-depends:
, aeson >=1.3.1 && <1.6.2
Expand Down
1 change: 1 addition & 0 deletions amazonka/src/Network/AWS.hs
Original file line number Diff line number Diff line change
Expand Up @@ -149,6 +149,7 @@ import qualified Network.AWS.HTTP as HTTP
import qualified Network.AWS.Lens as Lens
import Network.AWS.Logger
import qualified Network.AWS.Pager as Pager
import Network.AWS.Prelude
import qualified Network.AWS.Presign as Presign
import Network.AWS.Request (clientRequestURL)
import qualified Network.AWS.Waiter as Waiter
Expand Down
24 changes: 18 additions & 6 deletions amazonka/src/Network/AWS/Core.hs
Original file line number Diff line number Diff line change
Expand Up @@ -11,17 +11,29 @@ module Network.AWS.Core
( module Network.AWS.Types,
module Network.AWS.Endpoint,
module Network.AWS.Data,
module Network.AWS.Prelude,
module Network.AWS.Pager,
module Network.AWS.Waiter,
module Network.AWS.Error
module Network.AWS.Error,
(.!@),
may,
)
where

import Network.AWS.Types
import Network.AWS.Prelude
import Network.AWS.Endpoint
import Network.AWS.Data
import Network.AWS.Endpoint
import Network.AWS.Error
import Network.AWS.Pager
import Network.AWS.Prelude
import Network.AWS.Types
import Network.AWS.Waiter
import Network.AWS.Error

-- Legacy code generation operators

infixl 7 .!@

(.!@) :: Functor f => f (Maybe a) -> a -> f a
f .!@ x = fromMaybe x <$> f

may :: Applicative f => ([a] -> f b) -> [a] -> f (Maybe b)
may _ [] = pure Nothing
may f xs = Just <$> f xs
14 changes: 7 additions & 7 deletions amazonka/src/Network/AWS/Data/JSON.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,8 +7,8 @@
-- Portability : non-portable (GHC extensions)
module Network.AWS.Data.JSON
( -- * FromJSON
FromJSON (..),
FromJSONKey (..),
Aeson.FromJSON (..),
Aeson.FromJSONKey (..),
parseJSONText,
Aeson.eitherDecode,
Aeson.eitherDecode',
Expand All @@ -25,8 +25,8 @@ module Network.AWS.Data.JSON
(.?>),

-- * ToJSON
ToJSON (..),
ToJSONKey (..),
Aeson.ToJSON (..),
Aeson.ToJSONKey (..),
toJSONText,
Aeson.Value (Object),
Aeson.object,
Expand All @@ -46,16 +46,16 @@ parseJSONText n = Aeson.withText n (either fail pure . fromText)
toJSONText :: ToText a => a -> Aeson.Value
toJSONText = Aeson.String . toText

eitherParseJSON :: FromJSON a => Aeson.Object -> Either String a
eitherParseJSON :: Aeson.FromJSON a => Aeson.Object -> Either String a
eitherParseJSON = Aeson.Types.parseEither Aeson.parseJSON . Aeson.Object

(.:>) :: FromJSON a => Aeson.Object -> Text -> Either String a
(.:>) :: Aeson.FromJSON a => Aeson.Object -> Text -> Either String a
(.:>) o k =
case HashMap.lookup k o of
Nothing -> Left $ "key " ++ show k ++ " not present"
Just v -> Aeson.Types.parseEither Aeson.parseJSON v

(.?>) :: FromJSON a => Aeson.Object -> Text -> Either String (Maybe a)
(.?>) :: Aeson.FromJSON a => Aeson.Object -> Text -> Either String (Maybe a)
(.?>) o k =
case HashMap.lookup k o of
Nothing -> Right Nothing
Expand Down
1 change: 0 additions & 1 deletion amazonka/src/Network/AWS/Lens.hs
Original file line number Diff line number Diff line change
Expand Up @@ -50,7 +50,6 @@ import Control.Lens as Export
view,
(#),
(%~),
(&),
(.~),
(<&>),
(<>~),
Expand Down
16 changes: 1 addition & 15 deletions amazonka/src/Network/AWS/Prelude.hs
Original file line number Diff line number Diff line change
Expand Up @@ -22,8 +22,6 @@ module Network.AWS.Prelude
TextBuilder,
ByteStringLazy,
ByteStringBuilder,
(.!@),
may,
)
where

Expand All @@ -39,10 +37,8 @@ import Control.Lens as Export
)
import Control.Monad as Export
import Control.Monad.IO.Class as Export (MonadIO (liftIO))
import Data.Monoid as Export (First)
import Control.Monad.Trans as Export (MonadTrans (lift))
import Control.Monad.Trans.Resource as Export (MonadResource)
import Data.Aeson as Export (FromJSON (..), FromJSONKey (..), ToJSON (..), ToJSONKey (..))
import Data.Bifoldable as Export
import Data.Bifunctor as Export
import Data.Bitraversable as Export
Expand All @@ -62,6 +58,7 @@ import Data.Int as Export (Int16, Int32, Int64, Int8)
import Data.Kind as Export (Type)
import Data.List.NonEmpty as Export (NonEmpty ((:|)))
import Data.Maybe as Export
import Data.Monoid as Export (First)
import Data.Proxy as Export (Proxy (Proxy))
import Data.Scientific as Export (Scientific)
import Data.String as Export (IsString (fromString))
Expand All @@ -84,14 +81,3 @@ type TextBuilder = Text.Lazy.Builder.Builder
type ByteStringLazy = ByteString.Lazy.ByteString

type ByteStringBuilder = ByteString.Builder.Builder

-- Legacy code generation operators

infixl 7 .!@

(.!@) :: Functor f => f (Maybe a) -> a -> f a
f .!@ x = fromMaybe x <$> f

may :: Applicative f => ([a] -> f b) -> [a] -> f (Maybe b)
may _ [] = pure Nothing
may f xs = Just <$> f xs
2 changes: 1 addition & 1 deletion amazonka/src/Network/AWS/Request.hs
Original file line number Diff line number Diff line change
Expand Up @@ -40,9 +40,9 @@ module Network.AWS.Request
)
where

import Network.AWS.Core
import Network.AWS.Lens ((.~))
import Network.AWS.Prelude
import Network.AWS.Types
import qualified Network.HTTP.Client as Client
import Network.HTTP.Types (StdMethod (..))
import qualified Network.HTTP.Types as HTTP
Expand Down
3 changes: 2 additions & 1 deletion amazonka/test/Test/AWS/Arbitrary.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,8 +14,9 @@ import Data.CaseInsensitive (FoldCase)
import qualified Data.CaseInsensitive as CI
import qualified Data.Text as Text
import qualified Data.Text.Encoding as Text
import Data.Time (UTCTime (..), Day (..))
import Data.Time (Day (..), UTCTime (..))
import Network.AWS.Core
import Network.AWS.Prelude
import Network.AWS.Sign.V4
import Network.HTTP.Types (StdMethod (..))
import Test.QuickCheck.Gen as QC
Expand Down
1 change: 1 addition & 0 deletions amazonka/test/Test/AWS/Data/Base64.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,6 +8,7 @@
module Test.AWS.Data.Base64 (tests) where

import Network.AWS.Core
import Network.AWS.Prelude
import Network.HTTP.Types.URI (urlEncode)
import Test.AWS.Util
import Test.Tasty
Expand Down
Loading

0 comments on commit f47b960

Please sign in to comment.