git-annex/Remote/Web.hs

139 lines
3.5 KiB
Haskell
Raw Normal View History

{- Web remote.
-
- Copyright 2011 Joey Hess <id@joeyh.name>
-
- Licensed under the GNU GPL version 3 or higher.
-}
2013-09-09 06:16:22 +00:00
{-# LANGUAGE CPP #-}
module Remote.Web (remote) where
2011-10-05 20:02:51 +00:00
import Common.Annex
import Types.Remote
import qualified Git
import qualified Git.Construct
import Annex.Content
import Config.Cost
import Logs.Web
2014-12-17 17:57:52 +00:00
import Annex.UUID
import Types.Key
import Utility.Metered
import qualified Annex.Url as Url
2013-09-09 06:16:22 +00:00
#ifdef WITH_QUVI
import Annex.Quvi
import qualified Utility.Quvi as Quvi
2013-09-09 06:16:22 +00:00
#endif
2011-12-31 08:11:39 +00:00
remote :: RemoteType
remote = RemoteType {
typename = "web",
enumerate = list,
generate = gen,
setup = error "not supported"
}
-- There is only one web remote, and it always exists.
-- (If the web should cease to exist, remove this module and redistribute
-- a new release to the survivors by carrier pigeon.)
list :: Annex [Git.Repo]
2011-12-14 19:30:14 +00:00
list = do
r <- liftIO $ Git.Construct.remoteNamed "web" Git.Construct.fromUnknown
return [r]
gen :: Git.Repo -> UUID -> RemoteConfig -> RemoteGitConfig -> Annex (Maybe Remote)
2013-11-02 23:54:59 +00:00
gen r _ c gc =
2014-12-16 19:26:13 +00:00
return $ Just Remote
{ uuid = webUUID
, cost = expensiveRemoteCost
, name = Git.repoDescribe r
, storeKey = uploadKey
, retrieveKeyFile = downloadKey
, retrieveKeyFileCheap = downloadKeyCheap
, removeKey = dropKey
, checkPresent = checkKey
, checkPresentCheap = False
, whereisKey = Just getWebUrls
, remoteFsck = Nothing
, repairRepo = Nothing
, config = c
, gitconfig = gc
, localpath = Nothing
, repo = r
, readonly = True
, availability = GloballyAvailable
, remotetype = remote
, mkUnavailable = return Nothing
, getInfo = return []
, claimUrl = Nothing -- implicitly claims all urls
, checkUrl = Nothing
}
downloadKey :: Key -> AssociatedFile -> FilePath -> MeterUpdate -> Annex Bool
downloadKey key _file dest _p = get =<< getWebUrls key
2012-11-11 04:51:07 +00:00
where
get [] = do
warning "no known url"
return False
get urls = do
showOutput -- make way for download progress bar
untilTrue urls $ \u -> do
let (u', downloader) = getDownloader u
case downloader of
2013-09-09 06:16:22 +00:00
QuviDownloader -> do
#ifdef WITH_QUVI
flip downloadUrl dest
=<< withQuviOptions Quvi.queryLinks [Quvi.httponly, Quvi.quiet] u'
#else
warning "quvi support needed for this url"
return False
#endif
_ -> downloadUrl [u'] dest
downloadKeyCheap :: Key -> FilePath -> Annex Bool
downloadKeyCheap _ _ = return False
2012-09-21 18:50:14 +00:00
uploadKey :: Key -> AssociatedFile -> MeterUpdate -> Annex Bool
uploadKey _ _ _ = do
warning "upload to web not supported"
return False
2011-07-01 21:15:46 +00:00
dropKey :: Key -> Annex Bool
2012-11-29 21:01:07 +00:00
dropKey k = do
mapM_ (setUrlMissing webUUID k) =<< getWebUrls k
2012-11-29 21:01:07 +00:00
return True
checkKey :: Key -> Annex Bool
2011-07-01 21:15:46 +00:00
checkKey key = do
us <- getWebUrls key
if null us
then return False
else either error return =<< checkKey' key us
2013-09-09 06:16:22 +00:00
checkKey' :: Key -> [URLString] -> Annex (Either String Bool)
checkKey' key us = firsthit us (Right False) $ \u -> do
let (u', downloader) = getDownloader u
showAction $ "checking " ++ u'
case downloader of
QuviDownloader ->
2013-09-09 06:16:22 +00:00
#ifdef WITH_QUVI
Right <$> withQuviOptions Quvi.check [Quvi.httponly, Quvi.quiet] u'
#else
return $ Left "quvi support needed for this url"
#endif
_ -> do
2014-02-25 02:00:25 +00:00
Url.withUrlOptions $ catchMsgIO .
Url.checkBoth u' (keySize key)
2013-09-09 06:16:22 +00:00
where
firsthit [] miss _ = return miss
2013-09-09 06:16:22 +00:00
firsthit (u:rest) _ a = do
r <- a u
case r of
Right _ -> return r
Left _ -> firsthit rest r a
getWebUrls :: Key -> Annex [URLString]
getWebUrls key = filter supported <$> getUrls key
where
supported u = snd (getDownloader u)
`elem` [WebDownloader, QuviDownloader]