- backupByRenaming :: FilePath -> IO ()
- backupByCopying :: FilePath -> IO ()
- copyFileOrUrl :: [DarcsFlag] -> FilePath -> FilePath -> Cachable -> IO ()
- speculateFileOrUrl :: String -> FilePath -> IO ()
- copyFilesOrUrls :: [DarcsFlag] -> FilePath -> [String] -> FilePath -> Cachable -> IO ()
- copyLocal :: [DarcsFlag] -> String -> FilePath -> IO ()
- cloneFile :: FilePath -> FilePath -> IO ()
- cloneTree :: FilePath -> FilePath -> IO ()
- cloneTreeExcept :: [FilePath] -> FilePath -> FilePath -> IO ()
- clonePartialsTree :: FilePath -> FilePath -> [FilePath] -> IO ()
- clonePaths :: FilePath -> FilePath -> [FilePath] -> IO ()
- fetchFilePS :: String -> Cachable -> IO ByteString
- fetchFileLazyPS :: String -> Cachable -> IO ByteString
- gzFetchFilePS :: String -> Cachable -> IO ByteString
- sendEmail :: String -> String -> String -> String -> String -> String -> IO ()
- generateEmail :: Handle -> String -> String -> String -> String -> Doc -> IO ()
- sendEmailDoc :: String -> String -> String -> String -> String -> Maybe (Doc, Doc) -> Doc -> IO ()
- resendEmail :: String -> String -> ByteString -> IO ()
- signString :: [DarcsFlag] -> Doc -> IO Doc
- verifyPS :: [DarcsFlag] -> ByteString -> IO (Maybe ByteString)
- execDocPipe :: String -> [String] -> Doc -> IO Doc
- execPipeIgnoreError :: String -> [String] -> Doc -> IO Doc
- getTermNColors :: IO Int
- pipeDoc :: String -> [String] -> Doc -> IO ExitCode
- pipeDocSSH :: String -> [String] -> Doc -> IO ExitCode
- execSSH :: String -> String -> IO ExitCode
- remoteDarcsCmd :: [DarcsFlag] -> String
- maybeURLCmd :: String -> String -> IO (Maybe String)
- data Cachable
- = Cachable
- | Uncachable
- | MaxAge !CInt
- viewDoc :: Doc -> IO ()
- viewDocWith :: Printers -> Doc -> IO ()
- sendmailPath :: IO String
- diffProgram :: IO String
- darcsProgram :: IO String
Documentation
backupByRenaming :: FilePath -> IO ()Source
backupByCopying :: FilePath -> IO ()Source
fetchFilePS :: String -> Cachable -> IO ByteStringSource
fetchFile fileOrUrl cache
returns the content of its argument
(either a file or an URL). If it has to download an url, then it
will use a cache as required by its second argument.
fetchFileLazyPS :: String -> Cachable -> IO ByteStringSource
fetchFileLazyPS fileOrUrl cache
lazily reads the content of
its argument (either a file or an URL). Warning: this function may
constitute a fd leak; make sure to force consumption of file contents
to avoid that.
gzFetchFilePS :: String -> Cachable -> IO ByteStringSource
:: String | from |
-> String | to |
-> String | subject |
-> String | cc |
-> String | send command |
-> Maybe (Doc, Doc) | (content,bundle) |
-> Doc | body |
-> IO () |
Send an email, optionally containing a patch bundle (more precisely, its description and the bundle itself)
resendEmail :: String -> String -> ByteString -> IO ()Source
verifyPS :: [DarcsFlag] -> ByteString -> IO (Maybe ByteString)Source
execSSH :: String -> String -> IO ExitCodeSource
Run a command on a remote location without passing it any input or reading its output. Return its ExitCode
remoteDarcsCmd :: [DarcsFlag] -> StringSource
darcsProgram :: IO StringSource
Get the name of the darcs executable (as supplied by getProgName
)