git-annex/Assistant/WebApp/Configurators/S3.hs

129 lines
4 KiB
Haskell
Raw Normal View History

2012-09-26 18:44:07 +00:00
{- git-annex assistant webapp configurator for Amazon S3
-
- Copyright 2012 Joey Hess <joey@kitenet.net>
-
- Licensed under the GNU AGPL version 3 or higher.
-}
{-# LANGUAGE TypeFamilies, QuasiQuotes, MultiParamTypeClasses, TemplateHaskell, OverloadedStrings, RankNTypes #-}
module Assistant.WebApp.Configurators.S3 where
import Assistant.Common
import Assistant.MakeRemote
import Assistant.Sync
import Assistant.WebApp
import Assistant.WebApp.Types
import Assistant.WebApp.SideBar
import Assistant.ThreadedMonad
import Utility.Yesod
import qualified Remote.S3 as S3
2012-09-26 19:24:23 +00:00
import Logs.Remote
import qualified Remote
2012-09-26 19:24:23 +00:00
import Types.Remote (RemoteConfig)
import Logs.Group
2012-09-26 18:44:07 +00:00
import Yesod
import Data.Text (Text)
import qualified Data.Text as T
import qualified Data.Set as S
2012-09-26 18:44:07 +00:00
import qualified Data.Map as M
2012-09-26 19:24:23 +00:00
s3Configurator :: Widget -> Handler RepHtml
s3Configurator a = bootstrap (Just Config) $ do
sideBarDisplay
setTitle "Add an Amazon S3 repository"
a
data StorageClass = StandardRedundancy | ReducedRedundancy
deriving (Eq, Enum, Bounded)
instance Show StorageClass where
show StandardRedundancy = "STANDARD"
show ReducedRedundancy = "REDUCED_REDUNDANCY"
2012-09-26 18:44:07 +00:00
data S3Input = S3Input
{ accessKeyID :: Text
, secretAccessKey :: Text
-- Free form text for datacenter because Amazon adds new ones.
, datacenter :: Text
, storageClass :: StorageClass
, repoName :: Text
}
2012-09-26 19:24:23 +00:00
data S3Creds = S3Creds Text Text
2012-09-26 18:44:07 +00:00
2012-09-26 19:24:23 +00:00
extractCreds :: S3Input -> S3Creds
extractCreds i = S3Creds (accessKeyID i) (secretAccessKey i)
2012-09-26 18:44:07 +00:00
2012-09-26 19:24:23 +00:00
s3InputAForm :: AForm WebApp WebApp S3Input
s3InputAForm = S3Input
2012-09-26 18:44:07 +00:00
<$> areq textField "Access Key ID" Nothing
<*> areq passwordField "Secret Access Key" Nothing
<*> areq textField "Datacenter" (Just "US")
<*> areq (selectFieldList storageclasses) "Storage class" (Just StandardRedundancy)
<*> areq textField "Repository name" (Just "S3")
where
storageclasses :: [(Text, StorageClass)]
storageclasses =
[ ("Standard redundancy", StandardRedundancy)
, ("Reduced redundancy (costs less)", ReducedRedundancy)
]
2012-09-26 19:24:23 +00:00
s3CredsAForm :: AForm WebApp WebApp S3Creds
s3CredsAForm = S3Creds
<$> areq textField "Access Key ID" Nothing
<*> areq passwordField "Secret Access Key" Nothing
2012-09-26 18:44:07 +00:00
getAddS3R :: Handler RepHtml
2012-09-26 19:24:23 +00:00
getAddS3R = s3Configurator $ do
2012-09-26 18:44:07 +00:00
((result, form), enctype) <- lift $
2012-09-26 19:24:23 +00:00
runFormGet $ renderBootstrap s3InputAForm
2012-09-26 18:44:07 +00:00
case result of
FormSuccess s3input -> lift $ do
let name = T.unpack $ repoName s3input
makeS3Remote (extractCreds s3input) name setgroup $ M.fromList
2012-09-26 19:24:23 +00:00
[ ("encryption", "shared")
, ("type", "S3")
, ("datacenter", T.unpack $ datacenter s3input)
, ("storageclass", show $ storageClass s3input)
]
2012-09-26 18:44:07 +00:00
_ -> showform form enctype
where
showform form enctype = do
let authtoken = webAppFormAuthToken
$(widgetFile "configurators/adds3")
setgroup r = runAnnex () $
groupSet (Remote.uuid r) (S.singleton "servers")
2012-09-26 18:44:07 +00:00
2012-09-26 19:24:23 +00:00
getEnableS3R :: UUID -> Handler RepHtml
getEnableS3R uuid = s3Configurator $ do
((result, form), enctype) <- lift $
runFormGet $ renderBootstrap s3CredsAForm
case result of
FormSuccess s3creds -> lift $ do
m <- runAnnex M.empty readRemoteLog
let name = fromJust $ M.lookup "name" $
fromJust $ M.lookup uuid m
makeS3Remote s3creds name (const noop) M.empty
2012-09-26 19:24:23 +00:00
_ -> showform form enctype
where
showform form enctype = do
let authtoken = webAppFormAuthToken
description <- lift $ runAnnex "" $
T.pack . concat <$> Remote.prettyListUUIDs [uuid]
2012-09-26 19:24:23 +00:00
$(widgetFile "configurators/enables3")
makeS3Remote :: S3Creds -> String -> (Remote -> Handler ()) -> RemoteConfig -> Handler ()
makeS3Remote (S3Creds ak sk) name setup config = do
2012-09-26 18:44:07 +00:00
webapp <- getYesod
let st = fromJust $ threadState webapp
2012-09-26 19:24:23 +00:00
remotename <- runAnnex name $ fromRepo $ uniqueRemoteName name 0
liftIO $ S3.s3SetCredsEnv ( T.unpack ak, T.unpack sk)
r <- liftIO $ runThreadState st $ addRemote $ do
makeSpecialRemote name S3.remote config
return remotename
setup r
liftIO $ syncNewRemote st (daemonStatus webapp) (scanRemotes webapp) r
2012-09-26 18:44:07 +00:00
redirect RepositoriesR