Safe Haskell | None |
---|---|
Language | Haskell2010 |
- 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 :: Sign -> Doc -> IO Doc
- verifyPS :: Verify -> ByteString -> IO (Maybe ByteString)
- execDocPipe :: RenderMode -> String -> [String] -> Doc -> IO Doc
- execPipeIgnoreError :: RenderMode -> String -> [String] -> Doc -> IO Doc
- pipeDoc :: RenderMode -> String -> [String] -> Doc -> IO ExitCode
- pipeDocSSH :: Compression -> RenderMode -> SshFilePath -> [String] -> Doc -> IO ExitCode
- viewDoc :: Doc -> IO ()
- viewDocWith :: Printers -> RenderMode -> Doc -> IO ()
- haveSendmail :: IO Bool
- sendmailPath :: IO String
- diffProgram :: IO String
- darcsProgram :: IO String
- editText :: String -> ByteString -> IO ByteString
- editFile :: FilePathLike p => p -> IO (ExitCode, Bool)
- catchall :: IO a -> IO a -> IO a
- setDarcsEncodings :: IO ()
- getSystemEncoding :: IO String
- isUTF8Locale :: String -> Bool
Documentation
:: 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 :: Verify -> ByteString -> IO (Maybe ByteString) Source #
execDocPipe :: RenderMode -> String -> [String] -> Doc -> IO Doc Source #
execPipeIgnoreError :: RenderMode -> String -> [String] -> Doc -> IO Doc Source #
pipeDocSSH :: Compression -> RenderMode -> SshFilePath -> [String] -> Doc -> IO ExitCode Source #
viewDocWith :: Printers -> RenderMode -> Doc -> IO () Source #
haveSendmail :: IO Bool Source #
sendmailPath :: IO String 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 #
In some environments, darcs requires that certain global GHC library variables that control the encoding used in internal translations are set to specific values.
setDarcsEncoding
enforces those settings, and 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.
The current behaviour of this function is as follows, though this may change in future:
Encodings are only set on GHC 7.4 and up, on any non-Windows platform.
Two encodings are set, both to GHC.IO.Encoding.char8
:
GHC.IO.Encoding.setFileSystemEncoding
and GHC.IO.Encoding.setForeignEncoding
.
Prevent HLint from warning us about a redundant do if the macro isn't defined:
isUTF8Locale :: String -> Bool Source #
isUTF8
checks if an encoding is UTF-8 (or ascii, since it is a
subset of UTF-8).