Safe Haskell | None |
---|---|
Language | Haskell98 |
an interface for using the methods in varlibaptmethods
- withMethodPath :: FilePath -> (MethodHandle -> IO a) -> IO a
- withMethodURI :: URI -> (MethodHandle -> IO a) -> IO a
- whichMethodPath :: URI -> IO (Maybe FilePath)
- openMethod :: FilePath -> IO MethodHandle
- closeMethod :: MethodHandle -> IO ExitCode
- recvStatus :: MethodHandle -> IO Status
- sendCommand :: MethodHandle -> Command -> IO ()
- getLastModified :: FilePath -> IO (Maybe UTCTime)
- simpleFetch :: [ConfigItem] -> URI -> FilePath -> Maybe UTCTime -> IO Bool
- fetch :: FetchCallbacks -> [ConfigItem] -> URI -> FilePath -> Maybe UTCTime -> IO Bool
- data FetchCallbacks = FetchCallbacks {
- logCB :: Message -> IO ()
- statusCB :: URI -> Message -> IO ()
- uriStartCB :: URI -> Maybe Integer -> Maybe UTCTime -> Maybe Integer -> IO ()
- uriDoneCB :: URI -> Maybe Integer -> Maybe UTCTime -> Maybe Integer -> Maybe FilePath -> Hashes -> Bool -> IO ()
- uriFailureCB :: URI -> Message -> IO ()
- generalFailureCB :: Message -> IO ()
- authorizationRequiredCB :: Site -> IO (Maybe (User, Password))
- mediaFailureCB :: Media -> Drive -> IO ()
- debugCB :: String -> IO ()
- emptyFetchCallbacks :: FetchCallbacks
- cliFetchCallbacks :: FetchCallbacks
- data Command
- data Status
- = Capabilities {
- version :: String
- singleInstance :: Bool
- preScan :: Bool
- pipeline :: Bool
- sendConfig :: Bool
- needsCleanup :: Bool
- localOnly :: Bool
- | LogMsg Message
- | Status URI Message
- | URIStart { }
- | URIDone { }
- | URIFailure { }
- | GeneralFailure Message
- | AuthorizationRequired Site
- | MediaFailure Media Drive
- = Capabilities {
- type Message = String
- type Site = String
- type User = String
- type Password = String
- type Media = String
- type Drive = String
- type Header = (String, String)
- type ConfigItem = (String, String)
Documentation
withMethodPath :: FilePath -> (MethodHandle -> IO a) -> IO a Source #
withMethod - run |methodPath| bracketed with openMethod/closeMethod. |f| gets the open handle.
whichMethodPath :: URI -> IO (Maybe FilePath) Source #
whichMethodBinary - find the method executable associated with a URI throws an exception on failure
openMethod :: FilePath -> IO MethodHandle Source #
closeMethod :: MethodHandle -> IO ExitCode Source #
recvStatus :: MethodHandle -> IO Status Source #
sendCommand :: MethodHandle -> Command -> IO () Source #
simpleFetch :: [ConfigItem] -> URI -> FilePath -> Maybe UTCTime -> IO Bool Source #
fetch :: FetchCallbacks -> [ConfigItem] -> URI -> FilePath -> Maybe UTCTime -> IO Bool Source #
fetch a single item, show console output see also: getLastModified
data FetchCallbacks Source #
FetchCallbacks | |
|
emptyFetchCallbacks :: FetchCallbacks Source #
set of callbacks which do nothing. suitable for non-interactive usage. In the case authorization is required, no credentials will be supplied and the download should abort.
type ConfigItem = (String, String) Source #