summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--GetObject.hs24
-rw-r--r--PutObject.hs33
-rw-r--r--RemoveObject.hs19
3 files changed, 76 insertions, 0 deletions
diff --git a/GetObject.hs b/GetObject.hs
new file mode 100644
index 000000000..51764bf72
--- /dev/null
+++ b/GetObject.hs
@@ -0,0 +1,24 @@
+{-# LANGUAGE OverloadedStrings #-}
+
+import qualified Aws
+import qualified Aws.S3 as S3
+import Data.Conduit (($$+-))
+import Data.Conduit.Binary (sinkFile)
+import Network.HTTP.Conduit (withManager, responseBody)
+
+main :: IO ()
+main = do
+ {- Set up AWS credentials and the default configuration. -}
+ Just creds <- Aws.loadCredentialsFromEnv
+ let cfg = Aws.Configuration Aws.Timestamp creds (Aws.defaultLog Aws.Debug)
+ let s3cfg = Aws.defServiceConfig :: S3.S3Configuration Aws.NormalQuery
+
+ {- Set up a ResourceT region with an available HTTP manager. -}
+ withManager $ \mgr -> do
+ {- Create a request object with S3.getObject and run the request with pureAws. -}
+ S3.GetObjectResponse { S3.gorResponse = rsp } <-
+ Aws.pureAws cfg s3cfg mgr $
+ S3.getObject "joeyh-test" "cloud-remote.pdf"
+
+ {- Save the response to a file. -}
+ responseBody rsp $$+- sinkFile "cloud-remote2.pdf"
diff --git a/PutObject.hs b/PutObject.hs
new file mode 100644
index 000000000..68db1685a
--- /dev/null
+++ b/PutObject.hs
@@ -0,0 +1,33 @@
+{-# LANGUAGE OverloadedStrings #-}
+
+import qualified Aws
+import qualified Aws.S3 as S3
+import Data.Conduit (($$+-))
+import Data.Conduit.Binary (sinkFile)
+import Network.HTTP.Conduit (withManager, RequestBody(..))
+import qualified Data.ByteString.Lazy as L
+import qualified Data.ByteString as S
+import Control.Monad.IO.Class
+import Control.Concurrent
+import System.Posix.Files
+import System.IO
+import Control.Applicative
+import qualified Data.Text as T
+
+main :: IO ()
+main = do
+ {- Set up AWS credentials and the default configuration. -}
+ Just creds <- Aws.loadCredentialsFromEnv
+ let cfg = Aws.Configuration Aws.Timestamp creds (Aws.defaultLog Aws.Debug)
+ let s3cfg = Aws.defServiceConfig :: S3.S3Configuration Aws.NormalQuery
+
+ {- Set up a ResourceT region with an available HTTP manager. -}
+ withManager $ \mgr -> do
+ let file ="cloud-remote.pdf"
+ -- streams file content, without buffering more than 1k in memory!
+ let streamer sink = withFile file ReadMode $ \h -> sink $ S.hGet h 1024
+ b <- liftIO $ L.readFile file
+ size <- liftIO $ (fromIntegral . fileSize <$> getFileStatus file :: IO Integer)
+ rsp <- Aws.pureAws cfg s3cfg mgr $
+ S3.putObject "joeyh-test" (T.pack file) (RequestBodyStream (fromInteger size) streamer)
+ liftIO $ print rsp
diff --git a/RemoveObject.hs b/RemoveObject.hs
new file mode 100644
index 000000000..7d61907cd
--- /dev/null
+++ b/RemoveObject.hs
@@ -0,0 +1,19 @@
+{-# LANGUAGE OverloadedStrings #-}
+
+import qualified Aws
+import qualified Aws.S3 as S3
+import Data.Conduit (($$+-))
+import Data.Conduit.Binary (sinkFile)
+import Network.HTTP.Conduit (withManager, responseBody)
+import Control.Monad.IO.Class
+
+main :: IO ()
+main = do
+ Just creds <- Aws.loadCredentialsFromEnv
+ let cfg = Aws.Configuration Aws.Timestamp creds (Aws.defaultLog Aws.Debug)
+ let s3cfg = Aws.defServiceConfig :: S3.S3Configuration Aws.NormalQuery
+
+ withManager $ \mgr -> do
+ rsp <- Aws.pureAws cfg s3cfg mgr $
+ S3.DeleteObject "cloud-remote.pdf" "joeyh-test"
+ liftIO $ print "removal done"