DAV-1.0.3: RFC 4918 WebDAV support

Safe HaskellNone

Network.Protocol.HTTP.DAV

Synopsis

Documentation

newtype DAVT m a Source

Constructors

DAVT 

Fields

runDAVT :: EitherT String (StateT DAVContext m) a
 

Instances

MonadTrans DAVT 
Monad m => MonadError String (DAVT m) 
Monad m => MonadState DAVContext (DAVT m) 
MonadBase b m => MonadBase b (DAVT m) 
Monad m => Monad (DAVT m) 
Monad m => Functor (DAVT m) 
MonadFix m => MonadFix (DAVT m) 
Monad m => MonadPlus (DAVT m) 
Monad m => Applicative (DAVT m) 
MonadThrow m => MonadThrow (DAVT m) 
MonadCatch m => MonadCatch (DAVT m) 
MonadMask m => MonadMask (DAVT m) 
MonadIO m => MonadIO (DAVT m) 

evalDAVT :: MonadIO m => DAVURL -> DAVT m a -> m (Either String a)Source

withDAVContext :: (MonadIO m, MonadMask m) => DAVURL -> (DAVContext -> m a) -> m aSource

runDAVContext :: MonadIO m => DAVContext -> DAVT m a -> m (Either String a, DAVContext)Source

setDepth :: MonadIO m => Maybe Depth -> DAVT m ()Source

setResponseTimeout :: MonadIO m => Maybe Int -> DAVT m ()Source

getContentM :: MonadIO m => DAVT m (Maybe ByteString, ByteString)Source

Note that the entire request body is buffered in memory. To stream large files use withContentM instead.

mkCol :: (MonadIO m, MonadBase IO m, MonadCatch m) => DAVT m BoolSource

putContentM :: MonadIO m => (Maybe ByteString, ByteString) -> DAVT m ()Source

Note that the entire request body is buffered in memory; not suitable for large files.

putContentM' :: MonadIO m => (Maybe ByteString, RequestBody) -> DAVT m ()Source

To send a large file, pass eg a RequestBodyStream containing the file's content.

withLockIfPossible :: (MonadIO m, MonadBase IO m, MonadCatch m, MonadMask m) => Bool -> DAVT m a -> DAVT m aSource

inDAVLocation :: MonadIO m => (String -> String) -> DAVT m a -> DAVT m aSource

Normally, DAVT actions act on the url that is provided to eg, evalDAVT. Sometimes, it's useful to adjust the url that is acted on, while remaining in the same DAV session.

inLocation temporarily adjusts the url's path, while performing a DAVT action.

For example:

 import System.FilePath.Posix -- posix for url path manipulation

 mkColRecursive d = do
   let parent = takeDirectory d
   when (parent /= d) $
     mkColRecursive parent
   inDAVLocation (</> d) mkCol

Note that operations that modify the DAVContext (such as setCreds and setCreds) can be run inside davLocation, but will not have any effect on the calling DAVContext.

getDAVLocation :: Monad m => DAVT m StringSource

Gets the path of the url that DAVT actions will act on.

data Depth Source

Constructors

Depth0 
Depth1 
DepthInfinity 

Instances

Read Depth 
Show Depth