2011-03-28 02:00:44 +00:00
|
|
|
{- Amazon S3 remotes.
|
|
|
|
-
|
|
|
|
- Copyright 2011 Joey Hess <joey@kitenet.net>
|
|
|
|
-
|
|
|
|
- Licensed under the GNU GPL version 3 or higher.
|
|
|
|
-}
|
|
|
|
|
2011-03-29 03:51:07 +00:00
|
|
|
module Remote.S3 (remote) where
|
2011-03-28 02:00:44 +00:00
|
|
|
|
2011-03-29 21:20:22 +00:00
|
|
|
import Control.Exception.Extensible (IOException)
|
2011-03-28 05:32:47 +00:00
|
|
|
import Network.AWS.AWSConnection
|
|
|
|
import Network.AWS.S3Object
|
|
|
|
import Network.AWS.S3Bucket
|
|
|
|
import Network.AWS.AWSResult
|
|
|
|
import qualified Data.ByteString.Lazy.Char8 as L
|
2011-03-29 17:49:54 +00:00
|
|
|
import qualified Data.Map as M
|
2011-03-29 20:21:21 +00:00
|
|
|
import Data.Maybe
|
2011-03-29 22:28:37 +00:00
|
|
|
import Control.Monad (when)
|
2011-03-28 05:32:47 +00:00
|
|
|
import Control.Monad.State (liftIO)
|
|
|
|
import System.Environment
|
2011-03-28 02:00:44 +00:00
|
|
|
|
|
|
|
import RemoteClass
|
|
|
|
import Types
|
|
|
|
import qualified GitRepo as Git
|
|
|
|
import qualified Annex
|
|
|
|
import UUID
|
2011-03-29 20:21:21 +00:00
|
|
|
import Messages
|
2011-03-29 21:57:20 +00:00
|
|
|
import Locations
|
2011-03-30 19:15:46 +00:00
|
|
|
import Config
|
2011-03-30 18:00:54 +00:00
|
|
|
import Remote.Special
|
2011-04-17 04:40:23 +00:00
|
|
|
import Remote.Encryptable
|
2011-04-17 15:01:34 +00:00
|
|
|
import Crypto
|
2011-03-28 02:00:44 +00:00
|
|
|
|
2011-03-29 03:51:07 +00:00
|
|
|
remote :: RemoteType Annex
|
2011-03-29 18:55:59 +00:00
|
|
|
remote = RemoteType {
|
|
|
|
typename = "S3",
|
2011-03-30 18:00:54 +00:00
|
|
|
enumerate = findSpecialRemotes "s3",
|
|
|
|
generate = gen,
|
2011-03-29 18:55:59 +00:00
|
|
|
setup = s3Setup
|
|
|
|
}
|
2011-03-29 03:51:07 +00:00
|
|
|
|
2011-04-15 19:09:36 +00:00
|
|
|
gen :: Git.Repo -> UUID -> Maybe RemoteConfig -> Annex (Remote Annex)
|
2011-03-30 19:15:46 +00:00
|
|
|
gen r u c = do
|
|
|
|
cst <- remoteCost r expensiveRemoteCost
|
2011-04-17 15:01:34 +00:00
|
|
|
return $ gen' r u c cst
|
|
|
|
gen' :: Git.Repo -> UUID -> Maybe RemoteConfig -> Int -> Remote Annex
|
|
|
|
gen' r u c cst =
|
|
|
|
encryptableRemote c
|
|
|
|
(storeEncrypted this)
|
|
|
|
(retrieveEncrypted this)
|
|
|
|
this
|
2011-03-29 21:57:20 +00:00
|
|
|
where
|
2011-04-17 15:01:34 +00:00
|
|
|
this = Remote {
|
2011-03-29 21:57:20 +00:00
|
|
|
uuid = u,
|
|
|
|
cost = cst,
|
|
|
|
name = Git.repoDescribe r,
|
2011-04-17 15:01:34 +00:00
|
|
|
storeKey = store this,
|
|
|
|
retrieveKeyFile = retrieve this,
|
|
|
|
removeKey = remove this,
|
|
|
|
hasKey = checkPresent this,
|
2011-03-29 21:57:20 +00:00
|
|
|
hasKeyCheap = False,
|
|
|
|
config = c
|
|
|
|
}
|
2011-03-28 05:32:47 +00:00
|
|
|
|
2011-04-15 19:09:36 +00:00
|
|
|
s3Setup :: UUID -> RemoteConfig -> Annex RemoteConfig
|
2011-03-29 18:55:59 +00:00
|
|
|
s3Setup u c = do
|
2011-03-29 20:21:21 +00:00
|
|
|
-- verify configuration is sane
|
2011-04-16 17:25:27 +00:00
|
|
|
c' <- encryptionSetup c
|
|
|
|
let fullconfig = M.union c' defaults
|
2011-03-29 20:21:21 +00:00
|
|
|
|
2011-03-29 21:20:22 +00:00
|
|
|
-- check bucket location to see if the bucket exists, and create it
|
2011-03-29 20:21:21 +00:00
|
|
|
let datacenter = fromJust $ M.lookup "datacenter" fullconfig
|
2011-03-30 19:25:59 +00:00
|
|
|
conn <- s3ConnectionRequired fullconfig
|
|
|
|
|
2011-03-29 20:21:21 +00:00
|
|
|
showNote "checking bucket"
|
|
|
|
loc <- liftIO $ getBucketLocation conn bucket
|
|
|
|
case loc of
|
|
|
|
Right _ -> return ()
|
2011-04-19 18:45:19 +00:00
|
|
|
Left err@(NetworkError _) -> s3Error err
|
2011-03-29 20:21:21 +00:00
|
|
|
Left (AWSError _ _) -> do
|
2011-03-29 21:20:22 +00:00
|
|
|
showNote $ "creating bucket in " ++ datacenter
|
2011-03-29 20:21:21 +00:00
|
|
|
res <- liftIO $ createBucketIn conn bucket datacenter
|
|
|
|
case res of
|
|
|
|
Right _ -> return ()
|
2011-04-19 18:45:19 +00:00
|
|
|
Left err -> s3Error err
|
2011-03-29 20:21:21 +00:00
|
|
|
|
2011-03-30 18:32:08 +00:00
|
|
|
gitConfigSpecialRemote u fullconfig "s3" "true"
|
2011-03-29 20:21:21 +00:00
|
|
|
return fullconfig
|
|
|
|
where
|
2011-03-29 21:20:22 +00:00
|
|
|
remotename = fromJust (M.lookup "name" c)
|
|
|
|
bucket = remotename ++ "-" ++ u
|
2011-03-29 20:21:21 +00:00
|
|
|
defaults = M.fromList
|
|
|
|
[ ("datacenter", "US")
|
|
|
|
, ("storageclass", "STANDARD")
|
|
|
|
, ("host", defaultAmazonS3Host)
|
|
|
|
, ("port", show defaultAmazonS3Port)
|
|
|
|
, ("bucket", bucket)
|
|
|
|
]
|
|
|
|
|
2011-03-30 18:00:54 +00:00
|
|
|
store :: Remote Annex -> Key -> Annex Bool
|
2011-04-19 18:45:19 +00:00
|
|
|
store r k = s3Action r False $ \(conn, bucket) -> do
|
|
|
|
content <- lazyKeyContent k
|
|
|
|
res <- liftIO $ storeHelper (conn, bucket) r k content
|
|
|
|
s3Bool res
|
2011-04-17 15:01:34 +00:00
|
|
|
|
|
|
|
storeEncrypted :: Remote Annex -> (Cipher, Key) -> Key -> Annex Bool
|
2011-04-19 18:45:19 +00:00
|
|
|
storeEncrypted r (cipher, enck) k = s3Action r False $ \(conn, bucket) -> do
|
2011-04-17 15:01:34 +00:00
|
|
|
content <- lazyKeyContent k
|
2011-04-19 19:26:50 +00:00
|
|
|
res <- liftIO $ withEncryptedContent cipher (return content) $ \s -> do
|
2011-04-19 18:45:19 +00:00
|
|
|
storeHelper (conn, bucket) r enck s
|
|
|
|
s3Bool res
|
2011-04-17 15:01:34 +00:00
|
|
|
|
|
|
|
lazyKeyContent :: Key -> Annex L.ByteString
|
|
|
|
lazyKeyContent k = do
|
2011-03-29 21:57:20 +00:00
|
|
|
g <- Annex.gitRepo
|
2011-04-17 15:01:34 +00:00
|
|
|
liftIO $ L.readFile $ gitAnnexLocation g k
|
|
|
|
|
2011-04-19 18:45:19 +00:00
|
|
|
storeHelper :: (AWSConnection, String) -> Remote Annex -> Key -> L.ByteString -> IO (AWSResult ())
|
|
|
|
storeHelper (conn, bucket) r k content = do
|
2011-03-29 22:09:22 +00:00
|
|
|
let object = setStorageClass storageclass $ bucketKey bucket k content
|
2011-04-19 18:45:19 +00:00
|
|
|
sendObject conn object
|
2011-03-29 20:21:21 +00:00
|
|
|
where
|
2011-03-29 21:20:22 +00:00
|
|
|
storageclass =
|
|
|
|
case fromJust $ M.lookup "storageclass" $ fromJust $ config r of
|
|
|
|
"REDUCED_REDUNDANCY" -> REDUCED_REDUNDANCY
|
|
|
|
_ -> STANDARD
|
2011-03-29 22:09:22 +00:00
|
|
|
|
2011-03-30 18:00:54 +00:00
|
|
|
retrieve :: Remote Annex -> Key -> FilePath -> Annex Bool
|
2011-04-19 18:45:19 +00:00
|
|
|
retrieve r k f = s3Action r False $ \(conn, bucket) -> do
|
2011-03-29 22:09:22 +00:00
|
|
|
res <- liftIO $ getObject conn $ bucketKey bucket k L.empty
|
|
|
|
case res of
|
|
|
|
Right o -> do
|
2011-04-19 18:45:19 +00:00
|
|
|
liftIO $ L.writeFile f $ obj_data o
|
2011-03-29 22:09:22 +00:00
|
|
|
return True
|
2011-04-19 18:45:19 +00:00
|
|
|
Left e -> s3Warning e
|
|
|
|
|
|
|
|
retrieveEncrypted :: Remote Annex -> (Cipher, Key) -> FilePath -> Annex Bool
|
|
|
|
retrieveEncrypted r (cipher, enck) f = s3Action r False $ \(conn, bucket) -> do
|
|
|
|
res <- liftIO $ getObject conn $ bucketKey bucket enck L.empty
|
|
|
|
case res of
|
|
|
|
Right o -> liftIO $
|
2011-04-19 19:26:50 +00:00
|
|
|
withDecryptedContent cipher (return $ obj_data o) $ \content -> do
|
2011-04-19 18:45:19 +00:00
|
|
|
L.writeFile f content
|
|
|
|
return True
|
|
|
|
Left e -> s3Warning e
|
|
|
|
|
2011-03-30 18:00:54 +00:00
|
|
|
remove :: Remote Annex -> Key -> Annex Bool
|
2011-03-30 19:25:59 +00:00
|
|
|
remove r k = s3Action r False $ \(conn, bucket) -> do
|
2011-03-29 22:21:05 +00:00
|
|
|
res <- liftIO $ deleteObject conn $ bucketKey bucket k L.empty
|
2011-04-19 18:50:09 +00:00
|
|
|
s3Bool res
|
|
|
|
|
|
|
|
checkPresent :: Remote Annex -> Key -> Annex (Either IOException Bool)
|
|
|
|
checkPresent r k = s3Action r noconn $ \(conn, bucket) -> do
|
|
|
|
showNote ("checking " ++ name r ++ "...")
|
|
|
|
res <- liftIO $ getObjectInfo conn $ bucketKey bucket k L.empty
|
2011-03-29 22:21:05 +00:00
|
|
|
case res of
|
2011-04-19 18:50:09 +00:00
|
|
|
Right _ -> return $ Right True
|
|
|
|
Left (AWSError _ _) -> return $ Right False
|
|
|
|
Left e -> return $ Left (s3Error e)
|
|
|
|
where
|
|
|
|
noconn = Left $ error "S3 not configured"
|
2011-04-19 18:45:19 +00:00
|
|
|
|
|
|
|
s3Warning :: ReqError -> Annex Bool
|
|
|
|
s3Warning e = do
|
|
|
|
warning $ prettyReqError e
|
|
|
|
return False
|
|
|
|
|
|
|
|
s3Error :: ReqError -> a
|
|
|
|
s3Error e = error $ prettyReqError e
|
|
|
|
|
|
|
|
s3Bool :: AWSResult () -> Annex Bool
|
|
|
|
s3Bool res = do
|
|
|
|
case res of
|
|
|
|
Right _ -> return True
|
|
|
|
Left e -> s3Warning e
|
2011-04-19 18:50:09 +00:00
|
|
|
|
|
|
|
s3ConnectionRequired :: RemoteConfig -> Annex AWSConnection
|
|
|
|
s3ConnectionRequired c = do
|
|
|
|
conn <- s3Connection c
|
|
|
|
case conn of
|
|
|
|
Nothing -> error "Cannot connect to S3"
|
|
|
|
Just conn' -> return conn'
|
|
|
|
|
|
|
|
s3Connection :: RemoteConfig -> Annex (Maybe AWSConnection)
|
|
|
|
s3Connection c = do
|
|
|
|
ak <- getEnvKey "AWS_ACCESS_KEY_ID"
|
|
|
|
sk <- getEnvKey "AWS_SECRET_ACCESS_KEY"
|
|
|
|
if (null ak || null sk)
|
|
|
|
then do
|
|
|
|
warning "Set both AWS_ACCESS_KEY_ID and AWS_SECRET_ACCESS_KEY to use S3"
|
|
|
|
return Nothing
|
|
|
|
else return $ Just $ AWSConnection host port ak sk
|
|
|
|
where
|
|
|
|
host = fromJust $ (M.lookup "host" c)
|
|
|
|
port = let s = fromJust $ (M.lookup "port" c) in
|
|
|
|
case reads s of
|
|
|
|
[(p, _)] -> p
|
|
|
|
_ -> error $ "bad S3 port value: " ++ s
|
|
|
|
getEnvKey s = liftIO $ catch (getEnv s) (const $ return "")
|
|
|
|
|
|
|
|
s3Action :: Remote Annex -> a -> ((AWSConnection, String) -> Annex a) -> Annex a
|
|
|
|
s3Action r noconn action = do
|
|
|
|
when (config r == Nothing) $
|
|
|
|
error $ "Missing configuration for special remote " ++ name r
|
|
|
|
let bucket = M.lookup "bucket" $ fromJust $ config r
|
|
|
|
conn <- s3Connection (fromJust $ config r)
|
|
|
|
case (bucket, conn) of
|
|
|
|
(Just b, Just c) -> action (c, b)
|
|
|
|
_ -> return noconn
|
|
|
|
|
|
|
|
bucketKey :: String -> Key -> L.ByteString -> S3Object
|
|
|
|
bucketKey bucket k content = S3Object bucket (show k) "" [] content
|