annex.addunlocked expressions

* annex.addunlocked can be set to an expression with the same format used by
  annex.largefiles, in case you want to default to unlocking some files but
  not others.
* annex.addunlocked can be configured by git-annex config.

Added a git-annex-matching-expression man page, broken out from
tips/largefiles.

A tricky consequence of this is that git-annex add --relaxed
honors annex.addunlocked, but an expression might want to know the size
or content of an url, which it's not going to download. I decided it was
better not to fail, and just dummy up some plausible data in that case.

Performance impact should be negligible. The global config is already
loaded for annex.largefiles. The expression only has to be parsed once,
and in the simple true/false case, it should not do any additional work
matching it.
This commit is contained in:
Joey Hess 2019-12-20 15:01:34 -04:00
parent f79bd52132
commit 37467a008f
No known key found for this signature in database
GPG key ID: DB12DB0FF05F8F38
25 changed files with 305 additions and 179 deletions

View file

@ -20,8 +20,12 @@ module Annex.FileMatcher (
preferredContentParser, preferredContentParser,
ParseToken, ParseToken,
parsedToMatcher, parsedToMatcher,
mkLargeFilesParser, mkMatchExpressionParser,
largeFilesMatcher, largeFilesMatcher,
AddUnlockedMatcher,
addUnlockedMatcher,
checkAddUnlockedMatcher,
module Types.FileMatcher
) where ) where
import qualified Data.Map as M import qualified Data.Map as M
@ -37,6 +41,7 @@ import Git.FilePath
import Types.Remote (RemoteConfig) import Types.Remote (RemoteConfig)
import Annex.CheckAttr import Annex.CheckAttr
import Git.CheckAttr (unspecifiedAttr) import Git.CheckAttr (unspecifiedAttr)
import qualified Git.Config
#ifdef WITH_MAGICMIME #ifdef WITH_MAGICMIME
import Annex.Magic import Annex.Magic
#endif #endif
@ -174,8 +179,8 @@ preferredContentTokens pcd = concat
preferredContentParser :: [ParseToken (MatchFiles Annex)] -> String -> [ParseResult (MatchFiles Annex)] preferredContentParser :: [ParseToken (MatchFiles Annex)] -> String -> [ParseResult (MatchFiles Annex)]
preferredContentParser tokens = map (parseToken tokens) . tokenizeMatcher preferredContentParser tokens = map (parseToken tokens) . tokenizeMatcher
mkLargeFilesParser :: Annex (String -> [ParseResult (MatchFiles Annex)]) mkMatchExpressionParser :: Annex (String -> [ParseResult (MatchFiles Annex)])
mkLargeFilesParser = do mkMatchExpressionParser = do
#ifdef WITH_MAGICMIME #ifdef WITH_MAGICMIME
magicmime <- liftIO initMagicMime magicmime <- liftIO initMagicMime
let mimer n f = ValueToken n (usev $ f magicmime) let mimer n f = ValueToken n (usev $ f magicmime)
@ -198,7 +203,6 @@ mkLargeFilesParser = do
] ]
#endif #endif
return $ map parse . tokenizeMatcher return $ map parse . tokenizeMatcher
where
{- Generates a matcher for files large enough (or meeting other criteria) {- Generates a matcher for files large enough (or meeting other criteria)
- to be added to the annex, rather than directly to git. - to be added to the annex, rather than directly to git.
@ -222,10 +226,35 @@ largeFilesMatcher = go =<< getGitConfigVal' annexLargeFiles
else mkmatcher expr "gitattributes" else mkmatcher expr "gitattributes"
mkmatcher expr cfgfrom = do mkmatcher expr cfgfrom = do
parser <- mkLargeFilesParser parser <- mkMatchExpressionParser
either (badexpr cfgfrom) return $ parsedToMatcher $ parser expr either (badexpr cfgfrom) return $ parsedToMatcher $ parser expr
badexpr cfgfrom e = giveup $ "bad annex.largefiles configuration in " ++ cfgfrom ++ ": " ++ e badexpr cfgfrom e = giveup $ "bad annex.largefiles configuration in " ++ cfgfrom ++ ": " ++ e
newtype AddUnlockedMatcher = AddUnlockedMatcher (FileMatcher Annex)
addUnlockedMatcher :: Annex AddUnlockedMatcher
addUnlockedMatcher = AddUnlockedMatcher <$>
(go =<< getGitConfigVal' annexAddUnlocked)
where
go (HasGitConfig (Just expr)) = mkmatcher expr "git config"
go (HasGlobalConfig (Just expr)) = mkmatcher expr "git annex config"
go _ = matchalways False
mkmatcher :: String -> String -> Annex (FileMatcher Annex)
mkmatcher expr cfgfrom = case Git.Config.isTrueFalse expr of
Just b -> matchalways b
Nothing -> do
parser <- mkMatchExpressionParser
either (badexpr cfgfrom) return $ parsedToMatcher $ parser expr
badexpr cfgfrom e = giveup $ "bad annex.addunlocked configuration in " ++ cfgfrom ++ ": " ++ e
matchalways True = return $ MOp limitAnything
matchalways False = return $ MOp limitNothing
checkAddUnlockedMatcher :: AddUnlockedMatcher -> MatchInfo -> Annex Bool
checkAddUnlockedMatcher (AddUnlockedMatcher matcher) mi =
checkMatcher' matcher mi S.empty
simply :: MatchFiles Annex -> ParseResult (MatchFiles Annex) simply :: MatchFiles Annex -> ParseResult (MatchFiles Annex)
simply = Right . Operation simply = Right . Operation

View file

@ -25,6 +25,7 @@ module Annex.Ingest (
import Annex.Common import Annex.Common
import Types.KeySource import Types.KeySource
import Types.FileMatcher
import Backend import Backend
import Annex.Content import Annex.Content
import Annex.Perms import Annex.Perms
@ -45,6 +46,7 @@ import Utility.Metered
import Git.FilePath import Git.FilePath
import Annex.InodeSentinal import Annex.InodeSentinal
import Annex.AdjustedBranch import Annex.AdjustedBranch
import Annex.FileMatcher
import Control.Exception (IOException) import Control.Exception (IOException)
@ -306,10 +308,10 @@ forceParams = ifM (Annex.getState Annex.force)
- unless symlinks are not supported. annex.addunlocked can override that. - unless symlinks are not supported. annex.addunlocked can override that.
- Also, when in an adjusted unlocked branch, always add files unlocked. - Also, when in an adjusted unlocked branch, always add files unlocked.
-} -}
addUnlocked :: Annex Bool addUnlocked :: AddUnlockedMatcher -> MatchInfo -> Annex Bool
addUnlocked = addUnlocked matcher mi =
((not . coreSymlinks <$> Annex.getGitConfig) <||> ((not . coreSymlinks <$> Annex.getGitConfig) <||>
(annexAddUnlocked <$> Annex.getGitConfig) <||> (checkAddUnlockedMatcher matcher mi) <||>
(maybe False isadjustedunlocked . snd <$> getCurrentBranch) (maybe False isadjustedunlocked . snd <$> getCurrentBranch)
) )
where where
@ -319,12 +321,13 @@ addUnlocked =
{- Adds a file to the work tree for the key, and stages it in the index. {- Adds a file to the work tree for the key, and stages it in the index.
- The content of the key may be provided in a temp file, which will be - The content of the key may be provided in a temp file, which will be
- moved into place. - moved into place. If no content is provided, adds an annex link but does
- not ingest the content.
- -
- When the content of the key is not accepted into the annex, returns False. - When the content of the key is not accepted into the annex, returns False.
-} -}
addAnnexedFile :: FilePath -> Key -> Maybe FilePath -> Annex Bool addAnnexedFile :: AddUnlockedMatcher -> FilePath -> Key -> Maybe FilePath -> Annex Bool
addAnnexedFile file key mtmp = ifM addUnlocked addAnnexedFile matcher file key mtmp = ifM (addUnlocked matcher mi)
( do ( do
mode <- maybe mode <- maybe
(pure Nothing) (pure Nothing)
@ -348,6 +351,24 @@ addAnnexedFile file key mtmp = ifM addUnlocked
Nothing -> return True Nothing -> return True
) )
where where
mi = case mtmp of
Just tmp -> MatchingFile $ FileInfo
{ currFile = toRawFilePath tmp
, matchFile = toRawFilePath file
}
-- Provide as much info as we can without access to the
-- file's content. It's better to provide wrong info
-- than for an operation to fail just because it can't
-- tell if a file should be unlocked or locked.
Nothing -> MatchingInfo $ ProvidedInfo
{ providedFilePath = Right file
, providedKey = Right key
, providedFileSize = Right $ fromMaybe 0 $
keySize `fromKey` key
, providedMimeType = Right "application/octet-stream"
, providedMimeEncoding = Right "binary"
}
linkunlocked mode = linkFromAnnex key file mode >>= \case linkunlocked mode = linkFromAnnex key file mode >>= \case
LinkAnnexFailed -> liftIO $ LinkAnnexFailed -> liftIO $
writePointerFile (toRawFilePath file) key mode writePointerFile (toRawFilePath file) key mode

View file

@ -94,7 +94,7 @@ autoEnable = do
_ -> return () _ -> return ()
where where
configured rc = fromMaybe False $ configured rc = fromMaybe False $
Git.Config.isTrue =<< M.lookup autoEnableField rc Git.Config.isTrueFalse =<< M.lookup autoEnableField rc
canenable u = (/= DeadTrusted) <$> lookupTrust u canenable u = (/= DeadTrusted) <$> lookupTrust u
getenabledremotes = M.fromList getenabledremotes = M.fromList
. map (\r -> (getcu r, r)) . map (\r -> (getcu r, r))

View file

@ -11,6 +11,10 @@ git-annex (7.20191219) UNRELEASED; urgency=medium
to more easily set a default that will also be used by clones, to more easily set a default that will also be used by clones,
without needing to shoehorn the expression into the gitattributes file. without needing to shoehorn the expression into the gitattributes file.
The git config and gitattributes override that. The git config and gitattributes override that.
* annex.addunlocked can be set to an expression with the same format used by
annex.largefiles, when you want to default to unlocking some files but
not others.
* annex.addunlocked can be configured by git-annex config.
* git-annex-config --set/--unset: No longer change the local git config * git-annex-config --set/--unset: No longer change the local git config
setting, except for in the special case of annex.securehashesonly. setting, except for in the special case of annex.securehashesonly.

View file

@ -50,9 +50,10 @@ optParser desc = AddOptions
seek :: AddOptions -> CommandSeek seek :: AddOptions -> CommandSeek
seek o = startConcurrency commandStages $ do seek o = startConcurrency commandStages $ do
matcher <- largeFilesMatcher largematcher <- largeFilesMatcher
let gofile file = ifM (checkFileMatcher matcher (fromRawFilePath file) <||> Annex.getState Annex.force) addunlockedmatcher <- addUnlockedMatcher
( start file let gofile file = ifM (checkFileMatcher largematcher (fromRawFilePath file) <||> Annex.getState Annex.force)
( start file addunlockedmatcher
, ifM (annexAddSmallFiles <$> Annex.getGitConfig) , ifM (annexAddSmallFiles <$> Annex.getGitConfig)
( startSmall file ( startSmall file
, stop , stop
@ -87,8 +88,8 @@ addFile file = do
Annex.Queue.addCommand "add" (ps++[Param "--"]) [fromRawFilePath file] Annex.Queue.addCommand "add" (ps++[Param "--"]) [fromRawFilePath file]
return True return True
start :: RawFilePath -> CommandStart start :: RawFilePath -> AddUnlockedMatcher -> CommandStart
start file = do start file addunlockedmatcher = do
mk <- liftIO $ isPointerFile file mk <- liftIO $ isPointerFile file
maybe go fixuppointer mk maybe go fixuppointer mk
where where
@ -101,7 +102,7 @@ start file = do
starting "add" (ActionItemWorkTreeFile file) $ starting "add" (ActionItemWorkTreeFile file) $
if isSymbolicLink s if isSymbolicLink s
then next $ addFile file then next $ addFile file
else perform file else perform file addunlockedmatcher
addpresent key = addpresent key =
liftIO (catchMaybeIO $ R.getSymbolicLinkStatus file) >>= \case liftIO (catchMaybeIO $ R.getSymbolicLinkStatus file) >>= \case
Just s | isSymbolicLink s -> fixuplink key Just s | isSymbolicLink s -> fixuplink key
@ -117,9 +118,10 @@ start file = do
Database.Keys.addAssociatedFile key =<< inRepo (toTopFilePath file) Database.Keys.addAssociatedFile key =<< inRepo (toTopFilePath file)
next $ addFile file next $ addFile file
perform :: RawFilePath -> CommandPerform perform :: RawFilePath -> AddUnlockedMatcher -> CommandPerform
perform file = withOtherTmp $ \tmpdir -> do perform file addunlockedmatcher = withOtherTmp $ \tmpdir -> do
lockingfile <- not <$> addUnlocked lockingfile <- not <$> addUnlocked addunlockedmatcher
(MatchingFile (FileInfo file file))
let cfg = LockDownConfig let cfg = LockDownConfig
{ lockingFile = lockingfile { lockingFile = lockingfile
, hardlinkFileTmpDir = Just tmpdir , hardlinkFileTmpDir = Just tmpdir

View file

@ -94,16 +94,16 @@ parseDownloadOptions withfileoption = DownloadOptions
seek :: AddUrlOptions -> CommandSeek seek :: AddUrlOptions -> CommandSeek
seek o = startConcurrency commandStages $ do seek o = startConcurrency commandStages $ do
addunlockedmatcher <- addUnlockedMatcher
let go (o', u) = do
r <- Remote.claimingUrl u
if Remote.uuid r == webUUID || rawOption (downloadOptions o')
then void $ commandAction $ startWeb addunlockedmatcher o' u
else checkUrl addunlockedmatcher r o' u
forM_ (addUrls o) (\u -> go (o, u)) forM_ (addUrls o) (\u -> go (o, u))
case batchOption o of case batchOption o of
Batch fmt -> batchInput fmt (parseBatchInput o) go Batch fmt -> batchInput fmt (parseBatchInput o) go
NoBatch -> noop NoBatch -> noop
where
go (o', u) = do
r <- Remote.claimingUrl u
if Remote.uuid r == webUUID || rawOption (downloadOptions o')
then void $ commandAction $ startWeb o' u
else checkUrl r o' u
parseBatchInput :: AddUrlOptions -> String -> Either String (AddUrlOptions, URLString) parseBatchInput :: AddUrlOptions -> String -> Either String (AddUrlOptions, URLString)
parseBatchInput o s parseBatchInput o s
@ -114,8 +114,8 @@ parseBatchInput o s
else Right (o { downloadOptions = (downloadOptions o) { fileOption = Just f } }, u) else Right (o { downloadOptions = (downloadOptions o) { fileOption = Just f } }, u)
| otherwise = Right (o, s) | otherwise = Right (o, s)
checkUrl :: Remote -> AddUrlOptions -> URLString -> Annex () checkUrl :: AddUnlockedMatcher -> Remote -> AddUrlOptions -> URLString -> Annex ()
checkUrl r o u = do checkUrl addunlockedmatcher r o u = do
pathmax <- liftIO $ fileNameLengthLimit "." pathmax <- liftIO $ fileNameLengthLimit "."
let deffile = fromMaybe (urlString2file u (pathdepthOption o) pathmax) (fileOption (downloadOptions o)) let deffile = fromMaybe (urlString2file u (pathdepthOption o) pathmax) (fileOption (downloadOptions o))
go deffile =<< maybe go deffile =<< maybe
@ -129,49 +129,49 @@ checkUrl r o u = do
next $ return False next $ return False
go deffile (Right (UrlContents sz mf)) = do go deffile (Right (UrlContents sz mf)) = do
let f = adjustFile o (fromMaybe (maybe deffile fromSafeFilePath mf) (fileOption (downloadOptions o))) let f = adjustFile o (fromMaybe (maybe deffile fromSafeFilePath mf) (fileOption (downloadOptions o)))
void $ commandAction $ startRemote r o f u sz void $ commandAction $ startRemote addunlockedmatcher r o f u sz
go deffile (Right (UrlMulti l)) = case fileOption (downloadOptions o) of go deffile (Right (UrlMulti l)) = case fileOption (downloadOptions o) of
Nothing -> Nothing ->
forM_ l $ \(u', sz, f) -> do forM_ l $ \(u', sz, f) -> do
let f' = adjustFile o (deffile </> fromSafeFilePath f) let f' = adjustFile o (deffile </> fromSafeFilePath f)
void $ commandAction $ startRemote r o f' u' sz void $ commandAction $ startRemote addunlockedmatcher r o f' u' sz
Just f -> case l of Just f -> case l of
[] -> noop [] -> noop
((u',sz,_):[]) -> do ((u',sz,_):[]) -> do
let f' = adjustFile o f let f' = adjustFile o f
void $ commandAction $ startRemote r o f' u' sz void $ commandAction $ startRemote addunlockedmatcher r o f' u' sz
_ -> giveup $ unwords _ -> giveup $ unwords
[ "That url contains multiple files according to the" [ "That url contains multiple files according to the"
, Remote.name r , Remote.name r
, " remote; cannot add it to a single file." , " remote; cannot add it to a single file."
] ]
startRemote :: Remote -> AddUrlOptions -> FilePath -> URLString -> Maybe Integer -> CommandStart startRemote :: AddUnlockedMatcher -> Remote -> AddUrlOptions -> FilePath -> URLString -> Maybe Integer -> CommandStart
startRemote r o file uri sz = do startRemote addunlockedmatcher r o file uri sz = do
pathmax <- liftIO $ fileNameLengthLimit "." pathmax <- liftIO $ fileNameLengthLimit "."
let file' = joinPath $ map (truncateFilePath pathmax) $ splitDirectories file let file' = joinPath $ map (truncateFilePath pathmax) $ splitDirectories file
startingAddUrl uri o $ do startingAddUrl uri o $ do
showNote $ "from " ++ Remote.name r showNote $ "from " ++ Remote.name r
showDestinationFile file' showDestinationFile file'
performRemote r o uri file' sz performRemote addunlockedmatcher r o uri file' sz
performRemote :: Remote -> AddUrlOptions -> URLString -> FilePath -> Maybe Integer -> CommandPerform performRemote :: AddUnlockedMatcher -> Remote -> AddUrlOptions -> URLString -> FilePath -> Maybe Integer -> CommandPerform
performRemote r o uri file sz = ifAnnexed (toRawFilePath file) adduri geturi performRemote addunlockedmatcher r o uri file sz = ifAnnexed (toRawFilePath file) adduri geturi
where where
loguri = setDownloader uri OtherDownloader loguri = setDownloader uri OtherDownloader
adduri = addUrlChecked o loguri file (Remote.uuid r) checkexistssize adduri = addUrlChecked o loguri file (Remote.uuid r) checkexistssize
checkexistssize key = return $ case sz of checkexistssize key = return $ case sz of
Nothing -> (True, True, loguri) Nothing -> (True, True, loguri)
Just n -> (True, n == fromMaybe n (fromKey keySize key), loguri) Just n -> (True, n == fromMaybe n (fromKey keySize key), loguri)
geturi = next $ isJust <$> downloadRemoteFile r (downloadOptions o) uri file sz geturi = next $ isJust <$> downloadRemoteFile addunlockedmatcher r (downloadOptions o) uri file sz
downloadRemoteFile :: Remote -> DownloadOptions -> URLString -> FilePath -> Maybe Integer -> Annex (Maybe Key) downloadRemoteFile :: AddUnlockedMatcher -> Remote -> DownloadOptions -> URLString -> FilePath -> Maybe Integer -> Annex (Maybe Key)
downloadRemoteFile r o uri file sz = checkCanAdd file $ do downloadRemoteFile addunlockedmatcher r o uri file sz = checkCanAdd file $ do
let urlkey = Backend.URL.fromUrl uri sz let urlkey = Backend.URL.fromUrl uri sz
liftIO $ createDirectoryIfMissing True (parentDir file) liftIO $ createDirectoryIfMissing True (parentDir file)
ifM (Annex.getState Annex.fast <||> pure (relaxedOption o)) ifM (Annex.getState Annex.fast <||> pure (relaxedOption o))
( do ( do
addWorkTree (Remote.uuid r) loguri file urlkey Nothing addWorkTree addunlockedmatcher (Remote.uuid r) loguri file urlkey Nothing
return (Just urlkey) return (Just urlkey)
, do , do
-- Set temporary url for the urlkey -- Set temporary url for the urlkey
@ -181,15 +181,15 @@ downloadRemoteFile r o uri file sz = checkCanAdd file $ do
let downloader = \dest p -> fst let downloader = \dest p -> fst
<$> Remote.retrieveKeyFile r urlkey <$> Remote.retrieveKeyFile r urlkey
(AssociatedFile (Just (toRawFilePath file))) dest p (AssociatedFile (Just (toRawFilePath file))) dest p
ret <- downloadWith downloader urlkey (Remote.uuid r) loguri file ret <- downloadWith addunlockedmatcher downloader urlkey (Remote.uuid r) loguri file
removeTempUrl urlkey removeTempUrl urlkey
return ret return ret
) )
where where
loguri = setDownloader uri OtherDownloader loguri = setDownloader uri OtherDownloader
startWeb :: AddUrlOptions -> URLString -> CommandStart startWeb :: AddUnlockedMatcher -> AddUrlOptions -> URLString -> CommandStart
startWeb o urlstring = go $ fromMaybe bad $ parseURI urlstring startWeb addunlockedmatcher o urlstring = go $ fromMaybe bad $ parseURI urlstring
where where
bad = fromMaybe (giveup $ "bad url " ++ urlstring) $ bad = fromMaybe (giveup $ "bad url " ++ urlstring) $
Url.parseURIRelaxed $ urlstring Url.parseURIRelaxed $ urlstring
@ -209,12 +209,12 @@ startWeb o urlstring = go $ fromMaybe bad $ parseURI urlstring
( pure $ url2file url (pathdepthOption o) pathmax ( pure $ url2file url (pathdepthOption o) pathmax
, pure f , pure f
) )
performWeb o urlstring file urlinfo performWeb addunlockedmatcher o urlstring file urlinfo
performWeb :: AddUrlOptions -> URLString -> FilePath -> Url.UrlInfo -> CommandPerform performWeb :: AddUnlockedMatcher -> AddUrlOptions -> URLString -> FilePath -> Url.UrlInfo -> CommandPerform
performWeb o url file urlinfo = ifAnnexed (toRawFilePath file) addurl geturl performWeb addunlockedmatcher o url file urlinfo = ifAnnexed (toRawFilePath file) addurl geturl
where where
geturl = next $ isJust <$> addUrlFile (downloadOptions o) url urlinfo file geturl = next $ isJust <$> addUrlFile addunlockedmatcher (downloadOptions o) url urlinfo file
addurl = addUrlChecked o url file webUUID $ \k -> addurl = addUrlChecked o url file webUUID $ \k ->
ifM (pure (not (rawOption (downloadOptions o))) <&&> youtubeDlSupported url) ifM (pure (not (rawOption (downloadOptions o))) <&&> youtubeDlSupported url)
( return (True, True, setDownloader url YoutubeDownloader) ( return (True, True, setDownloader url YoutubeDownloader)
@ -249,15 +249,15 @@ addUrlChecked o url file u checkexistssize key =
- different file, based on the title of the media. Unless the user - different file, based on the title of the media. Unless the user
- specified fileOption, which then forces using the FilePath. - specified fileOption, which then forces using the FilePath.
-} -}
addUrlFile :: DownloadOptions -> URLString -> Url.UrlInfo -> FilePath -> Annex (Maybe Key) addUrlFile :: AddUnlockedMatcher -> DownloadOptions -> URLString -> Url.UrlInfo -> FilePath -> Annex (Maybe Key)
addUrlFile o url urlinfo file = addUrlFile addunlockedmatcher o url urlinfo file =
ifM (Annex.getState Annex.fast <||> pure (relaxedOption o)) ifM (Annex.getState Annex.fast <||> pure (relaxedOption o))
( nodownloadWeb o url urlinfo file ( nodownloadWeb addunlockedmatcher o url urlinfo file
, downloadWeb o url urlinfo file , downloadWeb addunlockedmatcher o url urlinfo file
) )
downloadWeb :: DownloadOptions -> URLString -> Url.UrlInfo -> FilePath -> Annex (Maybe Key) downloadWeb :: AddUnlockedMatcher -> DownloadOptions -> URLString -> Url.UrlInfo -> FilePath -> Annex (Maybe Key)
downloadWeb o url urlinfo file = downloadWeb addunlockedmatcher o url urlinfo file =
go =<< downloadWith' downloader urlkey webUUID url (AssociatedFile (Just (toRawFilePath file))) go =<< downloadWith' downloader urlkey webUUID url (AssociatedFile (Just (toRawFilePath file)))
where where
urlkey = addSizeUrlKey urlinfo $ Backend.URL.fromUrl url Nothing urlkey = addSizeUrlKey urlinfo $ Backend.URL.fromUrl url Nothing
@ -272,7 +272,7 @@ downloadWeb o url urlinfo file =
normalfinish tmp = checkCanAdd file $ do normalfinish tmp = checkCanAdd file $ do
showDestinationFile file showDestinationFile file
liftIO $ createDirectoryIfMissing True (parentDir file) liftIO $ createDirectoryIfMissing True (parentDir file)
finishDownloadWith tmp webUUID url file finishDownloadWith addunlockedmatcher tmp webUUID url file
tryyoutubedl tmp tryyoutubedl tmp
-- Ask youtube-dl what filename it will download -- Ask youtube-dl what filename it will download
-- first, and check if that is already an annexed file, -- first, and check if that is already an annexed file,
@ -298,7 +298,7 @@ downloadWeb o url urlinfo file =
cleanuptmp cleanuptmp
checkCanAdd dest $ do checkCanAdd dest $ do
showDestinationFile dest showDestinationFile dest
addWorkTree webUUID mediaurl dest mediakey (Just mediafile) addWorkTree addunlockedmatcher webUUID mediaurl dest mediakey (Just mediafile)
return $ Just mediakey return $ Just mediakey
Right Nothing -> normalfinish tmp Right Nothing -> normalfinish tmp
Left msg -> do Left msg -> do
@ -341,13 +341,13 @@ showDestinationFile file = do
- Downloads the url, sets up the worktree file, and returns the - Downloads the url, sets up the worktree file, and returns the
- real key. - real key.
-} -}
downloadWith :: (FilePath -> MeterUpdate -> Annex Bool) -> Key -> UUID -> URLString -> FilePath -> Annex (Maybe Key) downloadWith :: AddUnlockedMatcher -> (FilePath -> MeterUpdate -> Annex Bool) -> Key -> UUID -> URLString -> FilePath -> Annex (Maybe Key)
downloadWith downloader dummykey u url file = downloadWith addunlockedmatcher downloader dummykey u url file =
go =<< downloadWith' downloader dummykey u url afile go =<< downloadWith' downloader dummykey u url afile
where where
afile = AssociatedFile (Just (toRawFilePath file)) afile = AssociatedFile (Just (toRawFilePath file))
go Nothing = return Nothing go Nothing = return Nothing
go (Just tmp) = finishDownloadWith tmp u url file go (Just tmp) = finishDownloadWith addunlockedmatcher tmp u url file
{- Like downloadWith, but leaves the dummy key content in {- Like downloadWith, but leaves the dummy key content in
- the returned location. -} - the returned location. -}
@ -363,8 +363,8 @@ downloadWith' downloader dummykey u url afile =
then return (Just tmp) then return (Just tmp)
else return Nothing else return Nothing
finishDownloadWith :: FilePath -> UUID -> URLString -> FilePath -> Annex (Maybe Key) finishDownloadWith :: AddUnlockedMatcher -> FilePath -> UUID -> URLString -> FilePath -> Annex (Maybe Key)
finishDownloadWith tmp u url file = do finishDownloadWith addunlockedmatcher tmp u url file = do
backend <- chooseBackend file backend <- chooseBackend file
let source = KeySource let source = KeySource
{ keyFilename = file { keyFilename = file
@ -374,7 +374,7 @@ finishDownloadWith tmp u url file = do
genKey source nullMeterUpdate backend >>= \case genKey source nullMeterUpdate backend >>= \case
Nothing -> return Nothing Nothing -> return Nothing
Just (key, _) -> do Just (key, _) -> do
addWorkTree u url file key (Just tmp) addWorkTree addunlockedmatcher u url file key (Just tmp)
return (Just key) return (Just key)
{- Adds the url size to the Key. -} {- Adds the url size to the Key. -}
@ -384,8 +384,8 @@ addSizeUrlKey urlinfo key = alterKey key $ \d -> d
} }
{- Adds worktree file to the repository. -} {- Adds worktree file to the repository. -}
addWorkTree :: UUID -> URLString -> FilePath -> Key -> Maybe FilePath -> Annex () addWorkTree :: AddUnlockedMatcher -> UUID -> URLString -> FilePath -> Key -> Maybe FilePath -> Annex ()
addWorkTree u url file key mtmp = case mtmp of addWorkTree addunlockedmatcher u url file key mtmp = case mtmp of
Nothing -> go Nothing -> go
Just tmp -> do Just tmp -> do
-- Move to final location for large file check. -- Move to final location for large file check.
@ -407,15 +407,15 @@ addWorkTree u url file key mtmp = case mtmp of
maybeShowJSON $ JSONChunk [("key", serializeKey key)] maybeShowJSON $ JSONChunk [("key", serializeKey key)]
setUrlPresent key url setUrlPresent key url
logChange key u InfoPresent logChange key u InfoPresent
ifM (addAnnexedFile file key mtmp) ifM (addAnnexedFile addunlockedmatcher file key mtmp)
( do ( do
when (isJust mtmp) $ when (isJust mtmp) $
logStatus key InfoPresent logStatus key InfoPresent
, maybe noop (\tmp -> pruneTmpWorkDirBefore tmp (liftIO . nukeFile)) mtmp , maybe noop (\tmp -> pruneTmpWorkDirBefore tmp (liftIO . nukeFile)) mtmp
) )
nodownloadWeb :: DownloadOptions -> URLString -> Url.UrlInfo -> FilePath -> Annex (Maybe Key) nodownloadWeb :: AddUnlockedMatcher -> DownloadOptions -> URLString -> Url.UrlInfo -> FilePath -> Annex (Maybe Key)
nodownloadWeb o url urlinfo file nodownloadWeb addunlockedmatcher o url urlinfo file
| Url.urlExists urlinfo = if rawOption o | Url.urlExists urlinfo = if rawOption o
then nomedia then nomedia
else either (const nomedia) usemedia else either (const nomedia) usemedia
@ -426,20 +426,20 @@ nodownloadWeb o url urlinfo file
where where
nomedia = do nomedia = do
let key = Backend.URL.fromUrl url (Url.urlSize urlinfo) let key = Backend.URL.fromUrl url (Url.urlSize urlinfo)
nodownloadWeb' url key file nodownloadWeb' addunlockedmatcher url key file
usemedia mediafile = do usemedia mediafile = do
let dest = if isJust (fileOption o) let dest = if isJust (fileOption o)
then file then file
else takeFileName mediafile else takeFileName mediafile
let mediaurl = setDownloader url YoutubeDownloader let mediaurl = setDownloader url YoutubeDownloader
let mediakey = Backend.URL.fromUrl mediaurl Nothing let mediakey = Backend.URL.fromUrl mediaurl Nothing
nodownloadWeb' mediaurl mediakey dest nodownloadWeb' addunlockedmatcher mediaurl mediakey dest
nodownloadWeb' :: URLString -> Key -> FilePath -> Annex (Maybe Key) nodownloadWeb' :: AddUnlockedMatcher -> URLString -> Key -> FilePath -> Annex (Maybe Key)
nodownloadWeb' url key file = checkCanAdd file $ do nodownloadWeb' addunlockedmatcher url key file = checkCanAdd file $ do
showDestinationFile file showDestinationFile file
liftIO $ createDirectoryIfMissing True (parentDir file) liftIO $ createDirectoryIfMissing True (parentDir file)
addWorkTree webUUID url file key Nothing addWorkTree addunlockedmatcher webUUID url file key Nothing
return (Just key) return (Just key)
url2file :: URI -> Maybe Int -> Int -> FilePath url2file :: URI -> Maybe Int -> Int -> FilePath

View file

@ -27,7 +27,6 @@ import Annex.Content
import Annex.Transfer import Annex.Transfer
import Annex.CatFile import Annex.CatFile
import Annex.FileMatcher import Annex.FileMatcher
import Types.FileMatcher
import Annex.RemoteTrackingBranch import Annex.RemoteTrackingBranch
import Logs.Location import Logs.Location
import Logs.Export import Logs.Export

View file

@ -41,7 +41,7 @@ start = do
stop stop
guardTest :: Annex () guardTest :: Annex ()
guardTest = unlessM (fromMaybe False . Git.Config.isTrue' <$> getConfig key mempty) $ guardTest = unlessM (fromMaybe False . Git.Config.isTrueFalse' <$> getConfig key mempty) $
giveup $ unlines giveup $ unlines
[ "Running fuzz tests *writes* to and *deletes* files in" [ "Running fuzz tests *writes* to and *deletes* files in"
, "this repository, and pushes those changes to other" , "this repository, and pushes those changes to other"

View file

@ -102,7 +102,8 @@ seek o@(LocalImportOptions {}) = startConcurrency commandStages $ do
unless (null inrepops) $ do unless (null inrepops) $ do
giveup $ "cannot import files from inside the working tree (use git annex add instead): " ++ unwords inrepops giveup $ "cannot import files from inside the working tree (use git annex add instead): " ++ unwords inrepops
largematcher <- largeFilesMatcher largematcher <- largeFilesMatcher
(commandAction . startLocal largematcher (duplicateMode o)) addunlockedmatcher <- addUnlockedMatcher
(commandAction . startLocal addunlockedmatcher largematcher (duplicateMode o))
`withPathContents` importFiles o `withPathContents` importFiles o
seek o@(RemoteImportOptions {}) = startConcurrency commandStages $ do seek o@(RemoteImportOptions {}) = startConcurrency commandStages $ do
r <- getParsed (importFromRemote o) r <- getParsed (importFromRemote o)
@ -114,8 +115,8 @@ seek o@(RemoteImportOptions {}) = startConcurrency commandStages $ do
(importToSubDir o) (importToSubDir o)
seekRemote r (importToBranch o) subdir seekRemote r (importToBranch o) subdir
startLocal :: GetFileMatcher -> DuplicateMode -> (FilePath, FilePath) -> CommandStart startLocal :: AddUnlockedMatcher -> GetFileMatcher -> DuplicateMode -> (FilePath, FilePath) -> CommandStart
startLocal largematcher mode (srcfile, destfile) = startLocal addunlockedmatcher largematcher mode (srcfile, destfile) =
ifM (liftIO $ isRegularFile <$> getSymbolicLinkStatus srcfile) ifM (liftIO $ isRegularFile <$> getSymbolicLinkStatus srcfile)
( starting "import" (ActionItemWorkTreeFile (toRawFilePath destfile)) ( starting "import" (ActionItemWorkTreeFile (toRawFilePath destfile))
pickaction pickaction
@ -208,7 +209,11 @@ startLocal largematcher mode (srcfile, destfile) =
warning $ "not overwriting existing " ++ destfile ++ " " ++ why warning $ "not overwriting existing " ++ destfile ++ " " ++ why
stop stop
lockdown a = do lockdown a = do
lockingfile <- not <$> addUnlocked let mi = MatchingFile $ FileInfo
{ currFile = toRawFilePath srcfile
, matchFile = toRawFilePath destfile
}
lockingfile <- not <$> addUnlocked addunlockedmatcher mi
-- Minimal lock down with no hard linking so nothing -- Minimal lock down with no hard linking so nothing
-- has to be done to clean up from it. -- has to be done to clean up from it.
let cfg = LockDownConfig let cfg = LockDownConfig

View file

@ -38,6 +38,7 @@ import Annex.YoutubeDl
import Types.MetaData import Types.MetaData
import Logs.MetaData import Logs.MetaData
import Annex.MetaData import Annex.MetaData
import Annex.FileMatcher
import Command.AddUrl (addWorkTree) import Command.AddUrl (addWorkTree)
cmd :: Command cmd :: Command
@ -62,11 +63,12 @@ optParser desc = ImportFeedOptions
seek :: ImportFeedOptions -> CommandSeek seek :: ImportFeedOptions -> CommandSeek
seek o = do seek o = do
addunlockedmatcher <- addUnlockedMatcher
cache <- getCache (templateOption o) cache <- getCache (templateOption o)
forM_ (feedUrls o) (getFeed o cache) forM_ (feedUrls o) (getFeed addunlockedmatcher o cache)
getFeed :: ImportFeedOptions -> Cache -> URLString -> CommandSeek getFeed :: AddUnlockedMatcher -> ImportFeedOptions -> Cache -> URLString -> CommandSeek
getFeed opts cache url = do getFeed addunlockedmatcher opts cache url = do
showStart' "importfeed" (Just url) showStart' "importfeed" (Just url)
downloadFeed url >>= \case downloadFeed url >>= \case
Nothing -> showEndResult =<< feedProblem url Nothing -> showEndResult =<< feedProblem url
@ -77,7 +79,7 @@ getFeed opts cache url = do
[] -> debugfeedcontent feedcontent "bad feed content; no enclosures to download" [] -> debugfeedcontent feedcontent "bad feed content; no enclosures to download"
l -> do l -> do
showEndOk showEndOk
ifM (and <$> mapM (performDownload opts cache) l) ifM (and <$> mapM (performDownload addunlockedmatcher opts cache) l)
( clearFeedProblem url ( clearFeedProblem url
, void $ feedProblem url , void $ feedProblem url
"problem downloading some item(s) from feed" "problem downloading some item(s) from feed"
@ -153,8 +155,8 @@ downloadFeed url
, return Nothing , return Nothing
) )
performDownload :: ImportFeedOptions -> Cache -> ToDownload -> Annex Bool performDownload :: AddUnlockedMatcher -> ImportFeedOptions -> Cache -> ToDownload -> Annex Bool
performDownload opts cache todownload = case location todownload of performDownload addunlockedmatcher opts cache todownload = case location todownload of
Enclosure url -> checkknown url $ Enclosure url -> checkknown url $
rundownload url (takeWhile (/= '?') $ takeExtension url) $ \f -> do rundownload url (takeWhile (/= '?') $ takeExtension url) $ \f -> do
r <- Remote.claimingUrl url r <- Remote.claimingUrl url
@ -171,7 +173,7 @@ performDownload opts cache todownload = case location todownload of
-- don't use youtube-dl -- don't use youtube-dl
, rawOption = True , rawOption = True
} }
maybeToList <$> addUrlFile dlopts url urlinfo f maybeToList <$> addUrlFile addunlockedmatcher dlopts url urlinfo f
else do else do
res <- tryNonAsync $ maybe res <- tryNonAsync $ maybe
(error $ "unable to checkUrl of " ++ Remote.name r) (error $ "unable to checkUrl of " ++ Remote.name r)
@ -181,10 +183,10 @@ performDownload opts cache todownload = case location todownload of
Left _ -> return [] Left _ -> return []
Right (UrlContents sz _) -> Right (UrlContents sz _) ->
maybeToList <$> maybeToList <$>
downloadRemoteFile r (downloadOptions opts) url f sz downloadRemoteFile addunlockedmatcher r (downloadOptions opts) url f sz
Right (UrlMulti l) -> do Right (UrlMulti l) -> do
kl <- forM l $ \(url', sz, subf) -> kl <- forM l $ \(url', sz, subf) ->
downloadRemoteFile r (downloadOptions opts) url' (f </> fromSafeFilePath subf) sz downloadRemoteFile addunlockedmatcher r (downloadOptions opts) url' (f </> fromSafeFilePath subf) sz
return $ if all isJust kl return $ if all isJust kl
then catMaybes kl then catMaybes kl
else [] else []
@ -273,7 +275,7 @@ performDownload opts cache todownload = case location todownload of
[] -> ".m" [] -> ".m"
s -> s s -> s
ok <- rundownload linkurl ext $ \f -> do ok <- rundownload linkurl ext $ \f -> do
addWorkTree webUUID mediaurl f mediakey (Just mediafile) addWorkTree addunlockedmatcher webUUID mediaurl f mediakey (Just mediafile)
return [mediakey] return [mediakey]
return (Just ok) return (Just ok)
-- youtude-dl didn't support it, so -- youtude-dl didn't support it, so
@ -285,16 +287,16 @@ performDownload opts cache todownload = case location todownload of
return Nothing return Nothing
return (fromMaybe False r) return (fromMaybe False r)
where where
downloadlink = performDownload opts cache todownload downloadlink = performDownload addunlockedmatcher opts cache todownload
{ location = Enclosure linkurl } { location = Enclosure linkurl }
addmediafast linkurl mediaurl mediakey = addmediafast linkurl mediaurl mediakey =
ifM (pure (not (rawOption (downloadOptions opts))) ifM (pure (not (rawOption (downloadOptions opts)))
<&&> youtubeDlSupported linkurl) <&&> youtubeDlSupported linkurl)
( rundownload linkurl ".m" $ \f -> do ( rundownload linkurl ".m" $ \f -> do
addWorkTree webUUID mediaurl f mediakey Nothing addWorkTree addunlockedmatcher webUUID mediaurl f mediakey Nothing
return [mediakey] return [mediakey]
, performDownload opts cache todownload , performDownload addunlockedmatcher opts cache todownload
{ location = Enclosure linkurl } { location = Enclosure linkurl }
) )

View file

@ -9,7 +9,6 @@ module Command.MatchExpression where
import Command import Command
import Annex.FileMatcher import Annex.FileMatcher
import Types.FileMatcher
import Utility.DataUnits import Utility.DataUnits
import Utility.Matcher import Utility.Matcher
import Annex.UUID import Annex.UUID
@ -75,7 +74,7 @@ optParser desc = MatchExpressionOptions
seek :: MatchExpressionOptions -> CommandSeek seek :: MatchExpressionOptions -> CommandSeek
seek o = do seek o = do
parser <- if largeFilesExpression o parser <- if largeFilesExpression o
then mkLargeFilesParser then mkMatchExpressionParser
else do else do
u <- getUUID u <- getUUID
pure $ preferredContentParser $ preferredContentTokens $ PCD pure $ preferredContentParser $ preferredContentTokens $ PCD

View file

@ -137,7 +137,7 @@ applyCommitModeForCommitTree :: CommitMode -> [CommandParam] -> Repo -> [Command
applyCommitModeForCommitTree commitmode ps r applyCommitModeForCommitTree commitmode ps r
| commitmode == ManualCommit = | commitmode == ManualCommit =
case Git.Config.getMaybe "commit.gpgsign" r of case Git.Config.getMaybe "commit.gpgsign" r of
Just s | Git.Config.isTrue' s == Just True -> Just s | Git.Config.isTrueFalse' s == Just True ->
Param "-S":ps Param "-S":ps
_ -> ps' _ -> ps'
| otherwise = ps' | otherwise = ps'

View file

@ -156,12 +156,12 @@ parse s
. map (\(k,v) -> (ConfigKey k, [ConfigValue (S.drop 1 v)])) . map (\(k,v) -> (ConfigKey k, [ConfigValue (S.drop 1 v)]))
. map (S.break (== c)) . map (S.break (== c))
{- Checks if a string from git config is a true value. -} {- Checks if a string from git config is a true/false value. -}
isTrue :: String -> Maybe Bool isTrueFalse :: String -> Maybe Bool
isTrue = isTrue' . ConfigValue . encodeBS' isTrueFalse = isTrueFalse' . ConfigValue . encodeBS'
isTrue' :: ConfigValue -> Maybe Bool isTrueFalse' :: ConfigValue -> Maybe Bool
isTrue' (ConfigValue s) isTrueFalse' (ConfigValue s)
| s' == "true" = Just True | s' == "true" = Just True
| s' == "false" = Just False | s' == "false" = Just False
| otherwise = Nothing | otherwise = Nothing
@ -177,7 +177,7 @@ boolConfig' True = "true"
boolConfig' False = "false" boolConfig' False = "false"
isBare :: Repo -> Bool isBare :: Repo -> Bool
isBare r = fromMaybe False $ isTrue' =<< getMaybe coreBare r isBare r = fromMaybe False $ isTrueFalse' =<< getMaybe coreBare r
coreBare :: ConfigKey coreBare :: ConfigKey
coreBare = "core.bare" coreBare = "core.bare"

View file

@ -42,7 +42,6 @@ import Types.Group
import Types.Remote (RemoteConfig) import Types.Remote (RemoteConfig)
import Logs.Group import Logs.Group
import Logs.Remote import Logs.Remote
import Types.FileMatcher
import Types.StandardGroups import Types.StandardGroups
import Limit import Limit

View file

@ -18,7 +18,7 @@ import Types.CleanupActions
import Types.UrlContents import Types.UrlContents
import qualified Git import qualified Git
import Config import Config
import Git.Config (isTrue, boolConfig) import Git.Config (isTrueFalse, boolConfig)
import Git.Env import Git.Env
import Remote.Helper.Special import Remote.Helper.Special
import Remote.Helper.ExportImport import Remote.Helper.ExportImport
@ -157,7 +157,7 @@ externalSetup _ mu _ c gc = do
(c', _encsetup) <- encryptionSetup c gc (c', _encsetup) <- encryptionSetup c gc
c'' <- case M.lookup "readonly" c of c'' <- case M.lookup "readonly" c of
Just v | isTrue v == Just True -> do Just v | isTrueFalse v == Just True -> do
setConfig (remoteConfig (fromJust (lookupName c)) "readonly") (boolConfig True) setConfig (remoteConfig (fromJust (lookupName c)) "readonly") (boolConfig True)
return c' return c'
_ -> do _ -> do

View file

@ -96,7 +96,7 @@ getDifferences :: Git.Repo -> Differences
getDifferences r = mkDifferences $ S.fromList $ getDifferences r = mkDifferences $ S.fromList $
mapMaybe getmaybe [minBound .. maxBound] mapMaybe getmaybe [minBound .. maxBound]
where where
getmaybe d = case Git.Config.isTrue' =<< Git.Config.getMaybe (differenceConfigKey d) r of getmaybe d = case Git.Config.isTrueFalse' =<< Git.Config.getMaybe (differenceConfigKey d) r of
Just True -> Just d Just True -> Just d
_ -> Nothing _ -> Nothing

View file

@ -12,7 +12,7 @@ import Utility.Split
import Types.Key import Types.Key
import Key import Key
import Data.Time.Clock import Data.Time.Clock
import Git.Config (isTrue, boolConfig) import Git.Config (isTrueFalse, boolConfig)
import Control.Applicative import Control.Applicative
import Prelude import Prelude
@ -71,7 +71,7 @@ toAutoUpgrade :: Maybe String -> AutoUpgrade
toAutoUpgrade Nothing = AskUpgrade toAutoUpgrade Nothing = AskUpgrade
toAutoUpgrade (Just s) toAutoUpgrade (Just s)
| s == "ask" = AskUpgrade | s == "ask" = AskUpgrade
| isTrue s == Just True = AutoUpgrade | isTrueFalse s == Just True = AutoUpgrade
| otherwise = NoAutoUpgrade | otherwise = NoAutoUpgrade
fromAutoUpgrade :: AutoUpgrade -> String fromAutoUpgrade :: AutoUpgrade -> String

View file

@ -102,7 +102,7 @@ data GitConfig = GitConfig
, annexVerify :: Bool , annexVerify :: Bool
, annexPidLock :: Bool , annexPidLock :: Bool
, annexPidLockTimeout :: Seconds , annexPidLockTimeout :: Seconds
, annexAddUnlocked :: Bool , annexAddUnlocked :: Configurable (Maybe String)
, annexSecureHashesOnly :: Bool , annexSecureHashesOnly :: Bool
, annexRetry :: Maybe Integer , annexRetry :: Maybe Integer
, annexRetryDelay :: Maybe Seconds , annexRetryDelay :: Maybe Seconds
@ -177,7 +177,8 @@ extractGitConfig configsource r = GitConfig
, annexPidLock = getbool (annex "pidlock") False , annexPidLock = getbool (annex "pidlock") False
, annexPidLockTimeout = Seconds $ fromMaybe 300 $ , annexPidLockTimeout = Seconds $ fromMaybe 300 $
getmayberead (annex "pidlocktimeout") getmayberead (annex "pidlocktimeout")
, annexAddUnlocked = getbool (annex "addunlocked") False , annexAddUnlocked = configurable Nothing $
fmap Just $ getmaybe (annex "addunlocked")
, annexSecureHashesOnly = getbool (annex "securehashesonly") False , annexSecureHashesOnly = getbool (annex "securehashesonly") False
, annexRetry = getmayberead (annex "retry") , annexRetry = getmayberead (annex "retry")
, annexRetryDelay = Seconds , annexRetryDelay = Seconds
@ -207,7 +208,7 @@ extractGitConfig configsource r = GitConfig
} }
where where
getbool k d = fromMaybe d $ getmaybebool k getbool k d = fromMaybe d $ getmaybebool k
getmaybebool k = Git.Config.isTrue' =<< getmaybe' k getmaybebool k = Git.Config.isTrueFalse' =<< getmaybe' k
getmayberead k = readish =<< getmaybe k getmayberead k = readish =<< getmaybe k
getmaybe = fmap fromConfigValue . getmaybe' getmaybe = fmap fromConfigValue . getmaybe'
getmaybe' k = Git.Config.getMaybe k r getmaybe' k = Git.Config.getMaybe k r
@ -231,6 +232,7 @@ mergeGitConfig gitconfig repoglobals = gitconfig
, annexSyncContent = merge annexSyncContent , annexSyncContent = merge annexSyncContent
, annexResolveMerge = merge annexResolveMerge , annexResolveMerge = merge annexResolveMerge
, annexLargeFiles = merge annexLargeFiles , annexLargeFiles = merge annexLargeFiles
, annexAddUnlocked = merge annexAddUnlocked
} }
where where
merge f = case f gitconfig of merge f = case f gitconfig of
@ -354,7 +356,7 @@ extractRemoteGitConfig r remotename = do
} }
where where
getbool k d = fromMaybe d $ getmaybebool k getbool k d = fromMaybe d $ getmaybebool k
getmaybebool k = Git.Config.isTrue' =<< getmaybe' k getmaybebool k = Git.Config.isTrueFalse' =<< getmaybe' k
getmayberead k = readish =<< getmaybe k getmayberead k = readish =<< getmaybe k
getmaybe = fmap fromConfigValue . getmaybe' getmaybe = fmap fromConfigValue . getmaybe'
getmaybe' k = mplus (Git.Config.getMaybe (key k) r) getmaybe' k = mplus (Git.Config.getMaybe (key k) r)

View file

@ -31,11 +31,25 @@ These settings can be overridden on a per-repository basis using
Used to configure which files are large enough to be added to the annex. Used to configure which files are large enough to be added to the annex.
It is an expression that matches the large files, eg It is an expression that matches the large files, eg
"include=*.mp3 or largerthan(500kb)" "include=*.mp3 or largerthan(500kb)".
See [[git-annex-matching-expression]](1) for details on the syntax.
This sets a default, which can be overridden by annex.largefiles This sets a default, which can be overridden by annex.largefiles
attributes in `.gitattributes` files, or by `git config`. attributes in `.gitattributes` files, or by `git config`.
* `annex.addunlocked`
Commands like `git-annex add` default to adding files to the repository
in locked form. This can make them add the files in unlocked form,
the same as if [[git-annex-unlock]](1) were run on the files.
This can be set to "true" to add everything unlocked, or it can be a more
complicated expression that matches files by name, size, or content. See
[[git-annex-matching-expression]](1) for details.
This sets a default, which can be overridden by annex.addunlocked
in `git config`.
* `annex.autocommit` * `annex.autocommit`
Set to false to prevent the `git-annex assistant` and `git-annex sync` Set to false to prevent the `git-annex assistant` and `git-annex sync`

View file

@ -59,6 +59,8 @@ For example, this will exit 0:
[[git-annex-preferred-content]](1) [[git-annex-preferred-content]](1)
[[git-annex-matching-expression]](1)
# AUTHOR # AUTHOR
Joey Hess <id@joeyh.name> Joey Hess <id@joeyh.name>

View file

@ -0,0 +1,87 @@
# NAME
git-annex-matching-expression - specifying a set of files
# DESCRIPTION
The annex.largefiles and annex.addunlocked configurations both use
expressions that match some files in the working tree.
# SYNTAX
The format of these expressions is similar to
[[git-annex-preferred-content]](1) expressions.
For example:
largerthan=100kb and not (include=*.c or include=*.h)
This matches large files, but excludes C source files.
The following terms can be used:
* `include=glob` / `exclude=glob`
Specify files to include or exclude.
The glob can contain `*` and `?` to match arbitrary characters.
* `smallerthan=size` / `largerthan=size`
Matches only files smaller than, or larger than the specified size.
The size can be specified with any commonly used units, for example,
"0.5 gb" or "100 KiloBytes"
* `mimetype=glob`
Looks up the MIME type of a file, and checks if the glob matches it.
For example, `"mimetype=text/*"` will match many varieties of text files,
including "text/plain", but also "text/x-shellscript", "text/x-makefile",
etc.
The MIME types are the same that are displayed by running `file --mime-type`
This is only available to use when git-annex was built with the
MagicMime build flag.
* `mimeencoding=glob`
Looks up the MIME encoding of a file, and checks if the glob matches it.
For example, `"mimeencoding=binary"` will match many kinds of binary
files.
The MIME encodings are the same that are displayed by running `file --mime-encoding`
This is only available to use when git-annex was built with the
MagicMime build flag.
* `anything`
Matches any file.
* `nothing`
Matches no files. (Same as "not anything")
* `not expression`
Inverts what the expression matches.
* `and` / `or` / `( expression )`
These can be used to build up more complicated expressions.
# SEE ALSO
[[git-annex]](1)
# AUTHOR
Joey Hess <id@joeyh.name>
<http://git-annex.branchable.com/>
Warning: Automatically converted into a man page by mdwn2man. Edit with care.

View file

@ -892,6 +892,7 @@ Like other git commands, git-annex is configured via `.git/config`.
Used to configure which files are large enough to be added to the annex. Used to configure which files are large enough to be added to the annex.
It is an expression that matches the large files, eg It is an expression that matches the large files, eg
"include=*.mp3 or largerthan(500kb)" "include=*.mp3 or largerthan(500kb)"
See [[git-annex-matching-expression]](1) for details on the syntax.
Overrides any annex.largefiles attributes in `.gitattributes` files. Overrides any annex.largefiles attributes in `.gitattributes` files.
@ -909,9 +910,6 @@ Like other git commands, git-annex is configured via `.git/config`.
`git annex import`, `git annex addurl`, `git annex importfeed` `git annex import`, `git annex addurl`, `git annex importfeed`
and the assistant. and the assistant.
See <https://git-annex.branchable.com/tips/largefiles> for syntax
documentation and more.
* `annex.gitaddtoannex` * `annex.gitaddtoannex`
Setting this to false will prevent `git add` from adding Setting this to false will prevent `git add` from adding
@ -925,13 +923,20 @@ Like other git commands, git-annex is configured via `.git/config`.
* `annex.addunlocked` * `annex.addunlocked`
Set to true to make commands like `git-annex add` that add files to the Commands like `git-annex add` default to adding files to the repository
repository add them in unlocked form. The default is for these commands in locked form. This can make them add the files in unlocked form,
to add files in locked form. the same as if [[git-annex-unlock]](1) were run on the files.
This can be set to "true" to add everything unlocked, or it can be a more
complicated expression that matches files by name, size, or content. See
[[git-annex-matching-expression]](1) for details.
To configure a default annex.addunlocked for all clones of the repository,
this can be set in [[git-annex-config]](1).
(Using `git add` always adds files in unlocked form and it is not (Using `git add` always adds files in unlocked form and it is not
affected by this setting.) affected by this setting.)
When a repository has core.symlinks set to false, or has an adjusted When a repository has core.symlinks set to false, or has an adjusted
unlocked branch checked out, this setting is ignored, and files are unlocked branch checked out, this setting is ignored, and files are
always added to the repository in unlocked form. always added to the repository in unlocked form.
@ -1702,9 +1707,8 @@ There is a annex.largefiles attribute, which is used to configure which
files are large enough to be added to the annex. Since attributes cannot files are large enough to be added to the annex. Since attributes cannot
contain spaces, it is difficult to use for more complex annex.largefiles contain spaces, it is difficult to use for more complex annex.largefiles
settings. Setting annex.largefiles in [[git-annex-config]](1) is an easier settings. Setting annex.largefiles in [[git-annex-config]](1) is an easier
way to configure it across all clones of the repository. See way to configure it across all clones of the repository.
<https://git-annex.branchable.com/tips/largefiles> for examples and more See [[git-annex-matching-expression]](1) for details on the syntax.
documentation.
The numcopies setting can also be configured on a per-file-type basis via The numcopies setting can also be configured on a per-file-type basis via
the `annex.numcopies` attribute in `.gitattributes` files. This overrides the `annex.numcopies` attribute in `.gitattributes` files. This overrides

View file

@ -59,65 +59,9 @@ Or in all clones:
## syntax ## syntax
The value of annex.largefiles is similar to a See [[git-annex-matching-expression]] for details about the syntax.
[[preferred content expression|git-annex-preferred-content]].
The following terms can be used in annex.largefiles:
* `include=glob` / `exclude=glob` ## gitattributes format
Specify files to include or exclude.
The glob can contain `*` and `?` to match arbitrary characters.
* `smallerthan=size` / `largerthan=size`
Matches only files smaller than, or larger than the specified size.
The size can be specified with any commonly used units, for example,
"0.5 gb" or "100 KiloBytes"
* `mimetype=glob`
Looks up the MIME type of a file, and checks if the glob matches it.
For example, `"mimetype=text/*"` will match many varieties of text files,
including "text/plain", but also "text/x-shellscript", "text/x-makefile",
etc.
The MIME types are the same that are displayed by running `file --mime-type`
This is only available to use when git-annex was built with the
MagicMime build flag.
* `mimeencoding=glob`
Looks up the MIME encoding of a file, and checks if the glob matches it.
For example, `"mimeencoding=binary"` will match many kinds of binary
files.
The MIME encodings are the same that are displayed by running `file --mime-encoding`
This is only available to use when git-annex was built with the
MagicMime build flag.
* `anything`
Matches any file.
* `nothing`
Matches no files. (Same as "not anything")
* `not expression`
Inverts what the expression matches.
* `and` / `or` / `( expression )`
These can be used to build up more complicated expressions.
## gitattributes syntax
Here's that example `.gitattributes` again: Here's that example `.gitattributes` again:

View file

@ -3,3 +3,5 @@ Can the `annex.addunlocked` be extended to have the same syntax as `annex.largef
Basically, I want a reliable way to prevent inadvertently adding files as annexed unlocked files. Basically, I want a reliable way to prevent inadvertently adding files as annexed unlocked files.
Related: [[forum/lets_discuss_git_add_behavior]] Related: [[forum/lets_discuss_git_add_behavior]]
> [[done]] --[[Joey]]

View file

@ -0,0 +1,11 @@
[[!comment format=mdwn
username="joey"
subject="""comment 4"""
date="2019-12-20T19:45:21Z"
content="""
Made annex.addunlocked support expressions like annex.largefiles.
And both of them can be set globally with `git annex config`. I did not
make annex.addunlocked be settable by git attribute, because my sense is
that `git annex config` covers that use case, or mostly so.
"""]]