Coder Social home page Coder Social logo

Comments (6)

rjmac avatar rjmac commented on July 20, 2024

Hm, actually I'm not sure if S3 needs to be regional or if it needs to learn to associate a bucket with a region by following the redirects that are returned when the wrong (or no) region is sent. Individual buckets are regioned, but the top-level service itself is not.

from amazonka.

brendanhay avatar brendanhay commented on July 20, 2024

Thanks @rjmac.

Since I chose (or was forced to by the models, due to generality) to use the region specific endpoints instead of virtual host style buckets, region/endpoint logic needs to be specialised for S3. This is because it uses a different endpoint structure based on the region you're communicating with.

The API reference outlines this in detail, and the service models contain the invariants which I will parse/use to ensure the correct endpoint is chosen depending on the region.

from amazonka.

brendanhay avatar brendanhay commented on July 20, 2024

I'm going to merge the two PR's addressing this to develop, but leaving the issue open. If you could rerun your code and let me know if your problems have been solved, or add any additional info.

Alternatively if you could supply me with a small example I could use to quickly recreate any issues, it would be greatly appreciated!

from amazonka.

rjmac avatar rjmac commented on July 20, 2024

Doesn't quite; it looks like the line Endpoint host' scope = endpoint s r in V4.hs should be Endpoint scope host' = ... After changing that, there are a couple of incorrect timestamp formats (RFC822s that should be ISO8601s in the definitions of Bucket and Object in S3.Types).

Anyway, here's the program I've been using to experiment:

{-# LANGUAGE OverloadedStrings #-}

module Main where

import Network.AWS (Credentials(..), Region(..), getEnv, envLogger, Logger(Debug))
import Control.Monad.Trans.AWS (runAWST, send, paginate)
import Network.AWS.S3
import Network.AWS.Prelude
import Control.Lens
import qualified Data.Text.IO as Text
import qualified Data.Text as Text
import Control.Monad.IO.Class (liftIO)
import Data.Conduit
import System.Environment (lookupEnv)

main :: IO ()
main = do
  env <- getEnv Oregon Discover <&> envLogger .~ Debug Text.putStrLn

  -- Work with the bucket named in S3_BUCKET or whichever comes back first
  defaultBucket <- (fmap.fmap) Text.pack $ lookupEnv "S3_BUCKET"
  let bucketSelector = maybe head const defaultBucket

  -- The name of an object to retrieve
  objectToRetrieve <- (fmap.fmap) Text.pack $ lookupEnv "S3_OBJECT"

  er <- runAWST env $ do
    buckets <- send listBuckets <&> (^.lbrBuckets) <&> map (^.bName) <&> catMaybes
    liftIO $ print buckets
    let bucketToList = bucketSelector buckets
    paginate (listObjects bucketToList) $$ awaitForever (liftIO . print)
    case objectToRetrieve of
      Just name -> do
        obj <- send $ getObject bucketToList name
        liftIO $ print obj
        (obj^.gorBody) `connectBody` awaitForever (liftIO . print)
      Nothing ->
        return ()
  case er of
   Left err -> print err
   Right _ -> return ()

from amazonka.

brendanhay avatar brendanhay commented on July 20, 2024

Thanks! You beat me before I could push the fix for Endpoint to develop.

I'll check it out.

from amazonka.

brendanhay avatar brendanhay commented on July 20, 2024

I've successfully verified that c2f3c40 in combination with previous round of fixes results in things working as expected. The S3 example mostly demonstrates this, but avoids actually printing/downloading the objects since who knows what people keep in their buckets.

from amazonka.

Related Issues (20)

Recommend Projects

  • React photo React

    A declarative, efficient, and flexible JavaScript library for building user interfaces.

  • Vue.js photo Vue.js

    🖖 Vue.js is a progressive, incrementally-adoptable JavaScript framework for building UI on the web.

  • Typescript photo Typescript

    TypeScript is a superset of JavaScript that compiles to clean JavaScript output.

  • TensorFlow photo TensorFlow

    An Open Source Machine Learning Framework for Everyone

  • Django photo Django

    The Web framework for perfectionists with deadlines.

  • D3 photo D3

    Bring data to life with SVG, Canvas and HTML. 📊📈🎉

Recommend Topics

  • javascript

    JavaScript (JS) is a lightweight interpreted programming language with first-class functions.

  • web

    Some thing interesting about web. New door for the world.

  • server

    A server is a program made to process requests and deliver data to clients.

  • Machine learning

    Machine learning is a way of modeling and interpreting data that allows a piece of software to respond intelligently.

  • Game

    Some thing interesting about game, make everyone happy.

Recommend Org

  • Facebook photo Facebook

    We are working to build community through open source technology. NB: members must have two-factor auth.

  • Microsoft photo Microsoft

    Open source projects and samples from Microsoft.

  • Google photo Google

    Google ❤️ Open Source for everyone.

  • D3 photo D3

    Data-Driven Documents codes.