centralized "yes"/"no" parsing

This commit was sponsored by Jack Hill on Patreon.
This commit is contained in:
Joey Hess 2018-10-10 11:07:49 -04:00
parent 6f0d8870df
commit a9dd087074
No known key found for this signature in database
GPG key ID: DB12DB0FF05F8F38
7 changed files with 25 additions and 21 deletions

View file

@ -12,9 +12,11 @@ import Annex.CatFile
import Types.Key import Types.Key
import Types.Remote import Types.Remote
import qualified Git import qualified Git
import Config
import qualified Data.Map as M import qualified Data.Map as M
import Control.Applicative import Control.Applicative
import Data.Maybe
import Prelude import Prelude
-- An export includes both annexed files and files stored in git. -- An export includes both annexed files and files stored in git.
@ -40,6 +42,4 @@ exportKey sha = mk <$> catKey sha
} }
exportTree :: RemoteConfig -> Bool exportTree :: RemoteConfig -> Bool
exportTree c = case M.lookup "exporttree" c of exportTree c = fromMaybe False $ yesNo =<< M.lookup "exporttree" c
Just "yes" -> True
_ -> False

View file

@ -102,3 +102,8 @@ setCrippledFileSystem :: Bool -> Annex ()
setCrippledFileSystem b = do setCrippledFileSystem b = do
setConfig (annexConfig "crippledfilesystem") (Git.Config.boolConfig b) setConfig (annexConfig "crippledfilesystem") (Git.Config.boolConfig b)
Annex.changeGitConfig $ \c -> c { annexCrippledFileSystem = b } Annex.changeGitConfig $ \c -> c { annexCrippledFileSystem = b }
yesNo :: String -> Maybe Bool
yesNo "yes" = Just True
yesNo "no" = Just False
yesNo _ = Nothing

View file

@ -25,6 +25,7 @@ import qualified Data.ByteString as B
import Annex.Common import Annex.Common
import Types.Remote import Types.Remote
import Config
import Crypto import Crypto
import Types.Crypto import Types.Crypto
import qualified Annex import qualified Annex
@ -128,11 +129,9 @@ remoteCipher' c gc = go $ extractCipher c
- Not when a shared cipher is used. - Not when a shared cipher is used.
-} -}
embedCreds :: RemoteConfig -> Bool embedCreds :: RemoteConfig -> Bool
embedCreds c embedCreds c = case yesNo =<< M.lookup "embedcreds" c of
| M.lookup "embedcreds" c == Just "yes" = True Just v -> v
| M.lookup "embedcreds" c == Just "no" = False Nothing -> isJust (M.lookup "cipherkeys" c) && isJust (M.lookup "cipher" c)
| isJust (M.lookup "cipherkeys" c) && isJust (M.lookup "cipher" c) = True
| otherwise = False
{- Gets encryption Cipher, and key encryptor. -} {- Gets encryption Cipher, and key encryptor. -}
cipherKey :: RemoteConfig -> RemoteGitConfig -> Annex (Maybe (Cipher, EncKey)) cipherKey :: RemoteConfig -> RemoteGitConfig -> Annex (Maybe (Cipher, EncKey))

View file

@ -17,6 +17,7 @@ import Backend
import Remote.Helper.Encryptable (isEncrypted) import Remote.Helper.Encryptable (isEncrypted)
import Database.Export import Database.Export
import Annex.Export import Annex.Export
import Config
import qualified Data.Map as M import qualified Data.Map as M
import Control.Concurrent.STM import Control.Concurrent.STM
@ -69,13 +70,14 @@ adjustExportableRemoteType rt = rt { setup = setup' }
-- remote to be an export. -- remote to be an export.
adjustExportable :: Remote -> Annex Remote adjustExportable :: Remote -> Annex Remote
adjustExportable r = case M.lookup "exporttree" (config r) of adjustExportable r = case M.lookup "exporttree" (config r) of
Just "yes" -> ifM (isExportSupported r) Nothing -> notexport
Just c -> case yesNo c of
Just True -> ifM (isExportSupported r)
( isexport ( isexport
, notexport , notexport
) )
Nothing -> notexport Just False -> notexport
Just "no" -> notexport Nothing -> do
Just _ -> do
warning $ "bad exporttree value for " ++ name r ++ ", assuming not an export" warning $ "bad exporttree value for " ++ name r ++ ", assuming not an export"
notexport notexport
where where

View file

@ -114,7 +114,7 @@ genRsyncOpts c gc transport url = RsyncOpts
, rsyncOptions = transport ++ opts [] , rsyncOptions = transport ++ opts []
, rsyncUploadOptions = transport ++ opts (remoteAnnexRsyncUploadOptions gc) , rsyncUploadOptions = transport ++ opts (remoteAnnexRsyncUploadOptions gc)
, rsyncDownloadOptions = transport ++ opts (remoteAnnexRsyncDownloadOptions gc) , rsyncDownloadOptions = transport ++ opts (remoteAnnexRsyncDownloadOptions gc)
, rsyncShellEscape = M.lookup "shellescape" c /= Just "no" , rsyncShellEscape = (yesNo =<< M.lookup "shellescape" c) /= Just False
} }
where where
opts specificopts = map Param $ filter safe $ opts specificopts = map Param $ filter safe $

View file

@ -605,9 +605,7 @@ extractS3Info c = do
, host = M.lookup "host" c , host = M.lookup "host" c
} }
where where
boolcfg k = case M.lookup k c of boolcfg k = fromMaybe False $ yesNo =<< M.lookup k c
Just "yes" -> True
_ -> False
putObject :: S3Info -> T.Text -> RequestBody -> S3.PutObject putObject :: S3Info -> T.Text -> RequestBody -> S3.PutObject
putObject info file rbody = (S3.putObject (bucket info) file rbody) putObject info file rbody = (S3.putObject (bucket info) file rbody)

View file

@ -104,7 +104,7 @@ tahoeSetup _ mu _ c _ = do
u <- maybe (liftIO genUUID) return mu u <- maybe (liftIO genUUID) return mu
configdir <- liftIO $ defaultTahoeConfigDir u configdir <- liftIO $ defaultTahoeConfigDir u
scs <- liftIO $ tahoeConfigure configdir furl (M.lookup scsk c) scs <- liftIO $ tahoeConfigure configdir furl (M.lookup scsk c)
let c' = if M.lookup "embedcreds" c == Just "yes" let c' = if (yesNo =<< M.lookup "embedcreds" c) == Just True
then flip M.union c $ M.fromList then flip M.union c $ M.fromList
[ (furlk, furl) [ (furlk, furl)
, (scsk, scs) , (scsk, scs)