git-annex/Command/RegisterUrl.hs
Joey Hess 81d402216d cache the serialization of a Key
This will speed up the common case where a Key is deserialized from
disk, but is then serialized to build eg, the path to the annex object.

Previously attempted in 4536c93bb2
and reverted in 96aba8eff7.
The problems mentioned in the latter commit are addressed now:

Read/Show of KeyData is backwards-compatible with Read/Show of Key from before
this change, so Types.Distribution will keep working.

The Eq instance is fixed.

Also, Key has smart constructors, avoiding needing to remember to update
the cached serialization.

Used git-annex benchmark:
  find is 7% faster
  whereis is 3% faster
  get when all files are already present is 5% faster
Generally, the benchmarks are running 0.1 seconds faster per 2000 files,
on a ram disk in my laptop.
2019-11-22 17:49:16 -04:00

73 lines
2 KiB
Haskell

{- git-annex command
-
- Copyright 2015-2018 Joey Hess <id@joeyh.name>
-
- Licensed under the GNU AGPL version 3 or higher.
-}
{-# LANGUAGE BangPatterns #-}
module Command.RegisterUrl where
import Command
import Logs.Web
import Command.FromKey (keyOpt)
import qualified Remote
cmd :: Command
cmd = notBareRepo $
command "registerurl"
SectionPlumbing "registers an url for a key"
(paramPair paramKey paramUrl)
(seek <$$> optParser)
data RegisterUrlOptions = RegisterUrlOptions
{ keyUrlPairs :: CmdParams
, batchOption :: BatchMode
}
optParser :: CmdParamsDesc -> Parser RegisterUrlOptions
optParser desc = RegisterUrlOptions
<$> cmdParams desc
<*> parseBatchOption
seek :: RegisterUrlOptions -> CommandSeek
seek o = case (batchOption o, keyUrlPairs o) of
(Batch fmt, _) -> commandAction $ startMass fmt
-- older way of enabling batch input, does not support BatchNull
(NoBatch, []) -> commandAction $ startMass BatchLine
(NoBatch, ps) -> withWords (commandAction . start) ps
start :: [String] -> CommandStart
start (keyname:url:[]) =
starting "registerurl" (ActionItemOther (Just url)) $ do
let key = keyOpt keyname
perform key url
start _ = giveup "specify a key and an url"
startMass :: BatchFormat -> CommandStart
startMass fmt =
starting "registerurl" (ActionItemOther (Just "stdin")) $
massAdd fmt
massAdd :: BatchFormat -> CommandPerform
massAdd fmt = go True =<< map (separate (== ' ')) <$> batchLines fmt
where
go status [] = next $ return status
go status ((keyname,u):rest) | not (null keyname) && not (null u) = do
let key = keyOpt keyname
ok <- perform' key u
let !status' = status && ok
go status' rest
go _ _ = giveup "Expected pairs of key and url on stdin, but got something else."
perform :: Key -> URLString -> CommandPerform
perform key url = do
ok <- perform' key url
next $ return ok
perform' :: Key -> URLString -> Annex Bool
perform' key url = do
r <- Remote.claimingUrl url
setUrlPresent key (setDownloader' url r)
return True