webdav is fully working in non-enctypted mode
This commit is contained in:
parent
16840ee799
commit
a4b86c63d6
4 changed files with 105 additions and 25 deletions
121
Remote/WebDAV.hs
121
Remote/WebDAV.hs
|
@ -5,6 +5,8 @@
|
||||||
- Licensed under the GNU GPL version 3 or higher.
|
- Licensed under the GNU GPL version 3 or higher.
|
||||||
-}
|
-}
|
||||||
|
|
||||||
|
{-# LANGUAGE ScopedTypeVariables #-}
|
||||||
|
|
||||||
module Remote.WebDAV (remote) where
|
module Remote.WebDAV (remote) where
|
||||||
|
|
||||||
import Network.Protocol.HTTP.DAV
|
import Network.Protocol.HTTP.DAV
|
||||||
|
@ -13,6 +15,10 @@ import qualified Data.ByteString.UTF8 as B8
|
||||||
import qualified Data.ByteString.Lazy as L
|
import qualified Data.ByteString.Lazy as L
|
||||||
import qualified Data.Text as T
|
import qualified Data.Text as T
|
||||||
import qualified Text.XML as XML
|
import qualified Text.XML as XML
|
||||||
|
import Network.URI (normalizePathSegments)
|
||||||
|
import qualified Control.Exception as E
|
||||||
|
import Network.HTTP.Conduit (HttpException(..))
|
||||||
|
import Network.HTTP.Types
|
||||||
|
|
||||||
import Common.Annex
|
import Common.Annex
|
||||||
import Types.Remote
|
import Types.Remote
|
||||||
|
@ -22,7 +28,6 @@ import Remote.Helper.Special
|
||||||
import Remote.Helper.Encryptable
|
import Remote.Helper.Encryptable
|
||||||
import Crypto
|
import Crypto
|
||||||
import Creds
|
import Creds
|
||||||
import Annex.Content
|
|
||||||
|
|
||||||
type DavUrl = String
|
type DavUrl = String
|
||||||
type DavUser = B8.ByteString
|
type DavUser = B8.ByteString
|
||||||
|
@ -78,20 +83,29 @@ webdavSetup u c = do
|
||||||
store :: Remote -> Key -> AssociatedFile -> MeterUpdate -> Annex Bool
|
store :: Remote -> Key -> AssociatedFile -> MeterUpdate -> Annex Bool
|
||||||
store r k _f _p = do
|
store r k _f _p = do
|
||||||
f <- inRepo $ gitAnnexLocation k
|
f <- inRepo $ gitAnnexLocation k
|
||||||
davAction r False $ \(baseurl, user, pass) -> liftIO $ catchBoolIO $ do
|
davAction r False $ \(baseurl, user, pass) -> liftIO $ do
|
||||||
content <- L.readFile f
|
|
||||||
let url = Prelude.head $ davLocations baseurl k
|
let url = Prelude.head $ davLocations baseurl k
|
||||||
putContentAndProps url user pass
|
davMkdir (urlParent url) user pass
|
||||||
(noProps, (contentType, content))
|
b <- L.readFile f
|
||||||
return True
|
v <- catchMaybeHttp $ putContentAndProps url user pass
|
||||||
|
(noProps, (contentType, b))
|
||||||
|
return $ isJust v
|
||||||
|
|
||||||
storeEncrypted :: Remote -> (Cipher, Key) -> Key -> MeterUpdate -> Annex Bool
|
storeEncrypted :: Remote -> (Cipher, Key) -> Key -> MeterUpdate -> Annex Bool
|
||||||
storeEncrypted r (cipher, enck) k _p = davAction r False $ \creds -> do
|
storeEncrypted r (cipher, enck) k _p = davAction r False $ \creds -> liftIO $ do
|
||||||
error "TODO"
|
error "TODO"
|
||||||
|
|
||||||
retrieve :: Remote -> Key -> AssociatedFile -> FilePath -> Annex Bool
|
retrieve :: Remote -> Key -> AssociatedFile -> FilePath -> Annex Bool
|
||||||
retrieve r k _f d = davAction r False $ \creds -> do
|
retrieve r k _f d = davAction r False $ liftIO . go
|
||||||
error "TODO"
|
where
|
||||||
|
go (baseurl, user, pass) = get $ davLocations baseurl k
|
||||||
|
where
|
||||||
|
get [] = return False
|
||||||
|
get (u:urls) = maybe (get urls) save
|
||||||
|
=<< catchMaybeHttp (getPropsAndContent u user pass)
|
||||||
|
save (_, (_, b)) = do
|
||||||
|
L.writeFile d b
|
||||||
|
return True
|
||||||
|
|
||||||
retrieveCheap :: Remote -> Key -> FilePath -> Annex Bool
|
retrieveCheap :: Remote -> Key -> FilePath -> Annex Bool
|
||||||
retrieveCheap _ _ _ = return False
|
retrieveCheap _ _ _ = return False
|
||||||
|
@ -101,16 +115,41 @@ retrieveEncrypted r (cipher, enck) _ f = davAction r False $ \creds -> do
|
||||||
error "TODO"
|
error "TODO"
|
||||||
|
|
||||||
remove :: Remote -> Key -> Annex Bool
|
remove :: Remote -> Key -> Annex Bool
|
||||||
remove r k = davAction r False $ \creds -> do
|
remove r k = davAction r False $ liftIO . go
|
||||||
error "TODO"
|
where
|
||||||
|
go (baseurl, user, pass) = delone $ davLocations baseurl k
|
||||||
|
where
|
||||||
|
delone [] = return False
|
||||||
|
delone (u:urls) = maybe (delone urls) (const $ return True)
|
||||||
|
=<< catchMaybeHttp (deletedir u)
|
||||||
|
|
||||||
|
{- Rather than deleting first the file, and then its
|
||||||
|
- immediate parent directory (to clean up), delete the
|
||||||
|
- parent directory, along with all its contents in a
|
||||||
|
- single recursive DAV call.
|
||||||
|
-
|
||||||
|
- The file is the only thing we keep in there, and this
|
||||||
|
- is faster. -}
|
||||||
|
deletedir u = deleteContent (urlParent u) user pass
|
||||||
|
|
||||||
checkPresent :: Remote -> Key -> Annex (Either String Bool)
|
checkPresent :: Remote -> Key -> Annex (Either String Bool)
|
||||||
checkPresent r k = davAction r noconn $ \creds -> do
|
checkPresent r k = davAction r noconn go
|
||||||
showAction $ "checking " ++ name r
|
|
||||||
return $ Right False
|
|
||||||
--error "TODO"
|
|
||||||
where
|
where
|
||||||
noconn = Left $ error $ name r ++ " not configured"
|
noconn = Left $ error $ name r ++ " not configured"
|
||||||
|
go (baseurl, user, pass) = do
|
||||||
|
showAction $ "checking " ++ name r
|
||||||
|
liftIO $ check $ davLocations baseurl k
|
||||||
|
where
|
||||||
|
check [] = return $ Right False
|
||||||
|
check (u:urls) = do
|
||||||
|
v <- catchHttp $ getProps u user pass
|
||||||
|
case v of
|
||||||
|
Right _ -> return $ Right True
|
||||||
|
Left (Left (StatusCodeException status _))
|
||||||
|
| statusCode status == statusCode notFound404 -> check urls
|
||||||
|
| otherwise -> return $ Left $ show $ statusMessage status
|
||||||
|
Left (Left httpexception) -> return $ Left $ show httpexception
|
||||||
|
Left (Right ioexception) -> return $ Left $ show ioexception
|
||||||
|
|
||||||
davAction :: Remote -> a -> ((DavUrl, DavUser, DavPass) -> Annex a) -> Annex a
|
davAction :: Remote -> a -> ((DavUrl, DavUser, DavPass) -> Annex a) -> Annex a
|
||||||
davAction r unconfigured action = case config r of
|
davAction r unconfigured action = case config r of
|
||||||
|
@ -135,9 +174,48 @@ toDavPass = B8.fromString
|
||||||
davLocations :: DavUrl -> Key -> [DavUrl]
|
davLocations :: DavUrl -> Key -> [DavUrl]
|
||||||
davLocations baseurl k = map (davUrl baseurl) (keyPaths k)
|
davLocations baseurl k = map (davUrl baseurl) (keyPaths k)
|
||||||
|
|
||||||
{- FIXME: Replacing / with _ to avoid needing collections. -}
|
|
||||||
davUrl :: DavUrl -> FilePath -> DavUrl
|
davUrl :: DavUrl -> FilePath -> DavUrl
|
||||||
davUrl baseurl file = baseurl </> replace "/" "_" file
|
davUrl baseurl file = baseurl </> file
|
||||||
|
|
||||||
|
{- Creates a directory in WebDAV, if not already present; also creating
|
||||||
|
- any missing parent directories. -}
|
||||||
|
davMkdir :: DavUrl -> DavUser -> DavPass -> IO ()
|
||||||
|
davMkdir url user pass = go url
|
||||||
|
where
|
||||||
|
make u = makeCollection u user pass
|
||||||
|
|
||||||
|
go u = do
|
||||||
|
r <- E.try (make u) :: IO (Either E.SomeException Bool)
|
||||||
|
case r of
|
||||||
|
{- Parent directory is missing. Recurse to create
|
||||||
|
- it, and try once more to create the directory. -}
|
||||||
|
Right False -> do
|
||||||
|
go (urlParent u)
|
||||||
|
void $ make u
|
||||||
|
{- Directory created successfully -}
|
||||||
|
Right True -> return ()
|
||||||
|
{- Directory already exists, or some other error
|
||||||
|
- occurred. In the latter case, whatever wanted
|
||||||
|
- to use this directory will fail. -}
|
||||||
|
Left _ -> return ()
|
||||||
|
|
||||||
|
{- Catches HTTP and IO exceptions. -}
|
||||||
|
catchMaybeHttp :: IO a -> IO (Maybe a)
|
||||||
|
catchMaybeHttp a = (Just <$> a) `E.catches`
|
||||||
|
[ E.Handler $ \(_e :: HttpException) -> return Nothing
|
||||||
|
, E.Handler $ \(_e :: E.IOException) -> return Nothing
|
||||||
|
]
|
||||||
|
|
||||||
|
{- Catches HTTP and IO exceptions -}
|
||||||
|
catchHttp :: IO a -> IO (Either (Either HttpException E.IOException) a)
|
||||||
|
catchHttp a = (Right <$> a) `E.catches`
|
||||||
|
[ E.Handler $ \(e :: HttpException) -> return $ Left $ Left e
|
||||||
|
, E.Handler $ \(e :: E.IOException) -> return $ Left $ Right e
|
||||||
|
]
|
||||||
|
|
||||||
|
urlParent :: DavUrl -> DavUrl
|
||||||
|
urlParent url = reverse $ dropWhile (== '/') $ reverse $
|
||||||
|
normalizePathSegments (url ++ "/..")
|
||||||
|
|
||||||
{- Test if a WebDAV store is usable, by writing to a test file, and then
|
{- Test if a WebDAV store is usable, by writing to a test file, and then
|
||||||
- deleting the file. Exits with an error if not. -}
|
- deleting the file. Exits with an error if not. -}
|
||||||
|
@ -146,12 +224,13 @@ testDav baseurl Nothing = error "Need to configure webdav username and password.
|
||||||
testDav baseurl (Just (u, p)) = do
|
testDav baseurl (Just (u, p)) = do
|
||||||
showSideAction "testing WebDAV server"
|
showSideAction "testing WebDAV server"
|
||||||
liftIO $ do
|
liftIO $ do
|
||||||
putContentAndProps testurl username password
|
davMkdir baseurl user pass
|
||||||
|
putContentAndProps testurl user pass
|
||||||
(noProps, (contentType, L.empty))
|
(noProps, (contentType, L.empty))
|
||||||
deleteContent testurl username password
|
deleteContent testurl user pass
|
||||||
where
|
where
|
||||||
username = toDavUser u
|
user = toDavUser u
|
||||||
password = toDavPass p
|
pass = toDavPass p
|
||||||
testurl = davUrl baseurl "git-annex-test"
|
testurl = davUrl baseurl "git-annex-test"
|
||||||
|
|
||||||
{- Content-Type to use for files uploaded to WebDAV. -}
|
{- Content-Type to use for files uploaded to WebDAV. -}
|
||||||
|
|
2
debian/control
vendored
2
debian/control
vendored
|
@ -12,7 +12,7 @@ Build-Depends:
|
||||||
libghc-http-dev,
|
libghc-http-dev,
|
||||||
libghc-utf8-string-dev,
|
libghc-utf8-string-dev,
|
||||||
libghc-hs3-dev (>= 0.5.6),
|
libghc-hs3-dev (>= 0.5.6),
|
||||||
libghc-dav-dev (>= 0.1),
|
libghc-dav-dev (>= 0.2),
|
||||||
libghc-testpack-dev,
|
libghc-testpack-dev,
|
||||||
libghc-quickcheck2-dev,
|
libghc-quickcheck2-dev,
|
||||||
libghc-monad-control-dev (>= 0.3),
|
libghc-monad-control-dev (>= 0.3),
|
||||||
|
|
|
@ -20,7 +20,8 @@ the webdav remote.
|
||||||
the new key id. See [[encryption]].
|
the new key id. See [[encryption]].
|
||||||
|
|
||||||
* `url` - Required. The URL to the WebDAV directory where files will be
|
* `url` - Required. The URL to the WebDAV directory where files will be
|
||||||
stored. This directory must already exist. Use of a https URL is strongly
|
stored. This can be a subdirectory of a larger WebDAV repository, and will
|
||||||
|
be created as needed. Use of a https URL is strongly
|
||||||
encouraged, since HTTP basic authentication is used.
|
encouraged, since HTTP basic authentication is used.
|
||||||
|
|
||||||
* `chunksize` - Avoid storing files larger than the specified size in
|
* `chunksize` - Avoid storing files larger than the specified size in
|
||||||
|
@ -33,4 +34,4 @@ the webdav remote.
|
||||||
|
|
||||||
Setup example:
|
Setup example:
|
||||||
|
|
||||||
# WEBDAV_USERNAME=joey@kitenet.net WEBDAV_PASSWORD=xxxxxxx git annex initremote box.com type=webdav url=https://www.box.com/dav/ encryption=joey@kitenet.net
|
# WEBDAV_USERNAME=joey@kitenet.net WEBDAV_PASSWORD=xxxxxxx git annex initremote box.com type=webdav url=https://www.box.com/dav/git-annex encryption=joey@kitenet.net
|
||||||
|
|
|
@ -73,7 +73,7 @@ Executable git-annex
|
||||||
CPP-Options: -DWITH_S3
|
CPP-Options: -DWITH_S3
|
||||||
|
|
||||||
if flag(WebDAV)
|
if flag(WebDAV)
|
||||||
Build-Depends: DAV (>= 0.1)
|
Build-Depends: DAV (>= 0.2), http-conduit
|
||||||
CPP-Options: -DWITH_WebDAV
|
CPP-Options: -DWITH_WebDAV
|
||||||
|
|
||||||
if flag(Assistant) && ! os(windows) && ! os(solaris)
|
if flag(Assistant) && ! os(windows) && ! os(solaris)
|
||||||
|
|
Loading…
Add table
Reference in a new issue