2012-11-24 20:30:15 +00:00
|
|
|
{- git-annex assistant webapp configurators for Amazon AWS services
|
|
|
|
-
|
|
|
|
- Copyright 2012 Joey Hess <joey@kitenet.net>
|
|
|
|
-
|
|
|
|
- Licensed under the GNU AGPL version 3 or higher.
|
|
|
|
-}
|
|
|
|
|
2013-06-05 01:02:09 +00:00
|
|
|
{-# LANGUAGE CPP, QuasiQuotes, TemplateHaskell, OverloadedStrings #-}
|
2012-11-24 20:30:15 +00:00
|
|
|
|
|
|
|
module Assistant.WebApp.Configurators.AWS where
|
|
|
|
|
2012-11-25 04:26:46 +00:00
|
|
|
import Assistant.WebApp.Common
|
2013-10-28 15:33:14 +00:00
|
|
|
import Assistant.WebApp.MakeRemote
|
2012-11-24 20:30:15 +00:00
|
|
|
#ifdef WITH_S3
|
|
|
|
import qualified Remote.S3 as S3
|
|
|
|
#endif
|
|
|
|
import qualified Remote.Glacier as Glacier
|
|
|
|
import qualified Remote.Helper.AWS as AWS
|
|
|
|
import Logs.Remote
|
|
|
|
import qualified Remote
|
2013-04-27 19:16:06 +00:00
|
|
|
import qualified Types.Remote as Remote
|
2012-11-24 20:30:15 +00:00
|
|
|
import Types.Remote (RemoteConfig)
|
|
|
|
import Types.StandardGroups
|
2013-04-27 19:16:06 +00:00
|
|
|
import Creds
|
2013-09-26 20:09:45 +00:00
|
|
|
import Assistant.Gpg
|
2013-11-07 22:02:00 +00:00
|
|
|
import Git.Types (RemoteName)
|
2012-11-24 20:30:15 +00:00
|
|
|
|
|
|
|
import qualified Data.Text as T
|
|
|
|
import qualified Data.Map as M
|
2013-01-14 16:54:29 +00:00
|
|
|
import Data.Char
|
2012-11-24 20:30:15 +00:00
|
|
|
|
2013-06-27 05:15:28 +00:00
|
|
|
awsConfigurator :: Widget -> Handler Html
|
2012-12-30 03:10:18 +00:00
|
|
|
awsConfigurator = page "Add an Amazon repository" (Just Configuration)
|
2012-11-24 20:30:15 +00:00
|
|
|
|
2013-06-27 05:15:28 +00:00
|
|
|
glacierConfigurator :: Widget -> Handler Html
|
2012-11-24 20:30:15 +00:00
|
|
|
glacierConfigurator a = do
|
|
|
|
ifM (liftIO $ inPath "glacier")
|
|
|
|
( awsConfigurator a
|
|
|
|
, awsConfigurator needglaciercli
|
|
|
|
)
|
|
|
|
where
|
|
|
|
needglaciercli = $(widgetFile "configurators/needglaciercli")
|
|
|
|
|
|
|
|
data StorageClass = StandardRedundancy | ReducedRedundancy
|
|
|
|
deriving (Eq, Enum, Bounded)
|
|
|
|
|
|
|
|
instance Show StorageClass where
|
|
|
|
show StandardRedundancy = "STANDARD"
|
|
|
|
show ReducedRedundancy = "REDUCED_REDUNDANCY"
|
|
|
|
|
|
|
|
data AWSInput = AWSInput
|
|
|
|
{ accessKeyID :: Text
|
|
|
|
, secretAccessKey :: Text
|
|
|
|
, datacenter :: Text
|
|
|
|
-- Only used for S3, not Glacier.
|
|
|
|
, storageClass :: StorageClass
|
|
|
|
, repoName :: Text
|
2012-12-04 17:28:22 +00:00
|
|
|
, enableEncryption :: EnableEncryption
|
2012-11-24 20:30:15 +00:00
|
|
|
}
|
|
|
|
|
|
|
|
data AWSCreds = AWSCreds Text Text
|
|
|
|
|
|
|
|
extractCreds :: AWSInput -> AWSCreds
|
|
|
|
extractCreds i = AWSCreds (accessKeyID i) (secretAccessKey i)
|
|
|
|
|
2013-06-03 20:33:05 +00:00
|
|
|
s3InputAForm :: Maybe CredPair -> MkAForm AWSInput
|
2013-04-27 19:16:06 +00:00
|
|
|
s3InputAForm defcreds = AWSInput
|
|
|
|
<$> accessKeyIDFieldWithHelp (T.pack . fst <$> defcreds)
|
|
|
|
<*> secretAccessKeyField (T.pack . snd <$> defcreds)
|
2012-12-03 02:33:30 +00:00
|
|
|
<*> datacenterField AWS.S3
|
2014-04-18 00:07:09 +00:00
|
|
|
<*> areq (selectFieldList storageclasses) (bfs "Storage class") (Just StandardRedundancy)
|
|
|
|
<*> areq textField (bfs "Repository name") (Just "S3")
|
2012-12-04 17:28:22 +00:00
|
|
|
<*> enableEncryptionField
|
2012-11-24 20:30:15 +00:00
|
|
|
where
|
|
|
|
storageclasses :: [(Text, StorageClass)]
|
|
|
|
storageclasses =
|
|
|
|
[ ("Standard redundancy", StandardRedundancy)
|
|
|
|
, ("Reduced redundancy (costs less)", ReducedRedundancy)
|
|
|
|
]
|
|
|
|
|
2013-06-03 20:33:05 +00:00
|
|
|
glacierInputAForm :: Maybe CredPair -> MkAForm AWSInput
|
2013-04-27 19:16:06 +00:00
|
|
|
glacierInputAForm defcreds = AWSInput
|
|
|
|
<$> accessKeyIDFieldWithHelp (T.pack . fst <$> defcreds)
|
|
|
|
<*> secretAccessKeyField (T.pack . snd <$> defcreds)
|
2012-12-03 02:33:30 +00:00
|
|
|
<*> datacenterField AWS.Glacier
|
2012-11-24 20:30:15 +00:00
|
|
|
<*> pure StandardRedundancy
|
2014-04-18 00:07:09 +00:00
|
|
|
<*> areq textField (bfs "Repository name") (Just "glacier")
|
2012-12-04 17:28:22 +00:00
|
|
|
<*> enableEncryptionField
|
2012-11-24 20:30:15 +00:00
|
|
|
|
2013-06-03 20:33:05 +00:00
|
|
|
awsCredsAForm :: Maybe CredPair -> MkAForm AWSCreds
|
2013-04-27 19:16:06 +00:00
|
|
|
awsCredsAForm defcreds = AWSCreds
|
|
|
|
<$> accessKeyIDFieldWithHelp (T.pack . fst <$> defcreds)
|
|
|
|
<*> secretAccessKeyField (T.pack . snd <$> defcreds)
|
2012-12-03 02:33:30 +00:00
|
|
|
|
2013-06-03 20:33:05 +00:00
|
|
|
accessKeyIDField :: Widget -> Maybe Text -> MkAForm Text
|
2014-04-18 00:07:09 +00:00
|
|
|
accessKeyIDField help = areq (textField `withNote` help) (bfs "Access Key ID")
|
2013-04-25 16:23:36 +00:00
|
|
|
|
2013-06-03 20:33:05 +00:00
|
|
|
accessKeyIDFieldWithHelp :: Maybe Text -> MkAForm Text
|
2013-10-02 05:06:59 +00:00
|
|
|
accessKeyIDFieldWithHelp = accessKeyIDField help
|
2012-12-03 02:33:30 +00:00
|
|
|
where
|
|
|
|
help = [whamlet|
|
|
|
|
<a href="https://portal.aws.amazon.com/gp/aws/securityCredentials#id_block">
|
|
|
|
Get Amazon access keys
|
|
|
|
|]
|
|
|
|
|
2013-06-03 20:33:05 +00:00
|
|
|
secretAccessKeyField :: Maybe Text -> MkAForm Text
|
2014-04-18 00:07:09 +00:00
|
|
|
secretAccessKeyField = areq passwordField (bfs "Secret Access Key")
|
2012-12-03 02:33:30 +00:00
|
|
|
|
2013-06-03 20:33:05 +00:00
|
|
|
datacenterField :: AWS.Service -> MkAForm Text
|
2014-04-18 00:07:09 +00:00
|
|
|
datacenterField service = areq (selectFieldList list) (bfs "Datacenter") defregion
|
2012-12-03 02:33:30 +00:00
|
|
|
where
|
|
|
|
list = M.toList $ AWS.regionMap service
|
|
|
|
defregion = Just $ AWS.defaultRegion service
|
2012-11-24 20:30:15 +00:00
|
|
|
|
2013-06-27 05:15:28 +00:00
|
|
|
getAddS3R :: Handler Html
|
2013-03-16 22:48:23 +00:00
|
|
|
getAddS3R = postAddS3R
|
|
|
|
|
2013-06-27 05:15:28 +00:00
|
|
|
postAddS3R :: Handler Html
|
2012-11-24 20:30:15 +00:00
|
|
|
#ifdef WITH_S3
|
2013-03-16 22:48:23 +00:00
|
|
|
postAddS3R = awsConfigurator $ do
|
2013-04-27 19:16:06 +00:00
|
|
|
defcreds <- liftAnnex previouslyUsedAWSCreds
|
2013-06-03 17:51:54 +00:00
|
|
|
((result, form), enctype) <- liftH $
|
2014-04-18 00:07:09 +00:00
|
|
|
runFormPostNoToken $ renderBootstrap3 bootstrapFormLayout $ s3InputAForm defcreds
|
2012-11-24 20:30:15 +00:00
|
|
|
case result of
|
2013-06-03 17:51:54 +00:00
|
|
|
FormSuccess input -> liftH $ do
|
2012-11-24 20:30:15 +00:00
|
|
|
let name = T.unpack $ repoName input
|
2013-09-27 04:15:50 +00:00
|
|
|
makeAWSRemote initSpecialRemote S3.remote TransferGroup (extractCreds input) name $ M.fromList
|
2012-12-04 17:28:22 +00:00
|
|
|
[ configureEncryption $ enableEncryption input
|
2012-11-24 20:30:15 +00:00
|
|
|
, ("type", "S3")
|
|
|
|
, ("datacenter", T.unpack $ datacenter input)
|
|
|
|
, ("storageclass", show $ storageClass input)
|
2014-08-02 19:51:58 +00:00
|
|
|
, ("chunk", "1MiB")
|
2012-11-24 20:30:15 +00:00
|
|
|
]
|
2012-11-25 04:38:11 +00:00
|
|
|
_ -> $(widgetFile "configurators/adds3")
|
2012-11-24 20:30:15 +00:00
|
|
|
#else
|
2013-03-16 22:48:23 +00:00
|
|
|
postAddS3R = error "S3 not supported by this build"
|
2012-11-24 20:30:15 +00:00
|
|
|
#endif
|
|
|
|
|
2013-06-27 05:15:28 +00:00
|
|
|
getAddGlacierR :: Handler Html
|
2013-03-16 22:48:23 +00:00
|
|
|
getAddGlacierR = postAddGlacierR
|
|
|
|
|
2013-06-27 05:15:28 +00:00
|
|
|
postAddGlacierR :: Handler Html
|
2013-05-01 17:27:51 +00:00
|
|
|
#ifdef WITH_S3
|
2013-03-16 22:48:23 +00:00
|
|
|
postAddGlacierR = glacierConfigurator $ do
|
2013-04-27 19:16:06 +00:00
|
|
|
defcreds <- liftAnnex previouslyUsedAWSCreds
|
2013-06-03 17:51:54 +00:00
|
|
|
((result, form), enctype) <- liftH $
|
2014-04-18 00:07:09 +00:00
|
|
|
runFormPostNoToken $ renderBootstrap3 bootstrapFormLayout $ glacierInputAForm defcreds
|
2012-11-24 20:30:15 +00:00
|
|
|
case result of
|
2013-06-03 17:51:54 +00:00
|
|
|
FormSuccess input -> liftH $ do
|
2012-11-24 20:30:15 +00:00
|
|
|
let name = T.unpack $ repoName input
|
2013-09-27 04:15:50 +00:00
|
|
|
makeAWSRemote initSpecialRemote Glacier.remote SmallArchiveGroup (extractCreds input) name $ M.fromList
|
2012-12-04 17:28:22 +00:00
|
|
|
[ configureEncryption $ enableEncryption input
|
2012-11-24 20:30:15 +00:00
|
|
|
, ("type", "glacier")
|
|
|
|
, ("datacenter", T.unpack $ datacenter input)
|
|
|
|
]
|
2012-11-25 04:38:11 +00:00
|
|
|
_ -> $(widgetFile "configurators/addglacier")
|
2013-05-01 17:27:51 +00:00
|
|
|
#else
|
|
|
|
postAddGlacierR = error "S3 not supported by this build"
|
|
|
|
#endif
|
2012-11-24 20:30:15 +00:00
|
|
|
|
2013-06-27 05:15:28 +00:00
|
|
|
getEnableS3R :: UUID -> Handler Html
|
2013-04-26 20:07:55 +00:00
|
|
|
#ifdef WITH_S3
|
2013-04-25 17:14:49 +00:00
|
|
|
getEnableS3R uuid = do
|
|
|
|
m <- liftAnnex readRemoteLog
|
2014-10-24 00:25:31 +00:00
|
|
|
if maybe False S3.configIA (M.lookup uuid m)
|
2013-04-25 17:14:49 +00:00
|
|
|
then redirect $ EnableIAR uuid
|
|
|
|
else postEnableS3R uuid
|
2013-04-26 20:07:55 +00:00
|
|
|
#else
|
|
|
|
getEnableS3R = postEnableS3R
|
|
|
|
#endif
|
2013-03-16 22:48:23 +00:00
|
|
|
|
2013-06-27 05:15:28 +00:00
|
|
|
postEnableS3R :: UUID -> Handler Html
|
2012-11-24 20:30:15 +00:00
|
|
|
#ifdef WITH_S3
|
2013-04-25 17:14:49 +00:00
|
|
|
postEnableS3R uuid = awsConfigurator $ enableAWSRemote S3.remote uuid
|
2012-11-24 20:30:15 +00:00
|
|
|
#else
|
2013-03-16 22:48:23 +00:00
|
|
|
postEnableS3R _ = error "S3 not supported by this build"
|
2012-11-24 20:30:15 +00:00
|
|
|
#endif
|
|
|
|
|
2013-06-27 05:15:28 +00:00
|
|
|
getEnableGlacierR :: UUID -> Handler Html
|
2013-03-16 22:48:23 +00:00
|
|
|
getEnableGlacierR = postEnableGlacierR
|
|
|
|
|
2013-06-27 05:15:28 +00:00
|
|
|
postEnableGlacierR :: UUID -> Handler Html
|
2013-03-16 22:48:23 +00:00
|
|
|
postEnableGlacierR = glacierConfigurator . enableAWSRemote Glacier.remote
|
2012-11-24 20:30:15 +00:00
|
|
|
|
|
|
|
enableAWSRemote :: RemoteType -> UUID -> Widget
|
2013-05-01 17:27:51 +00:00
|
|
|
#ifdef WITH_S3
|
2012-11-24 20:30:15 +00:00
|
|
|
enableAWSRemote remotetype uuid = do
|
2013-04-27 19:16:06 +00:00
|
|
|
defcreds <- liftAnnex previouslyUsedAWSCreds
|
2013-06-03 17:51:54 +00:00
|
|
|
((result, form), enctype) <- liftH $
|
2014-04-18 00:07:09 +00:00
|
|
|
runFormPostNoToken $ renderBootstrap3 bootstrapFormLayout $ awsCredsAForm defcreds
|
2012-11-24 20:30:15 +00:00
|
|
|
case result of
|
2013-06-03 17:51:54 +00:00
|
|
|
FormSuccess creds -> liftH $ do
|
2013-03-04 20:36:38 +00:00
|
|
|
m <- liftAnnex readRemoteLog
|
2012-11-24 20:30:15 +00:00
|
|
|
let name = fromJust $ M.lookup "name" $
|
|
|
|
fromJust $ M.lookup uuid m
|
2013-09-27 04:15:50 +00:00
|
|
|
makeAWSRemote enableSpecialRemote remotetype SmallArchiveGroup creds name M.empty
|
2012-11-24 20:30:15 +00:00
|
|
|
_ -> do
|
2013-03-16 04:12:28 +00:00
|
|
|
description <- liftAnnex $
|
2013-04-03 21:01:40 +00:00
|
|
|
T.pack <$> Remote.prettyUUID uuid
|
2012-11-24 20:30:15 +00:00
|
|
|
$(widgetFile "configurators/enableaws")
|
2013-05-01 17:27:51 +00:00
|
|
|
#else
|
|
|
|
enableAWSRemote _ _ = error "S3 not supported by this build"
|
|
|
|
#endif
|
2012-11-24 20:30:15 +00:00
|
|
|
|
2013-09-27 04:15:50 +00:00
|
|
|
makeAWSRemote :: SpecialRemoteMaker -> RemoteType -> StandardGroup -> AWSCreds -> RemoteName -> RemoteConfig -> Handler ()
|
2014-02-11 18:06:50 +00:00
|
|
|
makeAWSRemote maker remotetype defaultgroup (AWSCreds ak sk) name config =
|
2013-09-29 18:39:10 +00:00
|
|
|
setupCloudRemote defaultgroup Nothing $
|
2014-02-11 18:06:50 +00:00
|
|
|
maker hostname remotetype (Just creds) config
|
2013-01-14 16:54:29 +00:00
|
|
|
where
|
2014-10-09 18:53:13 +00:00
|
|
|
creds = (T.unpack ak, T.unpack sk)
|
2013-01-14 16:54:29 +00:00
|
|
|
{- AWS services use the remote name as the basis for a host
|
|
|
|
- name, so filter it to contain valid characters. -}
|
|
|
|
hostname = case filter isAlphaNum name of
|
|
|
|
[] -> "aws"
|
|
|
|
n -> n
|
2013-04-25 20:42:17 +00:00
|
|
|
|
|
|
|
getRepoInfo :: RemoteConfig -> Widget
|
|
|
|
getRepoInfo c = [whamlet|S3 remote using bucket: #{bucket}|]
|
|
|
|
where
|
|
|
|
bucket = fromMaybe "" $ M.lookup "bucket" c
|
2013-04-27 19:16:06 +00:00
|
|
|
|
|
|
|
#ifdef WITH_S3
|
|
|
|
previouslyUsedAWSCreds :: Annex (Maybe CredPair)
|
|
|
|
previouslyUsedAWSCreds = getM gettype [S3.remote, Glacier.remote]
|
|
|
|
where
|
|
|
|
gettype t = previouslyUsedCredPair AWS.creds t $
|
2014-10-23 19:56:35 +00:00
|
|
|
not . S3.configIA . Remote.config
|
2013-05-01 17:27:51 +00:00
|
|
|
#endif
|