Copyright | Copyright (C) 2009 John MacFarlane, Gwern Branwen |
---|---|
License | BSD 3 |
Maintainer | John MacFarlane <jgm@berkeley.edu> |
Stability | alpha |
Portability | portable |
Safe Haskell | Safe-Inferred |
Language | Haskell98 |
Utility functions for running external processes.
- runShellCommand :: FilePath -> Maybe [(String, String)] -> String -> [String] -> IO (ExitCode, ByteString, ByteString)
- mergeContents :: (String, ByteString) -> (String, ByteString) -> (String, ByteString) -> IO (Bool, String)
- hashsMatch :: Eq a => [a] -> [a] -> Bool
- escapeRegexSpecialChars :: String -> String
- parseMatchLine :: String -> SearchMatch
- splitEmailAuthor :: String -> (Maybe String, String)
- ensureFileExists :: FilePath -> FilePath -> IO ()
- regSearchFiles :: FilePath -> [String] -> String -> IO [String]
- regsSearchFile :: [String] -> FilePath -> [String] -> String -> IO [String]
- withSanityCheck :: FilePath -> [FilePath] -> FilePath -> IO b -> IO b
- grepSearchRepo :: (FilePath -> IO [String]) -> FilePath -> SearchQuery -> IO [SearchMatch]
- withVerifyDir :: FilePath -> IO a -> IO a
- encodeArg :: String -> String
Documentation
:: FilePath | Working directory |
-> Maybe [(String, String)] | Environment |
-> String | Command |
-> [String] | Arguments |
-> IO (ExitCode, ByteString, ByteString) |
Run shell command and return error status, standard output, and error output. Assumes UTF-8 locale. Note that this does not actually go through /bin/sh!
:: (String, ByteString) | (label, contents) of edited version |
-> (String, ByteString) | (label, contents) of original revision |
-> (String, ByteString) | (label, contents) of latest version |
-> IO (Bool, String) | (were there conflicts?, merged contents) |
Do a three way merge, using either git merge-file or RCS merge. Assumes
that either git
or merge
is in the system path. Assumes UTF-8 locale.
hashsMatch :: Eq a => [a] -> [a] -> Bool Source
A number of VCS systems uniquely identify a particular revision or change via a
cryptographic hash of some sort. These hashs can be very long, and so systems like
Git and Darcs don't require the entire hash - a *unique prefix*. Thus a definition
of hash equality is ==
, certainly, but also simply whether either is a prefix of the
other. If both are reasonably long, then the likelihood the shorter one is not a unique
prefix of the longer (that is, clashes with another hash) is small.
The burden of proof is on the caller to not pass a uselessly short short-hash like '1', however.
parseMatchLine :: String -> SearchMatch Source
A parser function. This is intended for use on strings which are output by grep programs or programs which mimic the standard grep output - which uses colons as delimiters and has 3 fields: the filename, the line number, and then the matching line itself. Note that this is for use on only strings meeting that format - if it goes "file:match", this will throw a pattern-match exception.
parseMatchLine "foo:10:bar baz quux" ~> SearchMatch {matchResourceName = "foo", matchLineNumber = 10, matchLine = "bar baz quux"}
splitEmailAuthor :: String -> (Maybe String, String) Source
Our policy is: if the input is clearly a "name <e@mail.com>" input, then we return "(Just Address, Name)"
If there is no <
in the input, then it clearly can't be of that format, and so we just return "(Nothing, Name)"
splitEmailAuthor "foo bar baz@gmail.com" ~> (Nothing,"foo bar baz@gmail.com") splitEmailAuthor "foo bar <baz@gmail.com>" ~> (Just "baz@gmail.com","foo bar")
ensureFileExists :: FilePath -> FilePath -> IO () Source
If name doesn't exist in repo or is not a file, throw NotFound
exception.
regSearchFiles :: FilePath -> [String] -> String -> IO [String] Source
Search multiple files with a single regexp. This calls out to grep, and so supports the regular expressions grep does.
regsSearchFile :: [String] -> FilePath -> [String] -> String -> IO [String] Source
Search a single file with multiple regexps.
withSanityCheck :: FilePath -> [FilePath] -> FilePath -> IO b -> IO b Source
Check that the filename/location is within the given repo, and not inside
any of the (relative) paths in excludes
. Create the directory if needed.
If everything checks out, then perform the specified action.
grepSearchRepo :: (FilePath -> IO [String]) -> FilePath -> SearchQuery -> IO [SearchMatch] Source
Uses grep to search a file-based repository. Note that this calls out to grep; and so
is generic over repos like git or darcs-based repos. (The git FileStore instance doesn't
use this because git has builtin grep functionality.)
Expected usage is to specialize this function with a particular backend's index
.
withVerifyDir :: FilePath -> IO a -> IO a Source
we don't actually need the contents, just want to check that the directory exists and we have enough permissions