 77c43a388e
			
		
	
	
	77c43a388e
	
	
	
		
			
			This is especially useful because the caller doesn't need to generate valid url keys, which involves some escaping of characters, and may involve taking a md5sum of the url if it's too long.
		
			
				
	
	
		
			75 lines
		
	
	
	
		
			2 KiB
			
		
	
	
	
		
			Haskell
		
	
	
	
	
	
			
		
		
	
	
			75 lines
		
	
	
	
		
			2 KiB
			
		
	
	
	
		
			Haskell
		
	
	
	
	
	
| {- git-annex command
 | |
|  -
 | |
|  - Copyright 2010, 2015 Joey Hess <id@joeyh.name>
 | |
|  -
 | |
|  - Licensed under the GNU GPL version 3 or higher.
 | |
|  -}
 | |
| 
 | |
| {-# LANGUAGE BangPatterns #-}
 | |
| 
 | |
| module Command.FromKey where
 | |
| 
 | |
| import Common.Annex
 | |
| import Command
 | |
| import qualified Annex.Queue
 | |
| import Annex.Content
 | |
| import Types.Key
 | |
| import qualified Annex
 | |
| import qualified Backend.URL
 | |
| 
 | |
| import Network.URI
 | |
| 
 | |
| cmd :: [Command]
 | |
| cmd = [notDirect $ notBareRepo $
 | |
| 	command "fromkey" (paramPair paramKey paramPath) seek
 | |
| 		SectionPlumbing "adds a file using a specific key"]
 | |
| 
 | |
| seek :: CommandSeek
 | |
| seek ps = do
 | |
| 	force <- Annex.getState Annex.force
 | |
| 	withWords (start force) ps
 | |
| 
 | |
| start :: Bool -> [String] -> CommandStart
 | |
| start force (keyname:file:[]) = do
 | |
| 	let key = mkKey keyname
 | |
| 	unless force $ do
 | |
| 		inbackend <- inAnnex key
 | |
| 		unless inbackend $ error $
 | |
| 			"key ("++ keyname ++") is not present in backend (use --force to override this sanity check)"
 | |
| 	showStart "fromkey" file
 | |
| 	next $ perform key file
 | |
| start _ [] = do
 | |
| 	showStart "fromkey" "stdin"
 | |
| 	next massAdd
 | |
| start _ _ = error "specify a key and a dest file"
 | |
| 
 | |
| massAdd :: CommandPerform
 | |
| massAdd = go True =<< map (separate (== ' ')) . lines <$> liftIO getContents
 | |
|   where
 | |
| 	go status [] = next $ return status
 | |
| 	go status ((keyname,f):rest) | not (null keyname) && not (null f) = do
 | |
| 		let key = mkKey keyname
 | |
| 		ok <- perform' key f
 | |
| 		let !status' = status && ok
 | |
| 		go status' rest
 | |
| 	go _ _ = error "Expected pairs of key and file on stdin, but got something else."
 | |
| 
 | |
| mkKey :: String -> Key
 | |
| mkKey s = case file2key s of
 | |
| 	Just k -> k
 | |
| 	Nothing -> case parseURI s of
 | |
| 		Just _u -> Backend.URL.fromUrl s Nothing
 | |
| 		Nothing -> error $ "bad key " ++ s
 | |
| 
 | |
| perform :: Key -> FilePath -> CommandPerform
 | |
| perform key file = do
 | |
| 	ok <- perform' key file
 | |
| 	next $ return ok
 | |
| 
 | |
| perform' :: Key -> FilePath -> Annex Bool
 | |
| perform' key file = do
 | |
| 	link <- calcRepo $ gitAnnexLink file key
 | |
| 	liftIO $ createDirectoryIfMissing True (parentDir file)
 | |
| 	liftIO $ createSymbolicLink link file
 | |
| 	Annex.Queue.addCommand "add" [Param "--"] [file]
 | |
| 	return True
 |