summaryrefslogtreecommitdiff
path: root/Command/RegisterUrl.hs
diff options
context:
space:
mode:
authorGravatar Joey Hess <joeyh@joeyh.name>2015-03-15 14:37:33 -0400
committerGravatar Joey Hess <joeyh@joeyh.name>2015-03-15 14:37:33 -0400
commita29ec4336c45000635aae179ae64123b9e78a9b0 (patch)
treebe10c80b69d8b507a3e337e735219fc1ce019f50 /Command/RegisterUrl.hs
parent96af58d9e0f73ad78f09651e855b20cc27f9113a (diff)
registerurl: New plumbing command for mass-adding urls to keys.
Diffstat (limited to 'Command/RegisterUrl.hs')
-rw-r--r--Command/RegisterUrl.hs55
1 files changed, 55 insertions, 0 deletions
diff --git a/Command/RegisterUrl.hs b/Command/RegisterUrl.hs
new file mode 100644
index 000000000..3ff1becc9
--- /dev/null
+++ b/Command/RegisterUrl.hs
@@ -0,0 +1,55 @@
+{- git-annex command
+ -
+ - Copyright 2015 Joey Hess <id@joeyh.name>
+ -
+ - Licensed under the GNU GPL version 3 or higher.
+ -}
+
+{-# LANGUAGE BangPatterns #-}
+
+module Command.RegisterUrl where
+
+import Common.Annex
+import Command
+import Types.Key
+import Logs.Web
+import Annex.UUID
+
+cmd :: [Command]
+cmd = [notDirect $ notBareRepo $
+ command "registerurl" (paramPair paramKey paramUrl) seek
+ SectionPlumbing "registers an url for a key"]
+
+seek :: CommandSeek
+seek = withWords start
+
+start :: [String] -> CommandStart
+start (keyname:url:[]) = do
+ let key = fromMaybe (error "bad key") $ file2key keyname
+ showStart "registerurl" url
+ next $ perform key url
+start [] = do
+ showStart "registerurl" "stdin"
+ next massAdd
+start _ = error "specify a key and an url"
+
+massAdd :: CommandPerform
+massAdd = go True =<< map words . lines <$> liftIO getContents
+ where
+ go status [] = next $ return status
+ go status ([keyname,u]:rest) = do
+ let key = fromMaybe (error $ "bad key " ++ keyname) $ file2key keyname
+ ok <- perform' key u
+ let !status' = status && ok
+ go status' rest
+ go _ _ = error "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
+ setUrlPresent webUUID key url
+ return True