Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- sendEmail :: String -> String -> String -> String -> Maybe String -> String -> IO ()
- generateEmail :: Handle -> String -> String -> String -> String -> Doc -> IO ()
- sendEmailDoc :: String -> String -> String -> String -> Maybe String -> Maybe (Doc, Doc) -> Doc -> IO ()
- signString :: Sign -> Doc -> IO Doc
- verifyPS :: Verify -> ByteString -> IO (Maybe ByteString)
- execDocPipe :: String -> [String] -> Doc -> IO Doc
- pipeDoc :: String -> [String] -> Doc -> IO ExitCode
- pipeDocSSH :: Compression -> SshFilePath -> [String] -> Doc -> IO ExitCode
- viewDoc :: Doc -> IO ()
- viewDocWith :: Printers -> Doc -> IO ()
- checkDefaultSendmail :: IO ()
- diffProgram :: IO String
- darcsProgram :: IO String
- editText :: String -> ByteString -> IO ByteString
- editFile :: FilePathLike p => p -> IO (ExitCode, Bool)
- setDarcsEncodings :: IO ()
Documentation
:: String | from |
-> String | to |
-> String | subject |
-> String | cc |
-> Maybe 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)
verifyPS :: Verify -> ByteString -> IO (Maybe ByteString) Source #
pipeDocSSH :: Compression -> SshFilePath -> [String] -> Doc -> IO ExitCode Source #
checkDefaultSendmail :: IO () Source #
diffProgram :: IO String Source #
darcsProgram :: IO String Source #
Get the name of the darcs executable (as supplied by getExecutablePath
)
editText :: String -> ByteString -> IO ByteString Source #
editFile :: FilePathLike p => p -> IO (ExitCode, Bool) Source #
editFile f
lets the user edit a file which could but does not need to
already exist. This function returns the exit code from the text editor and a
flag indicating if the user made any changes.
setDarcsEncodings :: IO () Source #
On Posix systems, GHC by default uses the user's locale encoding to
determine how to decode/encode the raw byte sequences in the Posix API
to/from String
. It also uses certain special variants of this
encoding to determine how to handle encoding errors.
See GHC.IO.Encoding for details.
In particular, the default variant used for command line arguments and
environment variables is /ROUNDTRIP, which means that any/ byte sequence
can be decoded and re-encoded w/o failure or loss of information. To
enable this, GHC uses code points that are outside the range of the regular
unicode set. This is what you get with getFileSystemEncoding
.
We need to preserve the raw bytes e.g. for file names passed in by the user and also when reading file names from disk; also when re-generating files from patches, and when we display them to the user.
So we want to use this encoding variant for *all* IO and for (almost) all
conversions between raw bytes and String
s. The encoding used for IO from
and to handles is controlled by setLocaleEncoding
which we use here to
make it equal to the //ROUNDTRIP variant.
setDarcsEncoding
should be called before the
first time any darcs operation is run, and again if anything else might have
set those encodings to different values.
Note that it isn't thread-safe and has a global effect on your program.
On Windows, this function does (and should) not do anything.