-
-
Notifications
You must be signed in to change notification settings - Fork 225
/
S3.hs
138 lines (121 loc) · 3.52 KB
/
S3.hs
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedLabels #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE ViewPatterns #-}
module S3 where
import Amazonka
import Amazonka.S3
import Control.Lens
import Control.Monad
import Control.Monad.IO.Class
import Data.Conduit
import qualified Data.Conduit.Binary as CB
import qualified Data.Conduit.List as CL
import qualified Data.Foldable as Fold
import Data.Generics.Labels ()
import qualified Data.Text.IO as Text
import Data.Time
import System.IO
getPresignedURL ::
-- | Region to operate in.
Region ->
BucketName ->
-- | The source object key.
ObjectKey ->
IO ByteString
getPresignedURL r b k = do
lgr <- newLogger Trace stdout
env <- newEnv discover <&> set #envLogger lgr . within r
ts <- getCurrentTime
runResourceT $ presignURL env ts 60 (newGetObject b k)
listAll ::
-- | Region to operate in.
Region ->
IO ()
listAll r = do
lgr <- newLogger Debug stdout
env <- newEnv discover <&> set #envLogger lgr . within r
let val :: ToText a => Maybe a -> Text
val = maybe "Nothing" toText
lat v = maybe mempty (mappend " - " . toText) (v ^. #isLatest)
key v = val (v ^. #key) <> ": " <> val (v ^. #versionId) <> lat v
runResourceT $ do
say "Listing Buckets .."
Just bs <- view #buckets <$> send env newListBuckets
say $ "Found " <> toText (length bs) <> " Buckets."
forM_ bs $ \(view #name -> b) -> do
say $ "Listing Object Versions in: " <> toText b
runConduit $
paginate env (newListObjectVersions b)
.| CL.concatMap (toListOf $ #versions . _Just . folded)
.| CL.mapM_ (say . mappend " -> " . key)
getFile ::
-- | Region to operate in.
Region ->
BucketName ->
-- | The source object key.
ObjectKey ->
-- | The destination file to save as.
FilePath ->
IO ()
getFile r b k f = do
lgr <- newLogger Debug stdout
env <- newEnv discover <&> set #envLogger lgr . within r
runResourceT $ do
rs <- send env (newGetObject b k)
view #body rs `sinkBody` CB.sinkFile f
say $
"Successfully Download: "
<> toText b
<> " - "
<> toText k
<> " to "
<> toText f
putChunkedFile ::
-- | Region to operate in.
Region ->
-- | The bucket to store the file in.
BucketName ->
-- | The destination object key.
ObjectKey ->
-- | The chunk size to send env.
ChunkSize ->
-- | The source file to upload.
FilePath ->
IO ()
putChunkedFile r b k c f = do
lgr <- newLogger Debug stdout
env <- newEnv discover <&> set #envLogger lgr . within r
runResourceT $ do
bdy <- chunkedFile c f
void . send env $ newPutObject b k bdy
say $
"Successfully Uploaded: "
<> toText f
<> " to "
<> toText b
<> " - "
<> toText k
tagBucket ::
-- | Region to operate in.
Region ->
-- | Name of the bucket to tag.
BucketName ->
-- | List of K/V pairs to apply as tags.
[(ObjectKey, Text)] ->
IO ()
tagBucket r bkt xs = do
lgr <- newLogger Debug stdout
env <- newEnv discover <&> set #envLogger lgr . within r
let tags = map (uncurry newTag) xs
kv t = toText (t ^. #key) <> "=" <> (t ^. #value)
runResourceT $ do
void . send env $ newPutBucketTagging bkt (newTagging & #tagSet .~ tags)
say $ "Successfully Put Tags: " <> Fold.foldMap kv tags
ts <- view #tagSet <$> send env (newGetBucketTagging bkt)
forM_ ts $ \t ->
say $ "Found Tag: " <> kv t
say :: MonadIO m => Text -> m ()
say = liftIO . Text.putStrLn