WebDAV: Dropped support for DAV before 0.6.1.

0.6.1 is in testing, and stable does not have DAV at all, so I can dispense
with this compatability code
This commit is contained in:
Joey Hess 2014-07-30 11:19:05 -04:00
parent 89416ba2d9
commit b5ac627fee
3 changed files with 4 additions and 44 deletions

View file

@ -5,7 +5,7 @@
- Licensed under the GNU GPL version 3 or higher. - Licensed under the GNU GPL version 3 or higher.
-} -}
{-# LANGUAGE ScopedTypeVariables, CPP #-} {-# LANGUAGE ScopedTypeVariables #-}
module Remote.WebDAV (remote, davCreds, configUrl) where module Remote.WebDAV (remote, davCreds, configUrl) where
@ -16,11 +16,7 @@ import qualified Data.ByteString.Lazy.UTF8 as L8
import qualified Data.ByteString.Lazy as L import qualified Data.ByteString.Lazy as L
import qualified Control.Exception as E import qualified Control.Exception as E
import qualified Control.Exception.Lifted as EL import qualified Control.Exception.Lifted as EL
#if MIN_VERSION_DAV(0,6,0)
import Network.HTTP.Client (HttpException(..)) import Network.HTTP.Client (HttpException(..))
#else
import Network.HTTP.Conduit (HttpException(..))
#endif
import Network.HTTP.Types import Network.HTTP.Types
import System.Log.Logger (debugM) import System.Log.Logger (debugM)
import System.IO.Error import System.IO.Error
@ -308,57 +304,37 @@ debugDAV :: DavUrl -> String -> IO ()
debugDAV msg url = debugM "DAV" $ msg ++ " " ++ url debugDAV msg url = debugM "DAV" $ msg ++ " " ++ url
{--------------------------------------------------------------------- {---------------------------------------------------------------------
- Low-level DAV operations, using the new DAV monad when available. - Low-level DAV operations.
---------------------------------------------------------------------} ---------------------------------------------------------------------}
putDAV :: DavUrl -> DavUser -> DavPass -> L.ByteString -> IO () putDAV :: DavUrl -> DavUser -> DavPass -> L.ByteString -> IO ()
putDAV url user pass b = do putDAV url user pass b = do
debugDAV "PUT" url debugDAV "PUT" url
#if MIN_VERSION_DAV(0,6,0)
goDAV url user pass $ putContentM (contentType, b) goDAV url user pass $ putContentM (contentType, b)
#else
putContent url user pass (contentType, b)
#endif
getDAV :: DavUrl -> DavUser -> DavPass -> IO (Maybe L.ByteString) getDAV :: DavUrl -> DavUser -> DavPass -> IO (Maybe L.ByteString)
getDAV url user pass = do getDAV url user pass = do
debugDAV "GET" url debugDAV "GET" url
eitherToMaybe <$> tryNonAsync go eitherToMaybe <$> tryNonAsync go
where where
#if MIN_VERSION_DAV(0,6,0)
go = goDAV url user pass $ snd <$> getContentM go = goDAV url user pass $ snd <$> getContentM
#else
go = snd . snd <$> getPropsAndContent url user pass
#endif
deleteDAV :: DavUrl -> DavUser -> DavPass -> IO () deleteDAV :: DavUrl -> DavUser -> DavPass -> IO ()
deleteDAV url user pass = do deleteDAV url user pass = do
debugDAV "DELETE" url debugDAV "DELETE" url
#if MIN_VERSION_DAV(0,6,0)
goDAV url user pass delContentM goDAV url user pass delContentM
#else
deleteContent url user pass
#endif
moveDAV :: DavUrl -> DavUrl -> DavUser -> DavPass -> IO () moveDAV :: DavUrl -> DavUrl -> DavUser -> DavPass -> IO ()
moveDAV url newurl user pass = do moveDAV url newurl user pass = do
debugDAV ("MOVE to " ++ newurl ++ " from ") url debugDAV ("MOVE to " ++ newurl ++ " from ") url
#if MIN_VERSION_DAV(0,6,0)
goDAV url user pass $ moveContentM newurl' goDAV url user pass $ moveContentM newurl'
#else
moveContent url newurl' user pass
#endif
where where
newurl' = B8.fromString newurl newurl' = B8.fromString newurl
mkdirDAV :: DavUrl -> DavUser -> DavPass -> IO Bool mkdirDAV :: DavUrl -> DavUser -> DavPass -> IO Bool
mkdirDAV url user pass = do mkdirDAV url user pass = do
debugDAV "MKDIR" url debugDAV "MKDIR" url
#if MIN_VERSION_DAV(0,6,0)
goDAV url user pass mkCol goDAV url user pass mkCol
#else
makeCollection url user pass
#endif
existsDAV :: DavUrl -> DavUser -> DavPass -> IO (Either String Bool) existsDAV :: DavUrl -> DavUser -> DavPass -> IO (Either String Bool)
existsDAV url user pass = do existsDAV url user pass = do
@ -366,35 +342,19 @@ existsDAV url user pass = do
either (Left . show) id <$> tryNonAsync check either (Left . show) id <$> tryNonAsync check
where where
ispresent = return . Right ispresent = return . Right
#if MIN_VERSION_DAV(0,6,0)
check = goDAV url user pass $ do check = goDAV url user pass $ do
setDepth Nothing setDepth Nothing
EL.catchJust EL.catchJust
(matchStatusCodeException notFound404) (matchStatusCodeException notFound404)
(getPropsM >> ispresent True) (getPropsM >> ispresent True)
(const $ ispresent False) (const $ ispresent False)
#else
check = E.catchJust
(matchStatusCodeException notFound404)
#if ! MIN_VERSION_DAV(0,4,0)
(getProps url user pass >> ispresent True)
#else
(getProps url user pass Nothing >> ispresent True)
#endif
(const $ ispresent False)
#endif
matchStatusCodeException :: Status -> HttpException -> Maybe () matchStatusCodeException :: Status -> HttpException -> Maybe ()
#if MIN_VERSION_DAV(0,6,0)
matchStatusCodeException want (StatusCodeException s _ _) matchStatusCodeException want (StatusCodeException s _ _)
#else
matchStatusCodeException want (StatusCodeException s _)
#endif
| s == want = Just () | s == want = Just ()
| otherwise = Nothing | otherwise = Nothing
matchStatusCodeException _ _ = Nothing matchStatusCodeException _ _ = Nothing
#if MIN_VERSION_DAV(0,6,0)
goDAV :: DavUrl -> DavUser -> DavPass -> DAVT IO a -> IO a goDAV :: DavUrl -> DavUser -> DavPass -> DAVT IO a -> IO a
goDAV url user pass a = choke $ evalDAVT url $ do goDAV url user pass a = choke $ evalDAVT url $ do
setResponseTimeout Nothing -- disable default (5 second!) timeout setResponseTimeout Nothing -- disable default (5 second!) timeout
@ -407,4 +367,3 @@ goDAV url user pass a = choke $ evalDAVT url $ do
case x of case x of
Left e -> error e Left e -> error e
Right r -> return r Right r -> return r
#endif

1
debian/changelog vendored
View file

@ -14,6 +14,7 @@ git-annex (5.20140718) UNRELEASED; urgency=medium
Fix this, including support for fixing up repositories that Fix this, including support for fixing up repositories that
were incompletely repaired before. were incompletely repaired before.
* Fix cost calculation for non-encrypted remotes. * Fix cost calculation for non-encrypted remotes.
* WebDAV: Dropped support for DAV before 0.6.1.
-- Joey Hess <joeyh@debian.org> Mon, 21 Jul 2014 14:41:26 -0400 -- Joey Hess <joeyh@debian.org> Mon, 21 Jul 2014 14:41:26 -0400

View file

@ -142,7 +142,7 @@ Executable git-annex
CPP-Options: -DWITH_S3 CPP-Options: -DWITH_S3
if flag(WebDAV) if flag(WebDAV)
Build-Depends: DAV ((>= 0.3 && < 0.6) || > 0.6), Build-Depends: DAV (> 0.6),
http-client, http-conduit, http-types, lifted-base http-client, http-conduit, http-types, lifted-base
CPP-Options: -DWITH_WEBDAV CPP-Options: -DWITH_WEBDAV