2010-11-02 23:04:24 +00:00
|
|
|
{- git-annex command
|
|
|
|
-
|
2015-05-23 02:41:36 +00:00
|
|
|
- Copyright 2010, 2015 Joey Hess <id@joeyh.name>
|
2010-11-02 23:04:24 +00:00
|
|
|
-
|
|
|
|
- Licensed under the GNU GPL version 3 or higher.
|
|
|
|
-}
|
|
|
|
|
2015-03-15 18:07:43 +00:00
|
|
|
{-# LANGUAGE BangPatterns #-}
|
|
|
|
|
2010-11-02 23:04:24 +00:00
|
|
|
module Command.FromKey where
|
|
|
|
|
|
|
|
import Command
|
2011-10-04 04:40:47 +00:00
|
|
|
import qualified Annex.Queue
|
|
|
|
import Annex.Content
|
2015-03-15 17:51:58 +00:00
|
|
|
import qualified Annex
|
2015-05-23 02:41:36 +00:00
|
|
|
import qualified Backend.URL
|
|
|
|
|
|
|
|
import Network.URI
|
2010-11-02 23:04:24 +00:00
|
|
|
|
2015-07-08 16:33:27 +00:00
|
|
|
cmd :: Command
|
|
|
|
cmd = notDirect $ notBareRepo $
|
2015-07-08 19:08:02 +00:00
|
|
|
command "fromkey" SectionPlumbing "adds a file using a specific key"
|
2016-12-05 14:59:20 +00:00
|
|
|
(paramRepeating (paramPair paramKey paramPath))
|
2015-07-08 19:08:02 +00:00
|
|
|
(withParams seek)
|
2010-12-30 19:06:26 +00:00
|
|
|
|
2015-07-08 19:08:02 +00:00
|
|
|
seek :: CmdParams -> CommandSeek
|
2016-12-05 16:16:07 +00:00
|
|
|
seek [] = withNothing startMass []
|
2015-03-15 17:51:58 +00:00
|
|
|
seek ps = do
|
|
|
|
force <- Annex.getState Annex.force
|
2016-12-05 14:59:20 +00:00
|
|
|
withPairs (start force) ps
|
2010-11-11 22:54:52 +00:00
|
|
|
|
2016-12-05 14:59:20 +00:00
|
|
|
start :: Bool -> (String, FilePath) -> CommandStart
|
|
|
|
start force (keyname, file) = do
|
2015-05-23 02:41:36 +00:00
|
|
|
let key = mkKey keyname
|
2015-03-15 17:51:58 +00:00
|
|
|
unless force $ do
|
|
|
|
inbackend <- inAnnex key
|
2016-11-16 01:29:54 +00:00
|
|
|
unless inbackend $ giveup $
|
2015-03-15 17:51:58 +00:00
|
|
|
"key ("++ keyname ++") is not present in backend (use --force to override this sanity check)"
|
2010-11-02 23:04:24 +00:00
|
|
|
showStart "fromkey" file
|
2011-10-31 16:47:13 +00:00
|
|
|
next $ perform key file
|
2016-12-05 14:59:20 +00:00
|
|
|
|
|
|
|
startMass :: CommandStart
|
|
|
|
startMass = do
|
2015-03-15 18:07:43 +00:00
|
|
|
showStart "fromkey" "stdin"
|
|
|
|
next massAdd
|
2011-01-26 04:17:38 +00:00
|
|
|
|
2015-03-15 18:07:43 +00:00
|
|
|
massAdd :: CommandPerform
|
2016-12-13 19:35:04 +00:00
|
|
|
massAdd = go True =<< map (separate (== ' ')) <$> batchLines
|
2015-03-15 18:07:43 +00:00
|
|
|
where
|
|
|
|
go status [] = next $ return status
|
2015-04-07 04:58:51 +00:00
|
|
|
go status ((keyname,f):rest) | not (null keyname) && not (null f) = do
|
2015-05-23 02:41:36 +00:00
|
|
|
let key = mkKey keyname
|
2015-03-15 18:07:43 +00:00
|
|
|
ok <- perform' key f
|
|
|
|
let !status' = status && ok
|
|
|
|
go status' rest
|
2016-11-16 01:29:54 +00:00
|
|
|
go _ _ = giveup "Expected pairs of key and file on stdin, but got something else."
|
2015-03-15 18:07:43 +00:00
|
|
|
|
2015-05-30 06:08:49 +00:00
|
|
|
-- From user input to a Key.
|
|
|
|
-- User can input either a serialized key, or an url.
|
|
|
|
--
|
|
|
|
-- In some cases, an input can be parsed as both a key and as an uri.
|
|
|
|
-- For example, "WORM--a:a" parses as an uri. To disambiguate, check
|
|
|
|
-- the uri scheme, to see if it looks like the prefix of a key. This relies
|
|
|
|
-- on key backend names never containing a ':'.
|
2015-05-23 02:41:36 +00:00
|
|
|
mkKey :: String -> Key
|
2015-05-30 06:08:49 +00:00
|
|
|
mkKey s = case parseURI s of
|
|
|
|
Just u | not (isKeyPrefix (uriScheme u)) ->
|
|
|
|
Backend.URL.fromUrl s Nothing
|
|
|
|
_ -> case file2key s of
|
|
|
|
Just k -> k
|
2016-11-16 01:29:54 +00:00
|
|
|
Nothing -> giveup $ "bad key/url " ++ s
|
2015-05-23 02:41:36 +00:00
|
|
|
|
2011-10-31 16:47:13 +00:00
|
|
|
perform :: Key -> FilePath -> CommandPerform
|
|
|
|
perform key file = do
|
2015-03-15 18:07:43 +00:00
|
|
|
ok <- perform' key file
|
|
|
|
next $ return ok
|
|
|
|
|
|
|
|
perform' :: Key -> FilePath -> Annex Bool
|
|
|
|
perform' key file = do
|
2015-01-27 21:38:06 +00:00
|
|
|
link <- calcRepo $ gitAnnexLink file key
|
2015-01-09 17:11:56 +00:00
|
|
|
liftIO $ createDirectoryIfMissing True (parentDir file)
|
2010-11-02 23:04:24 +00:00
|
|
|
liftIO $ createSymbolicLink link file
|
2012-06-07 19:19:44 +00:00
|
|
|
Annex.Queue.addCommand "add" [Param "--"] [file]
|
2010-11-02 23:04:24 +00:00
|
|
|
return True
|