2013-09-18 00:02:42 +00:00
|
|
|
|
{- git-annex webapp gpg stuff
|
|
|
|
|
-
|
|
|
|
|
- Copyright 2013 Joey Hess <joey@kitenet.net>
|
|
|
|
|
-
|
|
|
|
|
- Licensed under the GNU AGPL version 3 or higher.
|
|
|
|
|
-}
|
|
|
|
|
|
2013-09-26 16:40:19 +00:00
|
|
|
|
{-# LANGUAGE QuasiQuotes, TemplateHaskell, OverloadedStrings #-}
|
2013-09-18 00:02:42 +00:00
|
|
|
|
|
|
|
|
|
module Assistant.WebApp.Gpg where
|
|
|
|
|
|
|
|
|
|
import Assistant.WebApp.Common
|
2013-09-26 20:09:45 +00:00
|
|
|
|
import Assistant.Gpg
|
2013-09-18 00:02:42 +00:00
|
|
|
|
import Utility.Gpg
|
2013-09-18 19:30:53 +00:00
|
|
|
|
import qualified Git.Command
|
|
|
|
|
import qualified Git.Remote
|
2013-09-27 20:21:56 +00:00
|
|
|
|
import qualified Git.Construct
|
2013-09-18 19:30:53 +00:00
|
|
|
|
import qualified Annex.Branch
|
|
|
|
|
import qualified Git.GCrypt
|
2013-09-27 20:21:56 +00:00
|
|
|
|
import qualified Remote.GCrypt as GCrypt
|
2013-11-07 22:02:00 +00:00
|
|
|
|
import Git.Types (RemoteName)
|
2013-10-28 15:33:14 +00:00
|
|
|
|
import Assistant.WebApp.MakeRemote
|
2013-09-18 19:30:53 +00:00
|
|
|
|
import Logs.Remote
|
2013-09-18 00:02:42 +00:00
|
|
|
|
|
|
|
|
|
import qualified Data.Map as M
|
|
|
|
|
|
|
|
|
|
gpgKeyDisplay :: KeyId -> Maybe UserId -> Widget
|
|
|
|
|
gpgKeyDisplay keyid userid = [whamlet|
|
|
|
|
|
<span title="key id #{keyid}">
|
|
|
|
|
<i .icon-user></i> #
|
2013-09-20 16:19:55 +00:00
|
|
|
|
$maybe name <- userid
|
|
|
|
|
#{name}
|
|
|
|
|
$nothing
|
|
|
|
|
key id #{keyid}
|
2013-09-18 00:02:42 +00:00
|
|
|
|
|]
|
|
|
|
|
|
2013-09-26 20:09:45 +00:00
|
|
|
|
genKeyModal :: Widget
|
|
|
|
|
genKeyModal = $(widgetFile "configurators/genkeymodal")
|
|
|
|
|
|
2013-09-27 20:21:56 +00:00
|
|
|
|
isGcryptInstalled :: IO Bool
|
|
|
|
|
isGcryptInstalled = inPath "git-remote-gcrypt"
|
|
|
|
|
|
2013-09-26 20:09:45 +00:00
|
|
|
|
whenGcryptInstalled :: Handler Html -> Handler Html
|
2013-09-27 20:21:56 +00:00
|
|
|
|
whenGcryptInstalled a = ifM (liftIO isGcryptInstalled)
|
2013-09-26 20:09:45 +00:00
|
|
|
|
( a
|
|
|
|
|
, page "Need git-remote-gcrypt" (Just Configuration) $
|
|
|
|
|
$(widgetFile "configurators/needgcrypt")
|
|
|
|
|
)
|
2013-09-18 00:02:42 +00:00
|
|
|
|
|
|
|
|
|
withNewSecretKey :: (KeyId -> Handler Html) -> Handler Html
|
|
|
|
|
withNewSecretKey use = do
|
2013-10-02 05:06:59 +00:00
|
|
|
|
userid <- liftIO newUserId
|
2013-09-18 00:02:42 +00:00
|
|
|
|
liftIO $ genSecretKey RSA "" userid maxRecommendedKeySize
|
|
|
|
|
results <- M.keys . M.filter (== userid) <$> liftIO secretKeys
|
|
|
|
|
case results of
|
|
|
|
|
[] -> error "Failed to generate gpg key!"
|
|
|
|
|
(key:_) -> use key
|
2013-09-18 19:30:53 +00:00
|
|
|
|
|
|
|
|
|
{- Tries to find the name used in remote.log for a gcrypt repository
|
|
|
|
|
- with a given uuid.
|
|
|
|
|
-
|
|
|
|
|
- The gcrypt remote may not be on that is listed in the local remote.log
|
|
|
|
|
- (or the info may be out of date), so this actually fetches the git-annex
|
|
|
|
|
- branch from the gcrypt remote and merges it in, and then looks up
|
|
|
|
|
- the name.
|
|
|
|
|
-}
|
2013-11-07 22:02:00 +00:00
|
|
|
|
getGCryptRemoteName :: UUID -> String -> Annex RemoteName
|
2013-09-18 19:30:53 +00:00
|
|
|
|
getGCryptRemoteName u repoloc = do
|
|
|
|
|
tmpremote <- uniqueRemoteName "tmpgcryptremote" 0 <$> gitRepo
|
|
|
|
|
void $ inRepo $ Git.Command.runBool
|
|
|
|
|
[Params "remote add", Param tmpremote, Param $ Git.GCrypt.urlPrefix ++ repoloc]
|
|
|
|
|
mname <- ifM (inRepo $ Git.Command.runBool [Param "fetch", Param tmpremote])
|
|
|
|
|
( do
|
2013-10-02 05:06:59 +00:00
|
|
|
|
void Annex.Branch.forceUpdate
|
2013-09-18 19:30:53 +00:00
|
|
|
|
(M.lookup "name" <=< M.lookup u) <$> readRemoteLog
|
|
|
|
|
, return Nothing
|
|
|
|
|
)
|
|
|
|
|
void $ inRepo $ Git.Remote.remove tmpremote
|
2013-09-27 20:21:56 +00:00
|
|
|
|
maybe missing return mname
|
|
|
|
|
where
|
|
|
|
|
missing = error $ "Cannot find configuration for the gcrypt remote at " ++ repoloc
|
2013-09-26 16:40:19 +00:00
|
|
|
|
|
2013-10-22 17:32:10 +00:00
|
|
|
|
{- Checks to see if a repo is encrypted with gcrypt, and runs one action if
|
|
|
|
|
- it's not an another if it is.
|
|
|
|
|
-
|
|
|
|
|
- Since the probing requires gcrypt to be installed, a third action must
|
|
|
|
|
- be provided to run if it's not installed.
|
|
|
|
|
-}
|
2013-10-24 16:59:20 +00:00
|
|
|
|
checkGCryptRepoEncryption :: (Monad m, LiftAnnex m) => String -> m a -> m a -> m a -> m a
|
2013-10-22 17:32:10 +00:00
|
|
|
|
checkGCryptRepoEncryption location notencrypted notinstalled encrypted =
|
2013-10-24 16:59:20 +00:00
|
|
|
|
ifM (liftAnnex $ liftIO isGcryptInstalled)
|
2013-10-22 17:32:10 +00:00
|
|
|
|
( dispatch =<< liftAnnex (inRepo $ Git.GCrypt.probeRepo location)
|
|
|
|
|
, notinstalled
|
|
|
|
|
)
|
2013-09-27 05:03:50 +00:00
|
|
|
|
where
|
|
|
|
|
dispatch Git.GCrypt.Decryptable = encrypted
|
|
|
|
|
dispatch Git.GCrypt.NotEncrypted = notencrypted
|
|
|
|
|
dispatch Git.GCrypt.NotDecryptable =
|
|
|
|
|
error "This git repository is encrypted with a GnuPG key that you do not have."
|
2013-09-27 20:21:56 +00:00
|
|
|
|
|
|
|
|
|
{- Gets the UUID of the gcrypt repo at a location, which may not exist.
|
|
|
|
|
- Only works if the gcrypt repo was created as a git-annex remote. -}
|
|
|
|
|
probeGCryptRemoteUUID :: String -> Annex (Maybe UUID)
|
|
|
|
|
probeGCryptRemoteUUID repolocation = do
|
|
|
|
|
r <- inRepo $ Git.Construct.fromRemoteLocation repolocation
|
|
|
|
|
GCrypt.getGCryptUUID False r
|