-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | a distributed, interactive, smart revision control system -- -- Darcs is a free, open source revision control system. It is: -- -- -- -- This smartness lets you respond to changing demands in ways that would -- otherwise not be possible. Learn more about spontaneous branches with -- darcs. @package darcs @version 2.8.4 module URL.Request data UrlRequest UrlRequest :: String -> FilePath -> Cachable -> Priority -> UrlRequest url :: UrlRequest -> String file :: UrlRequest -> FilePath cachable :: UrlRequest -> Cachable priority :: UrlRequest -> Priority data Cachable Cachable :: Cachable Uncachable :: Cachable MaxAge :: !CInt -> Cachable data UrlState UrlState :: Map String (FilePath, [FilePath], Cachable) -> Q String -> Int -> String -> UrlState inProgress :: UrlState -> Map String (FilePath, [FilePath], Cachable) waitToStart :: UrlState -> Q String pipeLength :: UrlState -> Int randomJunk :: UrlState -> String data Q a Q :: [a] -> [a] -> Q a readQ :: Q a -> Maybe (a, Q a) insertQ :: a -> Q a -> Q a pushQ :: a -> Q a -> Q a deleteQ :: Eq a => a -> Q a -> Q a elemQ :: Eq a => a -> Q a -> Bool emptyQ :: Q a nullQ :: Q a -> Bool data Priority High :: Priority Low :: Priority -- | Data type to represent a connection error. The following are the codes -- from libcurl which map to each of the constructors: * 6 -> -- CouldNotResolveHost : The remote host was not resolved. * 7 -> -- CouldNotConnectToServer : Failed to connect() to host or proxy. * 28 -- -> OperationTimeout: the specified time-out period was reached. data ConnectionError CouldNotResolveHost :: ConnectionError CouldNotConnectToServer :: ConnectionError OperationTimeout :: ConnectionError instance Show Cachable instance Eq Cachable instance Eq Priority instance Eq ConnectionError instance Read ConnectionError instance Show ConnectionError module Darcs.Witnesses.Show data ShowDict a ShowDictClass :: ShowDict a ShowDictRecord :: (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> ShowDict a showD :: ShowDict a -> a -> String showListD :: ShowDict a -> [a] -> ShowS showsPrecD :: ShowDict a -> Int -> a -> ShowS class Show1 a showDict1 :: Show1 a => ShowDict (a x) class Show2 a showDict2 :: Show2 a => ShowDict (a x y) show1 :: Show1 a => a x -> String showsPrec1 :: Show1 a => Int -> a x -> ShowS show2 :: Show2 a => a x y -> String showsPrec2 :: Show2 a => Int -> a x y -> ShowS showOp2 :: (Show2 a, Show2 b) => Int -> String -> Int -> a w x -> b y z -> String -> String appPrec :: Int module Darcs.Patch.OldDate -- | Read/interpret a date string, assuming UTC if timezone is not -- specified in the string readUTCDate :: String -> CalendarTime showIsoDateTime :: CalendarTime -> String module Darcs.Patch.Prim.V3.ObjectMap newtype UUID UUID :: ByteString -> UUID type Location = (UUID, ByteString) data Object (m :: * -> *) Directory :: DirContent -> Object Blob :: (m ByteString) -> !Hash -> Object data ObjectMap (m :: * -> *) ObjectMap :: (UUID -> m (Maybe (Object m))) -> (UUID -> Object m -> m (ObjectMap m)) -> m [UUID] -> ObjectMap getObject :: ObjectMap -> UUID -> m (Maybe (Object m)) putObject :: ObjectMap -> UUID -> Object m -> m (ObjectMap m) listObjects :: ObjectMap -> m [UUID] type DirContent = Map ByteString UUID instance Eq UUID instance Ord UUID instance Show UUID module Darcs.Patch.Format -- | Showing and reading lists of patches This class allows us to control -- how lists of patches are formatted on disk. For legacy reasons V1 -- patches have their own special treatment (see ListFormat). -- Other patch types use the default format which just puts them in a -- sequence without separators or any prelude/epilogue. -- -- This means that 'FL (FL p)' etc would be ambiguous, so there are no -- instances for 'FL p' or other list types. class PatchListFormat p where patchListFormat = ListFormatDefault patchListFormat :: PatchListFormat p => ListFormat p -- | This type is used to tweak the way that lists of p are shown -- for a given Patch type p. It is needed to maintain -- backwards compatibility for V1 and V2 patches. data ListFormat (p :: * -> * -> *) -- | Show and read lists without braces. ListFormatDefault :: ListFormat -- | Show lists with a single layer of braces around the outside, except -- for singletons which have no braces. Read with arbitrary nested braces -- and parens and flatten them out. ListFormatV1 :: ListFormat -- | Show lists without braces Read with arbitrary nested parens and -- flatten them out. ListFormatV2 :: ListFormat data FileNameFormat OldFormat :: FileNameFormat NewFormat :: FileNameFormat module Encoding -- | Encode a Unicode String into a ByteString suitable for -- the current console. encode :: String -> IO ByteString -- | Convert a ByteString from the console's encoding into a Unicode -- String. decode :: ByteString -> IO String module Darcs.Patch.RegChars -- | regChars returns a filter function that tells if a char is a -- member of the regChar expression or not. The regChar expression is -- basically a set of chars, but it can contain ranges with use of the -- - (dash), and it can also be specified as a complement set by -- prefixing with ^ (caret). The dash and caret, as well as the -- backslash, can all be escaped with a backslash to suppress their -- special meaning. -- -- NOTE: The . (dot) is allowed to be escaped. It has no special -- meaning if it is not escaped, but the default filename_toks -- in Darcs.Commands.Replace uses an escaped dot (WHY?). regChars :: String -> (Char -> Bool) module IsoDate -- | The current time in the format returned by showIsoDateTime getIsoDateTime :: IO String -- | Read/interpret a date string, assuming local timezone if not specified -- in the string readLocalDate :: String -> CalendarTime -- | Read/interpret a date string, assuming UTC if timezone is not -- specified in the string (see readDate) Warning! This errors out -- if we fail to interpret the date readUTCDate :: String -> CalendarTime -- | Parse a date string, assuming a default timezone if the date string -- does not specify one. The date formats understood are those of -- showIsoDateTime and dateTime parseDate :: Int -> String -> Either ParseError MCalendarTime -- | Return the local timezone offset from UTC in seconds getLocalTz :: IO Int -- | In English, either a date followed by a time, or vice-versa, e.g, -- -- -- -- See englishDate and englishTime Uses its first argument -- as now, i.e. the time relative to which yesterday, -- today etc are to be interpreted englishDateTime :: CalendarTime -> CharParser a CalendarTime -- | English expressions for intervals of time, -- -- englishInterval :: CalendarTime -> CharParser a TimeInterval -- | Durations in English that begin with the word "last", E.g. "last 4 -- months" is treated as the duration between 4 months ago and now englishLast :: CalendarTime -> CharParser a (CalendarTime, CalendarTime) -- | Intervals in ISO 8601, e.g., -- -- -- -- See iso8601Duration iso8601Interval :: Int -> CharParser a (Either TimeDiff (MCalendarTime, MCalendarTime)) -- | Durations in ISO 8601, e.g., -- -- iso8601Duration :: CharParser a TimeDiff -- | Convert a date string into ISO 8601 format (yyyymmdd variant) assuming -- local timezone if not specified in the string Warning! This errors out -- if we fail to interpret the date cleanLocalDate :: String -> String -- | Set a calendar to UTC time any eliminate any inconsistencies within -- (for example, where the weekday is given as Thursday, but -- this does not match what the numerical date would lead one to expect) resetCalendar :: CalendarTime -> CalendarTime -- | An MCalenderTime is an underspecified CalendarTime It -- is used for parsing dates. For example, if you want to parse the date -- '4 January', it may be useful to underspecify the year by setting it -- to Nothing. This uses almost the same fields as -- CalendarTime, a notable exception being that we introduce -- mctWeek to indicate if a weekday was specified or not data MCalendarTime MCalendarTime :: Maybe Int -> Maybe Month -> Maybe Int -> Maybe Int -> Maybe Int -> Maybe Int -> Maybe Integer -> Maybe Day -> Maybe Int -> Maybe String -> Maybe Int -> Maybe Bool -> Bool -> MCalendarTime mctYear :: MCalendarTime -> Maybe Int mctMonth :: MCalendarTime -> Maybe Month mctDay :: MCalendarTime -> Maybe Int mctHour :: MCalendarTime -> Maybe Int mctMin :: MCalendarTime -> Maybe Int mctSec :: MCalendarTime -> Maybe Int mctPicosec :: MCalendarTime -> Maybe Integer mctWDay :: MCalendarTime -> Maybe Day mctYDay :: MCalendarTime -> Maybe Int mctTZName :: MCalendarTime -> Maybe String mctTZ :: MCalendarTime -> Maybe Int mctIsDST :: MCalendarTime -> Maybe Bool mctWeek :: MCalendarTime -> Bool subtractFromMCal :: TimeDiff -> MCalendarTime -> MCalendarTime addToMCal :: TimeDiff -> MCalendarTime -> MCalendarTime -- | Trivially convert a CalendarTime to a fully specified -- MCalendarTime (note that this sets the mctWeek flag to -- False toMCalendarTime :: CalendarTime -> MCalendarTime -- | Returns the first CalendarTime that falls within a -- MCalendarTime This is only unsafe in the sense that it plugs in -- default values for fields that have not been set, e.g. -- January for the month or 0 for the seconds field. -- Maybe we should rename it something happier. See also -- resetCalendar unsafeToCalendarTime :: MCalendarTime -> CalendarTime -- | Zero the time fields of a CalendarTime unsetTime :: CalendarTime -> CalendarTime type TimeInterval = (Maybe CalendarTime, Maybe CalendarTime) instance Show MCalendarTime module DateMatcher -- | parseDateMatcher s return the first matcher in -- getMatchers that can parse s parseDateMatcher :: String -> IO (CalendarTime -> Bool) -- | A DateMatcher combines a potential parse for a date string with -- a matcher function that operates on a given date. We use an -- existential type on the matcher to allow the date string to either be -- interpreted as a point in time or as an interval. data DateMatcher DM :: String -> (Either ParseError d) -> (d -> CalendarTime -> Bool) -> DateMatcher -- | getMatchers d returns the list of matchers that will -- be applied on d. If you wish to extend the date parsing code, -- this will likely be the function that you modify to do so. getMatchers :: String -> IO [DateMatcher] -- | XXX: Perhaps a word of explanation here [WL] module Ratified -- | The readFile function reads a file and returns the contents of -- the file as a string. The file is read lazily, on demand, as with -- getContents. readFile :: FilePath -> IO String -- | Computation hGetContents hdl returns the list of -- characters corresponding to the unread portion of the channel or file -- managed by hdl, which is put into an intermediate state, -- semi-closed. In this state, hdl is effectively closed, -- but items are read from hdl on demand and accumulated in a -- special list returned by hGetContents hdl. -- -- Any operation that fails because a handle is closed, also fails if a -- handle is semi-closed. The only exception is hClose. A -- semi-closed handle becomes closed: -- -- -- -- Once a semi-closed handle becomes closed, the contents of the -- associated list becomes fixed. The contents of this final list is only -- partially specified: it will contain at least all the items of the -- stream that were evaluated prior to the handle becoming closed. -- -- Any I/O errors encountered while a handle is semi-closed are simply -- discarded. -- -- This operation may fail with: -- -- hGetContents :: Handle -> IO String module Darcs.Witnesses.Unsafe unsafeCoerceP :: a x y -> a b c unsafeCoercePStart :: a x1 y -> a x2 y unsafeCoercePEnd :: a x y1 -> a x y2 unsafeCoerceP2 :: t w x y z -> t a b c d unsafeCoerceP1 :: a x -> a y -- | This modules provides rudimentary natural language generation (NLG) -- utilities. That is, generating natural language from a machine -- representation. Initially, only English is supported at all. -- Representations are implemented for: -- -- module English -- |
--   englishNum 0 (Noun "watch") "" == "watches"
--   englishNum 1 (Noun "watch") "" == "watch"
--   englishNum 2 (Noun "watch") "" == "watches"
--   
englishNum :: Countable n => Int -> n -> ShowS -- | Things that have a plural and singular spelling class Countable a plural :: Countable a => a -> ShowS singular :: Countable a => a -> ShowS -- | This only distinguishes between nouns with a final -ch, and nouns -- which do not. More irregular nouns will just need to have their own -- type -- --
--   plural (Noun "batch") "" == "batches"
--   plural (Noun "bat")   "" == "bats"
--   plural (Noun "mouse") "" == "mouses" -- :-(
--   
newtype Noun Noun :: String -> Noun data Pronoun It :: Pronoun -- |
--   singular This (Noun "batch") "" == "this batch"
--   plural   This (Noun "batch") "" == "these batches"
--   
data This This :: Noun -> This -- | Given a list of things, combine them thusly: -- --
--   orClauses ["foo", "bar", "baz"] == "foo, bar or baz"
--   
andClauses :: [String] -> String -- | Given a list of things, combine them thusly: -- --
--   orClauses ["foo", "bar", "baz"] == "foo, bar or baz"
--   
orClauses :: [String] -> String -- | As intersperse, with a different separator for the last | -- interspersal. intersperseLast :: String -> String -> [String] -> String presentParticiple :: String -> String instance Countable This instance Countable Pronoun instance Countable Noun module Workaround -- | renameFile old new changes the name of an existing -- file system object from old to new. If the new -- object already exists, it is atomically replaced by the old -- object. Neither path may refer to an existing directory. A conformant -- implementation need not support renaming files in all situations (e.g. -- renaming across different physical devices), but the constraints must -- be documented. -- -- The operation may fail with: -- -- renameFile :: FilePath -> FilePath -> IO () setExecutable :: FilePath -> Bool -> IO () -- | If the operating system has a notion of current directories, -- getCurrentDirectory returns an absolute path to the current -- directory of the calling process. -- -- The operation may fail with: -- -- -- -- Note that in a concurrent program, the current directory is global -- state shared between all threads of the process. When using filesystem -- operations from multiple threads, it is therefore highly recommended -- to use absolute rather than relative FilePaths. getCurrentDirectory :: IO FilePath -- | installHandler int handler iset calls sigaction to -- install an interrupt handler for signal int. If -- handler is Default, SIG_DFL is installed; -- if handler is Ignore, SIG_IGN is installed; -- if handler is Catch action, a handler is installed -- which will invoke action in a new thread when (or shortly -- after) the signal is received. If iset is Just s, -- then the sa_mask of the sigaction structure is set -- to s; otherwise it is cleared. The previously installed -- signal handler for int is returned installHandler :: Signal -> Handler -> Maybe SignalSet -> IO Handler -- | raiseSignal int calls kill to signal the current -- process with interrupt signal int. raiseSignal :: Signal -> IO () -- | The actions to perform when a signal is received. data Handler :: * Default :: Handler Ignore :: Handler Catch :: IO () -> Handler CatchOnce :: IO () -> Handler type Signal = CInt sigINT :: CInt sigHUP :: CInt sigABRT :: CInt sigALRM :: CInt sigTERM :: CInt sigPIPE :: CInt module Darcs.Witnesses.Eq -- | EqCheck is used to pass around evidence (or lack thereof) of -- two witness types being equal. data EqCheck a b IsEq :: EqCheck a a NotEq :: EqCheck a b -- | An witness aware equality class. A minimal definition defines any one -- of unsafeCompare, =\/= and =/\=. class MyEq p where unsafeCompare a b = IsEq == (a =/\= unsafeCoerceP b) a =\/= b | unsafeCompare a b = unsafeCoerceP IsEq | otherwise = NotEq a =/\= b | IsEq == (a =\/= unsafeCoerceP b) = unsafeCoerceP IsEq | otherwise = NotEq unsafeCompare :: MyEq p => p a b -> p c d -> Bool (=\/=) :: MyEq p => p a b -> p a c -> EqCheck b c (=/\=) :: MyEq p => p a c -> p b c -> EqCheck a b isIsEq :: EqCheck a b -> Bool instance Show (EqCheck a b) instance Eq (EqCheck a b) module Darcs.SignalHandler withSignalsHandled :: IO a -> IO a withSignalsBlocked :: IO a -> IO a catchInterrupt :: IO a -> IO a -> IO a catchNonSignal :: IO a -> (SomeException -> IO a) -> IO a tryNonSignal :: IO a -> IO (Either SomeException a) stdoutIsAPipe :: IO Bool instance Typeable SignalException instance Show SignalException instance Exception SignalException module Darcs.Witnesses.Sealed data Sealed a Sealed :: a x -> Sealed a seal :: a x -> Sealed a unseal :: (forall x. a x -> b) -> Sealed a -> b mapSeal :: (forall x. a x -> b x) -> Sealed a -> Sealed b unsafeUnseal :: Sealed a -> a x unsafeUnsealFlipped :: FlippedSeal a y -> a x y unsafeUnseal2 :: Sealed2 a -> a x y data Sealed2 a Sealed2 :: !(a x y) -> Sealed2 a seal2 :: a x y -> Sealed2 a unseal2 :: (forall x y. a x y -> b) -> Sealed2 a -> b mapSeal2 :: (forall x y. a x y -> b x y) -> Sealed2 a -> Sealed2 b data FlippedSeal a y FlippedSeal :: !(a x y) -> FlippedSeal a y flipSeal :: a x y -> FlippedSeal a y unsealFlipped :: (forall x y. a x y -> b) -> FlippedSeal a z -> b mapFlipped :: (forall x. a x y -> b x z) -> FlippedSeal a y -> FlippedSeal b z unsealM :: Monad m => m (Sealed a) -> (forall x. a x -> m b) -> m b liftSM :: Monad m => (forall x. a x -> b) -> m (Sealed a) -> m b -- | Gap abstracts over FreeLeft and FreeRight for -- code constructing these values class Gap w emptyGap :: Gap w => (forall x. p x x) -> w p freeGap :: Gap w => (forall x y. p x y) -> w p joinGap :: Gap w => (forall x y z. p x y -> q y z -> r x z) -> w p -> w q -> w r -- | 'FreeLeft p' is 'forall x . exists y . p x y' In other words the -- caller is free to specify the left witness, and then the right witness -- is an existential. Note that the order of the type constructors is -- important for ensuring that y is dependent on the x -- that is supplied. This is why Stepped is needed, rather than -- writing the more obvious 'Sealed (Poly p)' which would notionally have -- the same quantification of the type witnesses. data FreeLeft p -- | Unwrap a FreeLeft value unFreeLeft :: FreeLeft p -> Sealed (p x) -- | 'FreeLeft p' is 'forall y . exists x . p x y' In other words the -- caller is free to specify the right witness, and then the left witness -- is an existential. Note that the order of the type constructors is -- important for ensuring that x is dependent on the y -- that is supplied. data FreeRight p -- | Unwrap a FreeRight value unFreeRight :: FreeRight p -> FlippedSeal p x instance Gap FreeRight instance Gap FreeLeft instance Show2 a => Show (Sealed2 a) instance Show1 a => Show (Sealed a) instance MyEq a => Eq (Sealed (a x)) -- | This was originally Tomasz Zielonka's AtExit module, slightly -- generalised to include global variables. Here, we attempt to cover -- broad, global features, such as exit handlers. These features slightly -- break the Haskellian purity of darcs, in favour of programming -- convenience. module Darcs.Global -- | Registers an IO action to run just before darcs exits. Useful for -- removing temporary files and directories, for example. Referenced in -- Issue1914. atexit :: IO () -> IO () withAtexit :: IO a -> IO a data SshSettings SshSettings :: String -> String -> String -> SshSettings ssh :: SshSettings -> String scp :: SshSettings -> String sftp :: SshSettings -> String defaultSsh :: SshSettings timingsMode :: Bool setTimingsMode :: IO () whenDebugMode :: IO () -> IO () withDebugMode :: (Bool -> IO a) -> IO a setDebugMode :: IO () debugMessage :: String -> IO () debugFail :: String -> IO a putTiming :: IO () addCRCWarning :: FilePath -> IO () getCRCWarnings :: IO [FilePath] resetCRCWarnings :: IO () addBadSource :: String -> IO () getBadSourcesList :: IO [String] isBadSource :: IO (String -> Bool) darcsdir :: String isReachableSource :: IO (String -> Bool) addReachableSource :: String -> IO () windows :: Bool instance Show SshSettings instance Eq SshSettings module Darcs.Patch.MatchData data PatchMatch PatternMatch :: String -> PatchMatch patchMatch :: String -> PatchMatch instance Eq PatchMatch instance Show PatchMatch -- | Utility functions for tracking progress of long-running actions. module Progress -- | beginTedious k starts a tedious process and registers it in -- _progressData with the key k. A tedious process is one -- for which we want a progress indicator. -- -- Wouldn't it be safer if it had type String -> IO ProgressDataKey, -- so that we can ensure there is no collision? What happens if you call -- beginTedious twice with the same string, without calling endTedious in -- the meantime? beginTedious :: String -> IO () -- | endTedious k unregisters the tedious process with key -- k, printing Done if such a tedious process exists. endTedious :: String -> IO () tediousSize :: String -> Int -> IO () debugMessage :: String -> IO () debugFail :: String -> IO a withoutProgress :: IO a -> IO a progress :: String -> a -> a progressKeepLatest :: String -> a -> a finishedOne :: String -> String -> a -> a finishedOneIO :: String -> String -> IO () progressList :: String -> [a] -> [a] -- | XXX: document this constant minlist :: Int setProgressMode :: Bool -> IO () module Exec exec :: String -> [String] -> Redirects -> IO ExitCode execInteractive :: String -> String -> IO ExitCode withoutNonBlock :: IO a -> IO a type Redirects = (Redirect, Redirect, Redirect) data Redirect AsIs :: Redirect Null :: Redirect File :: FilePath -> Redirect Stdout :: Redirect data ExecException ExecException :: String -> [String] -> Redirects -> String -> ExecException instance Typeable ExecException instance Show Redirect instance Show ExecException instance Exception ExecException -- | GZIp and MMap IO for ByteStrings, encoding utilities, and -- miscellaneous functions for Data.ByteString module ByteStringUtils -- | Do something with the internals of a PackedString. Beware of altering -- the contents! unsafeWithInternals :: ByteString -> (Ptr Word8 -> Int -> IO a) -> IO a -- | Decodes a ByteString containing UTF-8 to a String. -- Decoding errors are flagged with the U+FFFD character. unpackPSFromUTF8 :: ByteString -> String packStringToUTF8 :: String -> ByteString -- | Read an entire file, which may or may not be gzip compressed, directly -- into a ByteString. gzReadFilePS :: FilePath -> IO ByteString -- | Like readFilePS, this reads an entire file directly into a -- ByteString, but it is even more efficient. It involves directly -- mapping the file to memory. This has the advantage that the contents -- of the file never need to be copied. Also, under memory pressure the -- page may simply be discarded, wile in the case of readFilePS it would -- need to be written to swap. If you read many small files, mmapFilePS -- will be less memory-efficient than readFilePS, since each mmapFilePS -- takes up a separate page of memory. Also, you can run into bus errors -- if the file is modified. NOTE: as with readFilePS, the string -- representation in the file is assumed to be ISO-8859-1. mmapFilePS :: FilePath -> IO ByteString gzWriteFilePS :: FilePath -> ByteString -> IO () gzWriteFilePSs :: FilePath -> [ByteString] -> IO () -- | Read standard input, which may or may not be gzip compressed, directly -- into a ByteString. gzReadStdin :: IO ByteString isGZFile :: FilePath -> IO (Maybe Int) -- | Decompress the given bytestring into a lazy list of chunks, along with -- a boolean flag indicating (if True) that the CRC was corrupted. -- Inspecting the flag will cause the entire list of chunks to be -- evaluated (but if you throw away the list immediately this should run -- in constant space). gzDecompress :: Maybe Int -> ByteString -> ([ByteString], Bool) -- | dropSpace efficiently returns the ByteString argument -- with white space Chars removed from the front. It is more efficient -- than calling dropWhile for removing whitespace. I.e. -- --
--   dropWhile isSpace == dropSpace
--   
dropSpace :: ByteString -> ByteString -- | breakSpace returns the pair of ByteStrings when the argument is -- broken at the first whitespace byte. I.e. -- --
--   break isSpace == breakSpace
--   
breakSpace :: ByteString -> (ByteString, ByteString) linesPS :: ByteString -> [ByteString] -- | This function acts exactly like the Prelude unlines function, -- or like Data.ByteString.Char8 unlines, but with one -- important difference: it will produce a string which may not end with -- a newline! That is: -- --
--   unlinesPS ["foo", "bar"]
--   
-- -- evaluates to "foo\nbar", not "foo\nbar\n"! This point should hold true -- for linesPS as well. -- -- TODO: rename this function. unlinesPS :: [ByteString] -> ByteString hashPS :: ByteString -> Int32 breakFirstPS :: Char -> ByteString -> Maybe (ByteString, ByteString) breakLastPS :: Char -> ByteString -> Maybe (ByteString, ByteString) substrPS :: ByteString -> ByteString -> Maybe Int -- | readIntPS skips any whitespace at the beginning of its argument, and -- reads an Int from the beginning of the PackedString. If there is no -- integer at the beginning of the string, it returns Nothing, otherwise -- it just returns the int read, along with a B.ByteString containing the -- remainder of its input. readIntPS :: ByteString -> Maybe (Int, ByteString) isFunky :: ByteString -> Bool fromHex2PS :: ByteString -> ByteString fromPS2Hex :: ByteString -> ByteString -- | betweenLinesPS returns the B.ByteString between the two lines given, -- or Nothing if they do not appear. betweenLinesPS :: ByteString -> ByteString -> ByteString -> Maybe (ByteString) breakAfterNthNewline :: Int -> ByteString -> Maybe (ByteString, ByteString) breakBeforeNthNewline :: Int -> ByteString -> (ByteString, ByteString) -- | O(n) The intercalate function takes a ByteString -- and a list of ByteStrings and concatenates the list after -- interspersing the first argument between each element of the list. intercalate :: ByteString -> [ByteString] -> ByteString -- | Test if a ByteString is made of ascii characters isAscii :: ByteString -> Bool -- | Decode a ByteString to a String according to the current locale -- unsafePerformIO in the locale function is ratified by the fact that -- GHC 6.12 and above also supply locale conversion with functions with a -- pure type. Unrecognized byte sequences in the input are skipped. decodeLocale :: ByteString -> String -- | Encode a String to a ByteString according to the current locale encodeLocale :: String -> ByteString -- | Take a String that represents byte values and re-decode it -- acording to the current locale. decodeString :: String -> String module Darcs.Patch.TokenReplace tryTokInternal :: String -> ByteString -> ByteString -> ByteString -> Maybe [ByteString] forceTokReplace :: String -> String -> String -> ByteString -> Maybe ByteString -- | This module defines our parsing monad. In the past there have been -- lazy and strict parsers in this module. Currently we have only the -- strict variant and it is used for parsing patch files. module Darcs.Patch.ReadMonads class (Functor m, Applicative m, Alternative m, Monad m, MonadPlus m) => ParserM m parse :: ParserM m => m a -> ByteString -> Maybe (a, ByteString) -- | Takes exactly n bytes, or fails. take :: ParserM m => Int -> m ByteString -- | parseStrictly applies the parser functions to a string and -- checks that each parser produced a result as it goes. The strictness -- is in the ParserM instance for SM. parseStrictly :: SM a -> ByteString -> Maybe (a, ByteString) -- | Accepts only the specified character. Consumes a character, if -- available. char :: ParserM m => Char -> m () -- | Parse an integer and return it. Skips leading whitespaces and | uses -- the efficient ByteString readInt. int :: ParserM m => m Int -- | If p fails it returns x, otherwise it returns the -- result of p. option :: Alternative f => a -> f a -> f a -- | Attempts each option until one succeeds. choice :: Alternative f => [f a] -> f a -- | Discards spaces until a non-space character is encountered. Always -- succeeds. skipSpace :: ParserM m => m () -- | Discards any characters as long as p returns True. Always | -- succeeds. skipWhile :: ParserM m => (Char -> Bool) -> m () -- | Only succeeds if the characters in the input exactly match -- str. string :: ParserM m => ByteString -> m () -- | lexChar checks if the next space delimited token from the input -- stream matches a specific Char. Uses Maybe inside -- ParserM to handle failed matches, so that it always returns () -- on success. lexChar :: ParserM m => Char -> m () -- | lexString fetches the next whitespace delimited token from from -- the input and checks if it matches the ByteString input. Uses -- Maybe inside ParserM to handle failed matches, so that -- it always returns () on success. lexString :: ParserM m => ByteString -> m () -- | lexEof looks for optional spaces followed by the end of input. -- Uses Maybe inside ParserM to handle failed matches, so -- that it always returns () on success. lexEof :: ParserM m => m () -- | Equivalent to takeTill (==c), except that it is optimized for -- | the equality case. takeTillChar :: ParserM m => Char -> m ByteString -- | Like myLex except that it is in ParserM myLex' :: ParserM m => m ByteString -- | Accepts the next character and returns it. Only fails at end of input. anyChar :: ParserM m => m Char -- | Only succeeds at end of input, consumes no characters. endOfInput :: ParserM m => m () -- | Takes characters while p returns True. Always succeeds. takeTill :: ParserM m => (Char -> Bool) -> m ByteString -- | Ensure that a parser consumes input when producing a result Causes the -- initial state of the input stream to be held on to while the parser -- runs, so use with caution. checkConsumes :: ParserM m => m a -> m a -- | This is a highly optimized way to read lines that start with a -- particular character. To implement this efficiently we need access to -- the parser's internal state. If this is implemented in terms of the -- other primitives for the parser it requires us to consume one -- character at a time. That leads to (>>=) wasting -- significant time. linesStartingWith :: ParserM m => Char -> m [ByteString] -- | This is a highly optimized way to read lines that start with a -- particular character, and stops when it reaches a particular | -- character. See linesStartingWith for details on why this | -- defined here as a primitive. linesStartingWithEndingWith :: ParserM m => Char -> Char -> m [ByteString] instance Alternative SM instance Applicative SM instance Functor SM instance MonadPlus SM instance ParserM SM instance Monad SM module Printer -- | A Printable is either a String, a packed string, or a chunk of -- text with both representations. data Printable S :: !String -> Printable PS :: !ByteString -> Printable Both :: !String -> !ByteString -> Printable -- | a Doc is a bit of enriched text. Docs get concatanated -- using <>, which is right-associative. newtype Doc Doc :: (St -> Document) -> Doc unDoc :: Doc -> St -> Document type Printers = Handle -> Printers' -- | A set of printers to print different types of text to a handle. data Printers' Printers :: !(Color -> Printer) -> !Printer -> !Printer -> !Printer -> !Printer -> !(Color -> Doc -> Doc) -> !([Printable] -> [Printable]) -> Printers' colorP :: Printers' -> !(Color -> Printer) invisibleP :: Printers' -> !Printer hiddenP :: Printers' -> !Printer userchunkP :: Printers' -> !Printer defP :: Printers' -> !Printer lineColorT :: Printers' -> !(Color -> Doc -> Doc) lineColorS :: Printers' -> !([Printable] -> [Printable]) type Printer = Printable -> St -> Document data Color Blue :: Color Red :: Color Green :: Color Cyan :: Color Magenta :: Color -- | hputDoc puts a doc on the given handle using -- simplePrinters hPutDoc :: Handle -> Doc -> IO () hPutDocLn :: Handle -> Doc -> IO () -- | putDoc puts a doc on stdout using the simple printer -- simplePrinters. putDoc :: Doc -> IO () -- | putDocLn puts a doc, followed by a newline on stdout using -- simplePrinters putDocLn :: Doc -> IO () -- | hputDocWith puts a doc on the given handle using the given -- printer. hPutDocWith :: Printers -> Handle -> Doc -> IO () -- | hputDocLnWith puts a doc, followed by a newline on the given -- handle using the given printer. hPutDocLnWith :: Printers -> Handle -> Doc -> IO () -- | putDocWith puts a doc on stdout using the given printer. putDocWith :: Printers -> Doc -> IO () -- | putDocLnWith puts a doc, followed by a newline on stdout using -- the given printer. putDocLnWith :: Printers -> Doc -> IO () -- | renders a Doc into a String with control codes for the -- special features of the doc. renderString :: Doc -> String -- | renders a Doc into a String using a given set of -- printers. renderStringWith :: Printers' -> Doc -> String -- | renders a Doc into ByteString with control codes for the -- special features of the Doc. See also readerString. renderPS :: Doc -> ByteString -- | renders a doc into a ByteString using a given set of printers. renderPSWith :: Printers' -> Doc -> ByteString -- | renders a Doc into a list of PackedStrings, one for -- each line. renderPSs :: Doc -> [ByteString] -- | renders a Doc into a list of PackedStrings, one for -- each chunk of text that was added to the doc, using the given set of -- printers. renderPSsWith :: Printers' -> Doc -> [ByteString] lineColor :: Color -> Doc -> Doc prefix :: String -> Doc -> Doc insertBeforeLastline :: Doc -> Doc -> Doc -- | colorText creates a Doc containing colored text from a -- String colorText :: Color -> String -> Doc -- | invisibleText creates a Doc containing invisible text -- from a String invisibleText :: String -> Doc -- | hiddenText creates a Doc containing hidden text from a -- String hiddenText :: String -> Doc hiddenPrefix :: String -> Doc -> Doc -- | userchunk creates a Doc containing a user chunk from a -- String userchunk :: String -> Doc -- | text creates a Doc from a String, using -- printable. text :: String -> Doc -- | 'printable x' creates a Doc from any Printable. printable :: Printable -> Doc -- | wrapText n s is a Doc representing s -- line-wrapped at n characters wrapText :: Int -> String -> Doc -- | blueText creates a Doc containing blue text from a -- String blueText :: String -> Doc -- | blueText creates a Doc containing blue text from a -- String redText :: String -> Doc -- | blueText creates a Doc containing blue text from a -- String greenText :: String -> Doc -- | blueText creates a Doc containing blue text from a -- String magentaText :: String -> Doc -- | blueText creates a Doc containing blue text from a -- String cyanText :: String -> Doc -- | unsafeText creates a Doc from a String, using -- simplePrinter directly unsafeText :: String -> Doc -- | unsafeBoth builds a Doc from a String and a -- ByteString representing the same text, but does not check that -- they do. unsafeBoth :: String -> ByteString -> Doc -- | unsafeBothText builds a Doc from a String. The -- string is stored in the Doc as both a String and a ByteString. unsafeBothText :: String -> Doc -- | unsafeChar creates a Doc containing just one character. unsafeChar :: Char -> Doc -- | invisiblePS creates a Doc with invisible text from a -- ByteString invisiblePS :: ByteString -> Doc -- | packedString builds a Doc from a ByteString using -- printable packedString :: ByteString -> Doc -- | unsafePackedString builds a Doc from a ByteString -- using simplePrinter unsafePackedString :: ByteString -> Doc -- | userchunkPS creates a Doc representing a user chunk from -- a ByteString. userchunkPS :: ByteString -> Doc -- | simplePrinters is a Printers which uses the set -- 'simplePriners\'' on any handle. simplePrinters :: Printers -- | invisiblePrinter is the Printer for hidden text. It just -- replaces the document with empty. It's useful to have a printer -- that doesn't actually do anything because this allows you to have -- tunable policies, for example, only printing some text if it's to the -- terminal, but not if it's to a file or vice-versa. invisiblePrinter :: Printer -- | simplePrinter is the simplest Printer: it just -- concatenates together the pieces of the Doc simplePrinter :: Printer doc :: ([Printable] -> [Printable]) -> Doc -- | The empty Doc. empty :: Doc -- | '()' is the concatenation operator for Docs (<>) :: Doc -> Doc -> Doc -- | a <?> b is a b if a is -- not empty, else empty. () :: Doc -> Doc -> Doc -- | a <+> b is a followed by a space, then -- b. (<+>) :: Doc -> Doc -> Doc -- | a $$ b is a above b. ($$) :: Doc -> Doc -> Doc -- | vcat piles vertically a list of Docs. vcat :: [Doc] -> Doc -- | vsep piles vertically a list of Docs leaving a blank -- line between each. vsep :: [Doc] -> Doc -- | hcat concatenates (horizontally) a list of Docs hcat :: [Doc] -> Doc -- | Minimal Docs representing the common characters space, -- newline minus, plus, and backslash. minus :: Doc -- | Minimal Docs representing the common characters space, -- newline minus, plus, and backslash. newline :: Doc -- | Minimal Docs representing the common characters space, -- newline minus, plus, and backslash. plus :: Doc -- | Minimal Docs representing the common characters space, -- newline minus, plus, and backslash. space :: Doc -- | Minimal Docs representing the common characters space, -- newline minus, plus, and backslash. backslash :: Doc -- | lparen is the Doc that represents "(" lparen :: Doc -- | rparen is the Doc that represents ")" rparen :: Doc -- | parens doc returns a Doc with the content of -- doc put within a pair of parenthesis. parens :: Doc -> Doc errorDoc :: Doc -> a module Darcs.Bug _bug :: BugStuff -> String -> a _bugDoc :: BugStuff -> Doc -> a _impossible :: BugStuff -> a _fromJust :: BugStuff -> Maybe a -> a -- | Path resolving: -- -- -- -- Examples: -- --
--   /usr/repo/foo                 -- local file
--   c:/src/darcs                  -- local file
--   http://darcs.net/             -- URL
--   peter@host:/path              -- ssh
--   droundy@host:                 -- ssh
--   host:/path                    -- ssh
--   
-- -- This means that single-letter hosts in ssh-paths do not work, unless a -- username is provided. -- -- Perhaps ssh-paths should use "ssh://user@host/path"-syntax -- instead? module Darcs.URL isFile :: String -> Bool isHttpUrl :: String -> Bool isSshUrl :: String -> Bool isRelative :: String -> Bool isAbsolute :: String -> Bool isSshNopath :: String -> Bool data SshFilePath sshRepo :: SshFilePath -> String sshUhost :: SshFilePath -> String sshFile :: SshFilePath -> String urlOf :: SshFilePath -> String -- | Gives the (user, host, dir) out of an ssh url splitSshUrl :: String -> SshFilePath module Darcs.Email makeEmail :: String -> [(String, String)] -> (Maybe Doc) -> Maybe String -> Doc -> (Maybe String) -> Doc readEmail :: ByteString -> ByteString -- | Formats an e-mail header by encoding any non-ascii characters using -- UTF-8 and Q-encoding, and folding lines at appropriate points. It -- doesn't do more than that, so the header name and header value should -- be well-formatted give or take line length and encoding. So no -- non-ASCII characters within quoted-string, quoted-pair, or atom; no -- semantically meaningful signs in names; no non-ASCII characters in the -- header name; etcetera. formatHeader :: String -> String -> ByteString -- | LCS stands for Longest Common Subsequence, and it is a relatively -- challenging problem to find an LCS efficiently. This module implements -- the algorithm described in: -- -- An O(ND) Difference Algorithm and its Variations, Eugene Myers, -- Algorithmica Vol. 1 No. 2, 1986, pp. 251-266; especially the variation -- described in section 4.2 and most refinements implemented in GNU diff -- (D is the edit-distance). -- -- There is currently no heuristic to reduce the running time and produce -- suboptimal output for large inputs with many differences. It behaves -- like GNU diff with the -d option in this regard. -- -- In the first step, a hash value for every line is calculated and -- collisions are marked with a special value. This reduces a string -- comparison to an int comparison for line tuples where at least one of -- the hash values is not equal to the special value. After that, lines -- which only exists in one of the files are removed and marked as -- changed which reduces the running time of the following difference -- algorithm. GNU diff additionally removes lines that appear very often -- in the other file in some cases. The last step tries to create longer -- changed regions and line up deletions in the first file to insertions -- in the second by shifting changed lines forward and backward. module Lcs -- | create a list of changes between a and b, each change has the form -- (starta, lima, startb, limb) which means that a[starta, lima) has to -- be replaced by b[startb, limb) getChanges :: [ByteString] -> [ByteString] -> [(Int, [ByteString], [ByteString])] -- | try to create nicer diffs by shifting around regions of changed lines shiftBoundaries :: BSTArray s -> BSTArray s -> PArray -> Int -> Int -> ST s () module Darcs.Witnesses.Ordered data (:>) a1 a2 x y (:>) :: (a1 x z) -> (a2 z y) -> :> a1 a2 x y data (:<) a1 a2 x y (:<) :: (a1 z y) -> (a2 x z) -> :< a1 a2 x y data (:\/:) a1 a2 x y (:\/:) :: (a1 z x) -> (a2 z y) -> :\/: a1 a2 x y data (:/\:) a1 a2 x y (:/\:) :: (a1 x z) -> (a2 y z) -> :/\: a1 a2 x y data (:||:) a1 a2 x y (:||:) :: (a1 x y) -> (a2 x y) -> :||: a1 a2 x y data FL a x z (:>:) :: a x y -> FL a y z -> FL a x z NilFL :: FL a x x data RL a x z (:<:) :: a y z -> RL a x y -> RL a x z NilRL :: RL a x x lengthFL :: FL a x z -> Int mapFL :: (forall w z. a w z -> b) -> FL a x y -> [b] mapFL_FL :: (forall w y. a w y -> b w y) -> FL a x z -> FL b x z spanFL :: (forall w y. a w y -> Bool) -> FL a x z -> (FL a :> FL a) x z foldlFL :: (forall w y. a -> b w y -> a) -> a -> FL b x z -> a allFL :: (forall x y. a x y -> Bool) -> FL a w z -> Bool anyFL :: (forall x y. a x y -> Bool) -> FL a w z -> Bool filterFL :: (forall x y. a x y -> Bool) -> FL a w z -> [Sealed2 a] splitAtFL :: Int -> FL a x z -> (FL a :> FL a) x z splitAtRL :: Int -> RL a x z -> (RL a :< RL a) x z bunchFL :: Int -> FL a x y -> FL (FL a) x y foldlRL :: (forall w y. a -> b w y -> a) -> a -> RL b x z -> a lengthRL :: RL a x z -> Int isShorterThanRL :: RL a x y -> Int -> Bool mapRL :: (forall w z. a w z -> b) -> RL a x y -> [b] mapRL_RL :: (forall w y. a w y -> b w y) -> RL a x z -> RL b x z zipWithFL :: (forall x y. a -> p x y -> q x y) -> [a] -> FL p w z -> FL q w z filterFLFL :: (forall x y. p x y -> EqCheck x y) -> FL p w z -> FL p w z filterRL :: (forall x y. p x y -> Bool) -> RL p a b -> [Sealed2 p] reverseFL :: FL a x z -> RL a x z reverseRL :: RL a x z -> FL a x z (+>+) :: FL a x y -> FL a y z -> FL a x z (+<+) :: RL a y z -> RL a x y -> RL a x z nullFL :: FL a x z -> Bool concatFL :: FL (FL a) x z -> FL a x z concatRL :: RL (RL a) x z -> RL a x z consRLSealed :: a y z -> FlippedSeal (RL a) y -> FlippedSeal (RL a) z nullRL :: RL a x z -> Bool toFL :: [FreeLeft a] -> Sealed (FL a x) dropWhileFL :: (forall x y. a x y -> Bool) -> FL a r v -> FlippedSeal (FL a) v dropWhileRL :: (forall x y. a x y -> Bool) -> RL a r v -> Sealed (RL a r) spanFL_M :: Monad m => (forall w y. a w y -> m Bool) -> FL a x z -> m ((FL a :> FL a) x z) -- | Check that two FLs are equal element by element. This differs -- from the MyEq instance for FL which uses commutation. eqFL :: MyEq a => FL a x y -> FL a x z -> EqCheck y z eqFLRev :: MyEq a => FL a x z -> FL a y z -> EqCheck x y eqFLUnsafe :: MyEq a => FL a x y -> FL a z w -> Bool instance (Show2 a, Show2 b) => Show1 ((:>) a b x) instance Show2 a => Show2 (RL a) instance Show2 a => Show1 (RL a x) instance Show2 a => Show (RL a x z) instance Show2 a => Show2 (FL a) instance Show2 a => Show1 (FL a x) instance Show2 a => Show (FL a x z) instance (Show2 a, Show2 b) => Show2 (a :\/: b) instance (Show2 a, Show2 b) => Show ((:\/:) a b x y) instance (Show2 a, Show2 b) => Show2 (a :> b) instance (MyEq a, MyEq b) => Eq ((:<) a b x y) instance (MyEq a, MyEq b) => MyEq (a :< b) instance (MyEq a, MyEq b) => Eq ((:>) a b x y) instance (MyEq a, MyEq b) => MyEq (a :> b) instance (Show2 a, Show2 b) => Show ((:>) a b x y) module Darcs.Patch.Commute -- | Things that can commute. class Commute p commute :: Commute p => (p :> p) x y -> Maybe ((p :> p) x y) commuteFL :: Commute p => (p :> FL p) x y -> Maybe ((FL p :> p) x y) commuteFLorComplain :: Commute p => (p :> FL p) x y -> Either (Sealed2 p) ((FL p :> p) x y) commuteRL :: Commute p => (RL p :> p) x y -> Maybe ((p :> RL p) x y) commuteRLFL :: Commute p => (RL p :> FL p) x y -> Maybe ((FL p :> RL p) x y) -- | Swaps the ordered pair type so that commute can be called directly. toFwdCommute :: (Commute p, Commute q, Monad m) => ((p :< q) x y -> m ((q :< p) x y)) -> (q :> p) x y -> m ((p :> q) x y) -- | Swaps the ordered pair type from the order expected by commute to the -- reverse order. toRevCommute :: (Commute p, Commute q, Monad m) => ((p :> q) x y -> m ((q :> p) x y)) -> (q :< p) x y -> m ((p :< q) x y) instance Commute p => Commute (RL p) instance Commute p => Commute (FL p) module Darcs.Patch.Invert class Invert p invert :: Invert p => p x y -> p y x invertFL :: Invert p => FL p x y -> RL p y x invertRL :: Invert p => RL p x y -> FL p y x module Darcs.Patch.Permutations -- | removeFL x xs removes x from xs if -- x can be commuted to its head. Otherwise it returns -- Nothing removeFL :: (MyEq p, Commute p) => p x y -> FL p x z -> Maybe (FL p y z) -- | removeRL is like removeFL except with RL removeRL :: (MyEq p, Commute p) => p y z -> RL p x z -> Maybe (RL p x y) removeCommon :: (MyEq p, Commute p) => (FL p :\/: FL p) x y -> (FL p :\/: FL p) x y commuteWhatWeCanFL :: Commute p => (p :> FL p) x y -> (FL p :> (p :> FL p)) x y commuteWhatWeCanRL :: Commute p => (RL p :> p) x y -> (RL p :> (p :> RL p)) x y genCommuteWhatWeCanRL :: (forall a b. (p :> p) a b -> Maybe ((p :> p) a b)) -> (RL p :> p) x y -> (RL p :> (p :> RL p)) x y -- | split an FL into left and right lists according -- to a predicate p, using commutation as necessary. If a patch -- does satisfy the predicate but cannot be commuted past one that does -- not satisfy the predicate, it goes in the middle list; to sum -- up, we have: all p left and all (not.p) right, while -- midddle is mixed. partitionFL :: Commute p => (forall u v. p u v -> Bool) -> FL p x y -> ((FL p :> (FL p :> FL p)) x y) -- | split an RL into left and right lists according -- to a predicate, using commutation as necessary. If a patch does -- satisfy the predicate but cannot be commuted past one that does not -- satisfy the predicate, it goes in the left list. partitionRL :: Commute p => (forall u v. p u v -> Bool) -> RL p x y -> (RL p :> RL p) x y -- | This is a minor variant of headPermutationsFL with each -- permutation is simply returned as a FL simpleHeadPermutationsFL :: Commute p => FL p x y -> [FL p x y] -- | headPermutationsRL is like headPermutationsFL, except -- that we operate on an RL (in other words, we are pushing things -- to the end of a patch sequence instead of to the beginning). headPermutationsRL :: Commute p => RL p x y -> [RL p x y] -- | headPermutationsFL p:>:ps returns all the -- permutations of the list in which one element of ps is -- commuted past p -- -- Suppose we have a sequence of patches -- --
--   X h a y s-t-c k
--   
-- -- Suppose furthermore that the patch c depends on t, -- which in turn depends on s. This function will return -- --
--   X :> h a y s t c k
--   h :> X a y s t c k
--   a :> X h y s t c k
--   y :> X h a s t c k
--   s :> X h a y t c k
--   k :> X h a y s t c
--   
headPermutationsFL :: Commute p => FL p x y -> [(p :> FL p) x y] -- | removeSubsequenceFL ab abc returns Just c' -- where all the patches in ab have been commuted out of it, if -- possible. If this is not possible for any reason (the set of patches -- ab is not actually a subset of abc, or they can't be -- commuted out) we return Nothing. removeSubsequenceFL :: (MyEq p, Commute p) => FL p a b -> FL p a c -> Maybe (FL p b c) -- | removeSubsequenceRL is like removeSubsequenceFL except -- that it works on RL removeSubsequenceRL :: (MyEq p, Commute p) => RL p ab abc -> RL p a abc -> Maybe (RL p a ab) -- | Partition a list into the patches that commute with the given patch -- and those that don't (including dependencies) partitionConflictingFL :: (Commute p1, Invert p1) => CommuteFn p1 p2 -> FL p1 x y -> p2 x z -> (FL p1 :> FL p1) x y -- | CommuteFn is the basis of a general framework for building up -- commutation operations between different patch types in a generic -- manner. Unfortunately type classes are not well suited to the problem -- because of the multiple possible routes by which the commuter for (FL -- p1, FL p2) can be built out of the commuter for (p1, p2) - and more -- complicated problems when we start building multiple constructors on -- top of each other. The type class resolution machinery really can't -- cope with selecting some route, because it doesn't know that all -- possible routes should be equivalent. type CommuteFn p1 p2 = forall x y. (p1 :> p2) x y -> Maybe ((p2 :> p1) x y) -- | Build a commuter between a patch and itself using the operation from -- the type class. selfCommuter :: Commute p => CommuteFn p p commuterIdFL :: CommuteFn p1 p2 -> CommuteFn p1 (FL p2) commuterFLId :: CommuteFn p1 p2 -> CommuteFn (FL p1) p2 commuterIdRL :: CommuteFn p1 p2 -> CommuteFn p1 (RL p2) instance (Commute p, Invert p) => Invert (RL p) instance (MyEq p, Commute p) => MyEq (RL p) instance (Invert p, Commute p) => Invert (FL p) instance (MyEq p, Commute p) => MyEq (FL p) module Darcs.Patch.Bracketed -- | This type exists for legacy support of on-disk format patch formats. -- It is a wrapper type that explicitly tracks the nesting of braces and -- parens in the on-disk representation of such patches. It is used as an -- intermediate form when reading such patches normally, and also for -- round-tripping such patches when checking the hash in bundles. It -- shouldn't be used for anything else. data Bracketed p x y Singleton :: p x y -> Bracketed p x y Braced :: BracketedFL p x y -> Bracketed p x y Parens :: BracketedFL p x y -> Bracketed p x y mapBracketed :: (forall a b. p a b -> q a b) -> Bracketed p x y -> Bracketed q x y unBracketed :: Bracketed p x y -> FL p x y type BracketedFL p x y = FL (Bracketed p) x y mapBracketedFL_FL :: (forall a b. p a b -> q a b) -> BracketedFL p x y -> BracketedFL q x y unBracketedFL :: BracketedFL p x y -> FL p x y instance PatchListFormat (Bracketed p) module Darcs.Patch.Merge -- | Things that can always be merged class Commute p => Merge p merge :: Merge p => (p :\/: p) x y -> (p :/\: p) x y mergeFL :: Merge p => (p :\/: FL p) x y -> (FL p :/\: p) x y instance Merge p => Merge (RL p) instance Merge p => Merge (FL p) module Darcs.Patch.Inspect class PatchInspect p listTouchedFiles :: PatchInspect p => p x y -> [FilePath] hunkMatches :: PatchInspect p => (ByteString -> Bool) -> p x y -> Bool instance PatchInspect p => PatchInspect (RL p) instance PatchInspect p => PatchInspect (FL p) module Darcs.Witnesses.WZipper data FZipper a x z FZipper :: RL a x y -> FL a y z -> FZipper a x z focus :: FZipper a x y -> Maybe (Sealed2 a) leftmost :: FZipper p x y -> Bool left :: FZipper p x y -> FZipper p x y rightmost :: FZipper p x y -> Bool right :: FZipper p x y -> FZipper p x y -- | See clowns jokers :: FZipper a x y -> FlippedSeal (FL a) y -- | "Clowns to the left of me, jokers to the right. Here I am, stuck in -- the middle of you" -- http://en.wikipedia.org/wiki/Stuck_in_the_Middle clowns :: FZipper a x y -> Sealed ((RL a) x) flToZipper :: FL a x y -> FZipper a x y lengthFZ :: FZipper a x y -> Int nullFZ :: FZipper a x y -> Bool toEnd :: FZipper p x y -> FZipper p x y toStart :: FZipper p x y -> FZipper p x y -- | FileName is an abstract type intended to facilitate the input and -- output of unicode filenames. module Darcs.Patch.FileName data FileName fp2fn :: FilePath -> FileName fn2fp :: FileName -> FilePath fn2ps :: FileName -> ByteString ps2fn :: ByteString -> FileName niceps2fn :: ByteString -> FileName fn2niceps :: FileName -> ByteString breakOnDir :: FileName -> Maybe (FileName, FileName) normPath :: FileName -> FileName ownName :: FileName -> FileName superName :: FileName -> FileName movedirfilename :: FileName -> FileName -> FileName -> FileName -- | encodeWhite translates whitespace in filenames to a -- darcs-specific format (numerical representation according to -- ord surrounded by backslashes). Note that backslashes are also -- escaped since they are used in the encoding. -- --
--   encodeWhite "hello there" == "hello\32\there"
--   encodeWhite "hello\there" == "hello\92\there"
--   
encodeWhite :: FilePath -> String -- | decodeWhite interprets the Darcs-specific "encoded" filenames -- produced by encodeWhite -- --
--   decodeWhite "hello\32\there"  == "hello there"
--   decodeWhite "hello\92\there"  == "hello\there"
--   decodeWhite "hello\there"   == error "malformed filename"
--   
decodeWhite :: String -> FilePath (///) :: FileName -> FileName -> FileName -- | Split a file path at the slashes breakup :: String -> [String] isParentOrEqOf :: FileName -> FileName -> Bool instance Eq FileName instance Ord FileName instance Show FileName -- | Various abstractions for dealing with paths. module Darcs.RepoPath data AbsolutePath -- | Take an absolute path and a string representing a (possibly relative) -- path and combine them into an absolute path. If the second argument is -- already absolute, then the first argument gets ignored. This function -- also takes care that the result is converted to Posix convention and -- normalized. Also, parent directories ("..") at the front of the string -- argument get canceled out against trailing directory parts of the -- absolute path argument. -- -- Regarding the last point, someone more familiar with how these -- functions are used should verify that this is indeed necessary or at -- least useful. makeAbsolute :: AbsolutePath -> FilePath -> AbsolutePath -- | Interpret a possibly relative path wrt the current working directory. ioAbsolute :: FilePath -> IO AbsolutePath -- | The root directory as an absolute path. rootDirectory :: AbsolutePath -- | This is for situations where a string (e.g. a command line argument) -- may take the value "-" to mean stdin or stdout (which one depends on -- context) instead of a normal file path. data AbsolutePathOrStd makeAbsoluteOrStd :: AbsolutePath -> String -> AbsolutePathOrStd ioAbsoluteOrStd :: String -> IO AbsolutePathOrStd -- | Execute either the first or the second argument action, depending on -- whether the given path is an AbsolutePath or stdin/stdout. useAbsoluteOrStd :: (AbsolutePath -> a) -> a -> AbsolutePathOrStd -> a stdOut :: AbsolutePathOrStd data AbsoluteOrRemotePath ioAbsoluteOrRemote :: String -> IO AbsoluteOrRemotePath isRemote :: AbsoluteOrRemotePath -> Bool -- | Paths which are relative to the local darcs repository and normalized. -- Note: These are understood not to have the dot in front. data SubPath -- | Make the second path relative to the first, if possible makeSubPathOf :: AbsolutePath -> AbsolutePath -> Maybe SubPath simpleSubPath :: FilePath -> Maybe SubPath sp2fn :: SubPath -> FileName class FilePathOrURL a toPath :: FilePathOrURL a => a -> String class FilePathOrURL a => FilePathLike a toFilePath :: FilePathLike a => a -> FilePath getCurrentDirectory :: IO AbsolutePath setCurrentDirectory :: FilePathLike p => p -> IO () instance Eq SubPath instance Ord SubPath instance Eq AbsolutePath instance Ord AbsolutePath instance Eq AbsolutePathOrStd instance Ord AbsolutePathOrStd instance Eq AbsoluteOrRemotePath instance Ord AbsoluteOrRemotePath instance Show AbsoluteOrRemotePath instance Show AbsolutePathOrStd instance Show SubPath instance Show AbsolutePath instance CharLike c => FilePathLike [c] instance CharLike Char instance FilePathLike SubPath instance FilePathLike AbsolutePath instance FilePathLike FileName instance FilePathOrURL FileName instance FilePathOrURL AbsoluteOrRemotePath instance CharLike c => FilePathOrURL [c] instance FilePathOrURL SubPath instance FilePathOrURL AbsolutePath -- | Various utility functions that do not belong anywhere else. module Darcs.Utils -- | Given two shell commands as arguments, execute the former. The latter -- is then executed if the former failed because the executable wasn't -- found (code 127), wasn't executable (code 126) or some other exception -- occurred. Other failures (such as the user holding ^C) do not cause -- the second command to be tried. ortryrunning :: IO ExitCode -> IO ExitCode -> IO ExitCode nubsort :: Ord a => [a] -> [a] breakCommand :: String -> (String, [String]) showHexLen :: (Integral a, Show a) => Int -> a -> String maybeGetEnv :: String -> IO (Maybe String) -- | Format a path for screen output, so that the user sees where the path -- begins and ends. Could (should?) also warn about unprintable -- characters here. formatPath :: String -> String -- | The firstJustIO is a slight modification to firstJustM: the entries in -- the list must be IO monad operations and the firstJustIO will silently -- turn any monad call that throws an exception into Nothing, basically -- causing it to be ignored. firstJustIO :: [IO (Maybe a)] -> IO (Maybe a) -- | Ask the user to press Enter askEnter :: String -> IO () -- | Ask the user for a line of input. askUser :: String -> IO String -- | askUserListItem prompt xs enumerates xs on the -- screen, allowing the user to choose one of the items askUserListItem :: String -> [String] -> IO String data PromptConfig PromptConfig :: String -> [Char] -> [Char] -> Maybe Char -> [Char] -> PromptConfig pPrompt :: PromptConfig -> String pBasicCharacters :: PromptConfig -> [Char] -- | only shown on help pAdvancedCharacters :: PromptConfig -> [Char] pDefault :: PromptConfig -> Maybe Char pHelp :: PromptConfig -> [Char] -- | Prompt the user for a yes or no promptYorn :: [Char] -> IO Bool promptChar :: PromptConfig -> IO Char getViewer :: IO String -- | 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. editFile :: FilePathLike p => p -> IO (ExitCode, Bool) runEditor :: FilePath -> IO ExitCode stripCr :: String -> String environmentHelpEditor :: ([String], [String]) environmentHelpPager :: ([String], [String]) catchall :: IO a -> IO a -> IO a clarifyErrors :: IO a -> String -> IO a prettyException :: SomeException -> String prettyError :: IOError -> String addToErrorLoc :: IOException -> String -> IOException getFileStatus :: FilePath -> IO (Maybe FileStatus) withCurrentDirectory :: FilePathLike p => p -> IO a -> IO a withUMask :: String -> IO a -> IO a -- | 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. setDarcsEncodings :: IO () getSystemEncoding :: IO String -- | isUTF8 checks if an encoding is UTF-8 (or ascii, since it is -- a subset of UTF-8). isUTF8Locale :: String -> Bool -- | Same as filterPath, but for ordinary FilePaths (as -- opposed to AnchoredPath). filterFilePaths :: [FilePath] -> AnchoredPath -> t -> Bool -- | Construct a filter from a list of AnchoredPaths, that will accept any -- path that is either a parent or a child of any of the listed paths, -- and discard everything else. filterPaths :: [AnchoredPath] -> AnchoredPath -> t -> Bool treeHas :: (MonadError e m, Functor m, Monad m) => Tree m -> FilePath -> m Bool treeHasDir :: (MonadError e m, Functor m, Monad m) => Tree m -> FilePath -> m Bool treeHasFile :: (MonadError e m, Functor m, Monad m) => Tree m -> FilePath -> m Bool treeHasAnycase :: (MonadError e m, Functor m, Monad m) => Tree m -> FilePath -> m Bool module Darcs.Compat stdoutIsAPipe :: IO Bool mkStdoutTemp :: String -> IO String canonFilename :: FilePath -> IO FilePath maybeRelink :: String -> String -> IO Bool atomicCreate :: FilePath -> IO () sloppyAtomicCreate :: FilePath -> IO () module Darcs.Flags -- | The DarcsFlag type is a list of all flags that can ever be -- passed to darcs, or to one of its commands. data DarcsFlag Help :: DarcsFlag ListOptions :: DarcsFlag NoTest :: DarcsFlag Test :: DarcsFlag OnlyChangesToFiles :: DarcsFlag ChangesToAllFiles :: DarcsFlag LeaveTestDir :: DarcsFlag NoLeaveTestDir :: DarcsFlag Timings :: DarcsFlag Debug :: DarcsFlag DebugVerbose :: DarcsFlag DebugHTTP :: DarcsFlag Verbose :: DarcsFlag NormalVerbosity :: DarcsFlag Quiet :: DarcsFlag Target :: String -> DarcsFlag Cc :: String -> DarcsFlag Output :: AbsolutePathOrStd -> DarcsFlag OutputAutoName :: AbsolutePath -> DarcsFlag Subject :: String -> DarcsFlag InReplyTo :: String -> DarcsFlag Charset :: String -> DarcsFlag SendmailCmd :: String -> DarcsFlag Author :: String -> DarcsFlag PatchName :: String -> DarcsFlag OnePatch :: String -> DarcsFlag SeveralPatch :: String -> DarcsFlag AfterPatch :: String -> DarcsFlag UpToPatch :: String -> DarcsFlag TagName :: String -> DarcsFlag LastN :: Int -> DarcsFlag MaxCount :: Int -> DarcsFlag PatchIndexRange :: Int -> Int -> DarcsFlag NumberPatches :: DarcsFlag OneTag :: String -> DarcsFlag AfterTag :: String -> DarcsFlag UpToTag :: String -> DarcsFlag GenContext :: DarcsFlag Context :: AbsolutePath -> DarcsFlag Count :: DarcsFlag LogFile :: AbsolutePath -> DarcsFlag RmLogFile :: DarcsFlag DontRmLogFile :: DarcsFlag DistName :: String -> DarcsFlag All :: DarcsFlag Recursive :: DarcsFlag NoRecursive :: DarcsFlag Reorder :: DarcsFlag RestrictPaths :: DarcsFlag DontRestrictPaths :: DarcsFlag AskDeps :: DarcsFlag NoAskDeps :: DarcsFlag IgnoreTimes :: DarcsFlag DontIgnoreTimes :: DarcsFlag LookForAdds :: DarcsFlag NoLookForAdds :: DarcsFlag AnyOrder :: DarcsFlag CreatorHash :: String -> DarcsFlag Intersection :: DarcsFlag Union :: DarcsFlag Complement :: DarcsFlag Sign :: DarcsFlag SignAs :: String -> DarcsFlag NoSign :: DarcsFlag SignSSL :: String -> DarcsFlag HappyForwarding :: DarcsFlag NoHappyForwarding :: DarcsFlag Verify :: AbsolutePath -> DarcsFlag VerifySSL :: AbsolutePath -> DarcsFlag RemoteDarcsOpt :: String -> DarcsFlag EditDescription :: DarcsFlag NoEditDescription :: DarcsFlag Toks :: String -> DarcsFlag EditLongComment :: DarcsFlag NoEditLongComment :: DarcsFlag PromptLongComment :: DarcsFlag KeepDate :: DarcsFlag NoKeepDate :: DarcsFlag AllowConflicts :: DarcsFlag MarkConflicts :: DarcsFlag NoAllowConflicts :: DarcsFlag SkipConflicts :: DarcsFlag Boring :: DarcsFlag SkipBoring :: DarcsFlag AllowCaseOnly :: DarcsFlag DontAllowCaseOnly :: DarcsFlag AllowWindowsReserved :: DarcsFlag DontAllowWindowsReserved :: DarcsFlag DontGrabDeps :: DarcsFlag DontPromptForDependencies :: DarcsFlag PromptForDependencies :: DarcsFlag Compress :: DarcsFlag NoCompress :: DarcsFlag UnCompress :: DarcsFlag WorkRepoDir :: String -> DarcsFlag WorkRepoUrl :: String -> DarcsFlag RemoteRepo :: String -> DarcsFlag NewRepo :: String -> DarcsFlag Reply :: String -> DarcsFlag ApplyAs :: String -> DarcsFlag MachineReadable :: DarcsFlag HumanReadable :: DarcsFlag Pipe :: DarcsFlag Interactive :: DarcsFlag DiffCmd :: String -> DarcsFlag ExternalMerge :: String -> DarcsFlag Summary :: DarcsFlag NoSummary :: DarcsFlag PauseForGui :: DarcsFlag NoPauseForGui :: DarcsFlag Unified :: DarcsFlag NonUnified :: DarcsFlag Reverse :: DarcsFlag Forward :: DarcsFlag Complete :: DarcsFlag Lazy :: DarcsFlag FixFilePath :: AbsolutePath -> AbsolutePath -> DarcsFlag DiffFlags :: String -> DarcsFlag XMLOutput :: DarcsFlag ForceReplace :: DarcsFlag OnePattern :: PatchMatch -> DarcsFlag SeveralPattern :: PatchMatch -> DarcsFlag AfterPattern :: PatchMatch -> DarcsFlag UpToPattern :: PatchMatch -> DarcsFlag NonApply :: DarcsFlag NonVerify :: DarcsFlag NonForce :: DarcsFlag DryRun :: DarcsFlag SetDefault :: Bool -> DarcsFlag NoSetDefault :: Bool -> DarcsFlag Disable :: DarcsFlag SetScriptsExecutable :: DarcsFlag DontSetScriptsExecutable :: DarcsFlag Bisect :: DarcsFlag UseHashedInventory :: DarcsFlag UseFormat2 :: DarcsFlag UseNoWorkingDir :: DarcsFlag UseWorkingDir :: DarcsFlag NoUpdateWorking :: DarcsFlag Sibling :: AbsolutePath -> DarcsFlag Relink :: DarcsFlag OptimizePristine :: DarcsFlag OptimizeHTTP :: DarcsFlag UpgradeFormat :: DarcsFlag Files :: DarcsFlag NoFiles :: DarcsFlag Directories :: DarcsFlag NoDirectories :: DarcsFlag Pending :: DarcsFlag NoPending :: DarcsFlag PosthookCmd :: String -> DarcsFlag NoPosthook :: DarcsFlag AskPosthook :: DarcsFlag RunPosthook :: DarcsFlag PrehookCmd :: String -> DarcsFlag NoPrehook :: DarcsFlag AskPrehook :: DarcsFlag RunPrehook :: DarcsFlag UMask :: String -> DarcsFlag StoreInMemory :: DarcsFlag ApplyOnDisk :: DarcsFlag NoHTTPPipelining :: DarcsFlag Packs :: DarcsFlag NoPacks :: DarcsFlag NoCache :: DarcsFlag AllowUnrelatedRepos :: DarcsFlag Check :: DarcsFlag Repair :: DarcsFlag JustThisRepo :: DarcsFlag NullFlag :: DarcsFlag RecordRollback :: DarcsFlag NoRecordRollback :: DarcsFlag NoAmendUnrecord :: DarcsFlag AmendUnrecord :: DarcsFlag data Compression NoCompression :: Compression GzipCompression :: Compression data UseIndex UseIndex :: UseIndex IgnoreIndex :: UseIndex data ScanKnown -- | Just files already known to darcs ScanKnown :: ScanKnown -- | All files, i.e. look for new ones ScanAll :: ScanKnown -- | All files, even boring ones ScanBoring :: ScanKnown data RemoteDarcs RemoteDarcs :: String -> RemoteDarcs DefaultRemoteDarcs :: RemoteDarcs compression :: [DarcsFlag] -> Compression remoteDarcs :: [DarcsFlag] -> RemoteDarcs diffingOpts :: [DarcsFlag] -> (UseIndex, ScanKnown) wantExternalMerge :: [DarcsFlag] -> Maybe String wantGuiPause :: [DarcsFlag] -> Bool isInteractive :: [DarcsFlag] -> Bool maxCount :: [DarcsFlag] -> Maybe Int willIgnoreTimes :: [DarcsFlag] -> Bool willRemoveLogFile :: [DarcsFlag] -> Bool isUnified :: [DarcsFlag] -> Bool isNotUnified :: [DarcsFlag] -> Bool doHappyForwarding :: [DarcsFlag] -> Bool includeBoring :: [DarcsFlag] -> Bool doAllowCaseOnly :: [DarcsFlag] -> Bool doAllowWindowsReserved :: [DarcsFlag] -> Bool doReverse :: [DarcsFlag] -> Bool usePacks :: [DarcsFlag] -> Bool showChangesOnlyToFiles :: [DarcsFlag] -> Bool rollbackInWorkingDir :: [DarcsFlag] -> Bool removeFromAmended :: [DarcsFlag] -> Bool -- | Set flags to a default value, but only one has not already been -- provided defaultFlag :: [DarcsFlag] -> DarcsFlag -> [DarcsFlag] -> [DarcsFlag] instance Eq DarcsFlag instance Show DarcsFlag module Darcs.Ssh copySSH :: RemoteDarcs -> SshFilePath -> FilePath -> IO () data SSHCmd SSH :: SSHCmd SCP :: SSHCmd SFTP :: SSHCmd -- | Return the command and arguments needed to run an ssh command First -- try the appropriate darcs environment variable and SSH_PORT defaulting -- to ssh and no specified port. getSSH :: SSHCmd -> IO (String, [String]) environmentHelpSsh :: ([String], [String]) environmentHelpScp :: ([String], [String]) environmentHelpSshPort :: ([String], [String]) remoteDarcs :: RemoteDarcs -> String module Darcs.Lock withLock :: String -> IO a -> IO a -- | Tries to perform some task if it can obtain the lock, Otherwise, just -- gives up without doing the task withLockCanFail :: String -> IO a -> IO (Either () a) -- | withTemp safely creates an empty file (not open for writing) -- and returns its name. -- -- The temp file operations are rather similar to the locking operations, -- in that they both should always try to clean up, so exitWith causes -- trouble. withTemp :: (String -> IO a) -> IO a -- | withOpenTemp creates a temporary file, and opens it. Both of -- them run their argument and then delete the file. Also, both of them -- (to my knowledge) are not susceptible to race conditions on the -- temporary file (as long as you never delete the temporary file; that -- would reintroduce a race condition). withOpenTemp :: ((Handle, String) -> IO a) -> IO a withStdoutTemp :: (String -> IO a) -> IO a -- | withTempDir creates an empty directory and then removes it when -- it is no longer needed. withTempDir creates a temporary directory. The -- location of that directory is determined by the contents of -- _darcsprefstmpdir, if it exists, otherwise by -- $DARCS_TMPDIR, and if that doesn't exist then whatever your -- operating system considers to be a a temporary directory (e.g. -- $TMPDIR under Unix, $TEMP under Windows). -- -- If none of those exist it creates the temporary directory in the -- current directory, unless the current directory is under a _darcs -- directory, in which case the temporary directory in the parent of the -- highest _darcs directory to avoid accidentally corrupting darcs's -- internals. This should not fail, but if it does indeed fail, we go -- ahead and use the current directory anyway. If -- $DARCS_KEEP_TMPDIR variable is set temporary directory is not -- removed, this can be useful for debugging. withTempDir :: String -> (AbsolutePath -> IO a) -> IO a -- | withPermDir is like withTempDir, except that it doesn't -- delete the directory afterwards. withPermDir :: String -> (AbsolutePath -> IO a) -> IO a withDelayedDir :: String -> (AbsolutePath -> IO a) -> IO a withNamedTemp :: String -> (String -> IO a) -> IO a writeToFile :: FilePathLike p => p -> (Handle -> IO ()) -> IO () appendToFile :: FilePathLike p => p -> (Handle -> IO ()) -> IO () writeBinFile :: FilePathLike p => p -> String -> IO () -- | Writes a file. Differs from writeBinFile in that it writes the string -- encoded with the current locale instead of what GHC thinks is right. writeLocaleFile :: FilePathLike p => p -> String -> IO () writeDocBinFile :: FilePathLike p => p -> Doc -> IO () appendBinFile :: FilePathLike p => p -> String -> IO () appendDocBinFile :: FilePathLike p => p -> Doc -> IO () readBinFile :: FilePathLike p => p -> IO String -- | Reads a file. Differs from readBinFile in that it interprets the file -- in the current locale instead of as ISO-8859-1. readLocaleFile :: FilePathLike p => p -> IO String readDocBinFile :: FilePathLike p => p -> IO Doc writeAtomicFilePS :: FilePathLike p => p -> ByteString -> IO () gzWriteAtomicFilePS :: FilePathLike p => p -> ByteString -> IO () gzWriteAtomicFilePSs :: FilePathLike p => p -> [ByteString] -> IO () gzWriteDocFile :: FilePathLike p => p -> Doc -> IO () rmRecursive :: FilePath -> IO () removeFileMayNotExist :: FilePathLike p => p -> IO () canonFilename :: FilePath -> IO FilePath maybeRelink :: String -> String -> IO Bool worldReadableTemp :: String -> IO String tempdirLoc :: IO FilePath editText :: String -> ByteString -> IO ByteString environmentHelpTmpdir :: ([String], [String]) environmentHelpKeepTmpdir :: ([String], [String]) module Darcs.Patch.Read class ReadPatch p readPatch' :: (ReadPatch p, ParserM m) => m (Sealed (p x)) readPatch :: ReadPatch p => ByteString -> Maybe (Sealed (p x)) readPatchPartial :: ReadPatch p => ByteString -> Maybe (Sealed (p x), ByteString) bracketedFL :: ParserM m => (forall y. m (Sealed (p y))) -> Char -> Char -> m (Sealed (FL p x)) peekfor :: ParserM m => ByteString -> m a -> m a -> m a readFileName :: FileNameFormat -> ByteString -> FileName instance (ReadPatch p, PatchListFormat p) => ReadPatch (RL p) instance (ReadPatch p, PatchListFormat p) => ReadPatch (FL p) instance ReadPatch p => ReadPatch (Bracketed p) module Darcs.Patch.SummaryData data SummDetail SummAddDir :: FileName -> SummDetail SummRmDir :: FileName -> SummDetail SummFile :: SummOp -> FileName -> Int -> Int -> Int -> SummDetail SummMv :: FileName -> FileName -> SummDetail SummNone :: SummDetail data SummOp SummAdd :: SummOp SummRm :: SummOp SummMod :: SummOp instance Ord SummOp instance Eq SummOp instance Ord SummDetail instance Eq SummDetail module Crypt.SHA256 sha256sum :: ByteString -> String -- | |A parser for commandlines, returns an arg list and expands format -- strings given in a translation table. Additionally the commandline can -- end with %< specifying that the command expects input on -- stdin. -- -- Some tests for the parser. -- --
--   formatTable = [('s',"<insert subject here>"),
--                  ('a',"<insert author here>")]
--   
--   testParser :: (Show a, Eq a) => Parser a -> String -> a -> a
--   testParser p s ok = case parse p "" s of
--                       Left e -> error $ "Parser failed with: " ++ (show e)
--                       Right res -> if res == ok
--                                    then res
--                                    else error $ "Parser failed: got "
--                                           ++ (show res) ++ ", expected "
--                                           ++ (show ok)
--   
--   testCases = [("a b",(["a","b"], False)),
--                ("a b %<",(["a","b"], True)),
--                ("a b %< ",(["a","b"], True)),
--                ("\"arg0 contains spaces \\\"quotes\\\"\" b",
--                 (["arg0 contains spaces \"quotes\"","b"],False)),
--                ("a %s %<",(["a","<insert subject here>"], True))]
--   
--   runTests = map (uncurry $ testParser (commandline formatTable)) testCases
--   
module CommandLine -- | parse a commandline returning a list of strings (intended to be used -- as argv) and a bool value which specifies if the command expects input -- on stdin format specifiers with a mapping in ftable are accepted and -- replaced by the given strings. E.g. if the ftable is -- [(s,Some subject)], then %s is replaced by -- Some subject parseCmd :: FTable -> String -> Either ParseError ([String], Bool) -- | for every mapping (c,s), add a mapping with uppercase c and the -- urlencoded string s addUrlencoded :: FTable -> FTable module URL copyUrl :: String -> FilePath -> Cachable -> IO () copyUrlFirst :: String -> FilePath -> Cachable -> IO () setDebugHTTP :: IO () disableHTTPPipelining :: IO () maxPipelineLength :: IO Int waitUrl :: String -> IO () data Cachable Cachable :: Cachable Uncachable :: Cachable MaxAge :: !CInt -> Cachable environmentHelpProxy :: ([String], [String]) environmentHelpProxyPassword :: ([String], [String]) -- | Data type to represent a connection error. The following are the codes -- from libcurl which map to each of the constructors: * 6 -> -- CouldNotResolveHost : The remote host was not resolved. * 7 -> -- CouldNotConnectToServer : Failed to connect() to host or proxy. * 28 -- -> OperationTimeout: the specified time-out period was reached. data ConnectionError CouldNotResolveHost :: ConnectionError CouldNotConnectToServer :: ConnectionError OperationTimeout :: ConnectionError module Darcs.External backupByRenaming :: FilePath -> IO () backupByCopying :: FilePath -> IO () copyFileOrUrl :: RemoteDarcs -> FilePath -> FilePath -> Cachable -> IO () speculateFileOrUrl :: String -> FilePath -> IO () copyLocal :: String -> FilePath -> IO () cloneFile :: FilePath -> FilePath -> IO () cloneTree :: FilePath -> FilePath -> IO () cloneTreeExcept :: [FilePath] -> FilePath -> FilePath -> IO () -- | 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. -- -- We always use default remote darcs, since it is not fatal if the -- remote darcs does not exist or is too old -- anything that supports -- transfer-mode should do, and if not, we will fall back to SFTP or SCP. fetchFilePS :: String -> Cachable -> IO ByteString -- | 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. See fetchFilePS for details. 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 () -- | Send an email, optionally containing a patch bundle (more precisely, -- its description and the bundle itself) 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 :: SshFilePath -> [String] -> Doc -> IO ExitCode -- | Run a command on a remote location without passing it any input or -- reading its output. Return its ExitCode execSSH :: SshFilePath -> String -> IO ExitCode maybeURLCmd :: String -> String -> IO (Maybe (String)) data Cachable Cachable :: Cachable Uncachable :: Cachable MaxAge :: !CInt -> Cachable viewDoc :: Doc -> IO () viewDocWith :: Printers -> Doc -> IO () haveSendmail :: IO Bool sendmailPath :: IO String diffProgram :: IO String -- | Get the name of the darcs executable (as supplied by -- getProgName) darcsProgram :: IO String module Darcs.ColorPrinter errorDoc :: Doc -> a traceDoc :: Doc -> a -> a assertDoc :: Maybe Doc -> a -> a -- | fancyPrinters h returns a set of printers suitable for -- outputting to h fancyPrinters :: Printers instance Show Doc module Darcs.MonadProgress class Monad m => MonadProgress m runProgressActions :: MonadProgress m => String -> [ProgressAction m ()] -> m () -- | a monadic action, annotated with a progress message that could be -- printed out while running the action, and a message that could be -- printed out on error. Actually printing out these messages is optional -- to allow non-IO monads to just run the action. data ProgressAction m a ProgressAction :: m a -> Doc -> Doc -> ProgressAction m a paAction :: ProgressAction m a -> m a paMessage :: ProgressAction m a -> Doc paOnError :: ProgressAction m a -> Doc -- | run a list of ProgressActions without any feedback messages silentlyRunProgressActions :: Monad m => String -> [ProgressAction m ()] -> m () instance (Functor m, Monad m) => MonadProgress (TreeMonad m) instance MonadProgress IO module Darcs.Patch.ApplyMonad class (Functor m, Monad m, Functor (ApplyMonadBase m), Monad (ApplyMonadBase m), ToTree state) => ApplyMonad m (state :: (* -> *) -> *) where type family ApplyMonadBase m :: * -> * mReadFilePSs f = linesPS `fmap` mReadFilePS f mCreateFile f = mModifyFilePS f $ \ _ -> return empty mModifyFilePSs f j = mModifyFilePS f (fmap unlinesPS . j . linesPS) mChangePref _ _ _ = return () nestedApply :: ApplyMonad m state => m x -> state (ApplyMonadBase m) -> m (x, state (ApplyMonadBase m)) liftApply :: ApplyMonad m state => (state (ApplyMonadBase m) -> (ApplyMonadBase m) x) -> state (ApplyMonadBase m) -> m (x, state (ApplyMonadBase m)) getApplyState :: ApplyMonad m state => m (state (ApplyMonadBase m)) putApplyState :: ApplyMonad m state => state m -> m () editFile :: (ApplyMonad m state, state ~ ObjectMap) => UUID -> (ByteString -> ByteString) -> m () editDirectory :: (ApplyMonad m state, state ~ ObjectMap) => UUID -> (DirContent -> DirContent) -> m () mDoesDirectoryExist :: (ApplyMonad m state, state ~ Tree) => FileName -> m Bool mDoesFileExist :: (ApplyMonad m state, state ~ Tree) => FileName -> m Bool mReadFilePS :: (ApplyMonad m state, state ~ Tree) => FileName -> m ByteString mReadFilePSs :: (ApplyMonad m state, state ~ Tree) => FileName -> m [ByteString] mCreateDirectory :: (ApplyMonad m state, state ~ Tree) => FileName -> m () mRemoveDirectory :: (ApplyMonad m state, state ~ Tree) => FileName -> m () mCreateFile :: (ApplyMonad m state, state ~ Tree) => FileName -> m () mRemoveFile :: (ApplyMonad m state, state ~ Tree) => FileName -> m () mRename :: (ApplyMonad m state, state ~ Tree) => FileName -> FileName -> m () mModifyFilePS :: (ApplyMonad m state, state ~ Tree) => FileName -> (ByteString -> m ByteString) -> m () mModifyFilePSs :: (ApplyMonad m state, state ~ Tree) => FileName -> ([ByteString] -> m [ByteString]) -> m () mChangePref :: (ApplyMonad m state, state ~ Tree) => String -> String -> String -> m () class (Functor m, Monad m, ApplyMonad (ApplyMonadOver m state) state) => ApplyMonadTrans m (state :: (* -> *) -> *) where type family ApplyMonadOver m state :: * -> * runApplyMonad :: ApplyMonadTrans m state => (ApplyMonadOver m state) x -> state m -> m (x, state m) -- | withFileNames takes a maybe list of existing rename-pairs, a list of -- filenames and an action, and returns the resulting triple of affected -- files, updated filename list and new rename details. If the -- rename-pairs are not present, a new list is generated from the -- filesnames. withFileNames :: (Maybe [OrigFileNameOf]) -> [FileName] -> FilePathMonad a -> FilePathMonadState withFiles :: [(FileName, ByteString)] -> RestrictedApply a -> [(FileName, ByteString)] class ToTree s toTree :: ToTree s => s m -> Tree m instance MonadProgress RestrictedApply instance ApplyMonad RestrictedApply Tree instance MonadProgress FilePathMonad instance ApplyMonad FilePathMonad Tree instance (Functor m, Monad m) => ApplyMonad (TreeMonad m) Tree instance (Functor m, Monad m) => ApplyMonadTrans m Tree instance ToTree Tree module Darcs.Patch.Apply class Apply p where type family ApplyState p :: (* -> *) -> * apply :: (Apply p, ApplyMonad m (ApplyState p)) => p x y -> m () applyToFilePaths :: (Apply p, ApplyState p ~ Tree) => p x y -> Maybe [(FilePath, FilePath)] -> [FilePath] -> ([FilePath], [FilePath], [(FilePath, FilePath)]) -- | Apply a patch to a Tree, yielding a new Tree. applyToTree :: (Apply p, Functor m, Monad m, ApplyState p ~ Tree) => p x y -> Tree m -> m (Tree m) applyToState :: (Apply p, ApplyMonadTrans m (ApplyState p)) => p x y -> (ApplyState p) m -> m ((ApplyState p) m) effectOnFilePaths :: (Apply p, ApplyState p ~ Tree) => p x y -> [FilePath] -> [FilePath] instance Apply p => Apply (RL p) instance Apply p => Apply (FL p) module Darcs.Patch.Repair -- | Repair and RepairToFL deal with repairing old patches -- that were were written out due to bugs or that we no longer wish to -- support. Repair is implemented by collections of patches (FL, -- Named, PatchInfoAnd) that might need repairing. class Repair p applyAndTryToFix :: (Repair p, ApplyMonad m (ApplyState p)) => p x y -> m (Maybe (String, p x y)) -- | RepairToFL is implemented by single patches that can be -- repaired (Prim, Patch, RealPatch) There is a default so that patch -- types with no current legacy problems don't need to have an -- implementation. class Apply p => RepairToFL p where applyAndTryToFixFL p = do { apply p; return Nothing } applyAndTryToFixFL :: (RepairToFL p, ApplyMonad m (ApplyState p)) => p x y -> m (Maybe (String, FL p x y)) mapMaybeSnd :: (a -> b) -> Maybe (c, a) -> Maybe (c, b) class Check p where isInconsistent _ = Nothing isInconsistent :: Check p => p x y -> Maybe Doc instance RepairToFL p => Repair (FL p) instance Check p => Check (RL p) instance Check p => Check (FL p) module Darcs.Repository.Format -- | RepoFormat is the representation of the format of a -- repository. Each sublist corresponds to a line in the format file. -- Each line is decomposed into words. newtype RepoFormat RF :: [[ByteString]] -> RepoFormat data RepoProperty Darcs1_0 :: RepoProperty Darcs2 :: RepoProperty HashedInventory :: RepoProperty NoWorkingDir :: RepoProperty -- | identifyRepoFormat URL identifies the format of the -- repository at the given address. Fails if we weren't able to identify -- the format. identifyRepoFormat :: String -> IO RepoFormat -- | tryIdentifyRepoFormat URL identifies the format of the -- repository at the given address. Return Left reason if it -- fails, where reason explains why we weren't able to identify -- the format. tryIdentifyRepoFormat :: String -> IO (Either String RepoFormat) createRepoFormat :: [DarcsFlag] -> RepoFormat -- | writeRepoFormat writes the repo format to the given file. writeRepoFormat :: RepoFormat -> FilePath -> IO () -- | writeProblem form tells if we can write to a repo in format -- form. It returns Nothing if there's no problem -- writing to such a repository. writeProblem :: RepoFormat -> Maybe String -- | readProblem form tells if we can read from a repo in format -- form. It returns Nothing if there's no problem -- reading from such a repository. readProblem :: RepoFormat -> Maybe String -- | readfromAndWritetoProblem form tells if we can read from and -- write to a repo in format form. It returns Nothing -- if there's no problem reading and writing to such a repository. readfromAndWritetoProblem :: RepoFormat -> RepoFormat -> Maybe String formatHas :: RepoProperty -> RepoFormat -> Bool instance Show RepoFormat instance Show RepoProperty module Darcs.Repository.Motd -- | Fetch and return the message of the day for a given repository. getMotd :: String -> IO ByteString -- | Display the message of the day for a given repository, unless either -- the XMLOutput or the Quiet flags are passed in showMotd :: [DarcsFlag] -> String -> IO () -- | This module is used by the push and put commands to apply the a bundle -- to a remote repository. By remote I do not necessarily mean a -- repository on another machine, it is just not the repository we're -- located in. module Darcs.RemoteApply remoteApply :: [DarcsFlag] -> String -> Doc -> IO ExitCode applyAs :: [DarcsFlag] -> Maybe String module SHA1 sha1PS :: ByteString -> String module Darcs.Patch.Info -- | A PatchInfo value contains the metadata of a patch. The date, name, -- author and log fields are UTF-8 encoded text in darcs 2.4 and later, -- and just sequences of bytes (decoded with whatever is the locale when -- displayed) in earlier darcs. -- -- The members with names that start with '_' are not supposed to be used -- directly in code that does not care how the patch info is stored. data PatchInfo PatchInfo :: !ByteString -> !ByteString -> !ByteString -> ![ByteString] -> !Bool -> PatchInfo _piDate :: PatchInfo -> !ByteString _piName :: PatchInfo -> !ByteString _piAuthor :: PatchInfo -> !ByteString _piLog :: PatchInfo -> ![ByteString] isInverted :: PatchInfo -> !Bool patchinfo :: String -> String -> String -> [String] -> IO PatchInfo invertName :: PatchInfo -> PatchInfo idpatchinfo :: PatchInfo -- | addJunk adds a line that contains a random number to make the patch -- unique. addJunk :: PatchInfo -> IO PatchInfo makePatchname :: PatchInfo -> String -- | This makes darcs-1 (non-hashed repos) filenames, and is also generally -- used in both in hashed and non-hashed repo code for making patch -- hashes. -- -- The name consists of three segments: -- -- makeFilename :: PatchInfo -> String makeAltFilename :: PatchInfo -> String -- | Parser for PatchInfo as stored in patch bundles and inventory -- files, for example: -- --
--   [Document the foo interface
--   John Doe <john.doe@example.com>**20110615084241
--    Ignore-this: 85b94f67d377c4ab671101266ef9c229
--    Nobody knows what a 'foo' is, so describe it.
--   ]
--   
-- -- See showPatchInfo for the inverse operation. readPatchInfo :: ParserM m => m (PatchInfo) -- | Get the name, including an UNDO: prefix if the patch is -- inverted. justName :: PatchInfo -> String -- | Returns the author of a patch. justAuthor :: PatchInfo -> String justLog :: PatchInfo -> String repopatchinfo :: String -> PatchInfo -> RepoPatchInfo data RepoPatchInfo humanFriendly :: PatchInfo -> Doc toXml :: PatchInfo -> Doc piDate :: PatchInfo -> CalendarTime setPiDate :: String -> PatchInfo -> PatchInfo piDateString :: PatchInfo -> String piDateBytestring :: PatchInfo -> ByteString -- | Returns the name of the patch. Unlike justName, it does not -- preprend UNDO: to the name if the patch is inverted. piName :: PatchInfo -> String piRename :: PatchInfo -> String -> PatchInfo -- | Returns the author of a patch. piAuthor :: PatchInfo -> String -- | Get the tag name, if the patch is a tag patch. piTag :: PatchInfo -> Maybe String -- | Get the log message of a patch. piLog :: PatchInfo -> [String] -- | Patch is stored between square brackets. -- --
--   [ <patch name>
--   <patch author>*<patch date>
--    <patch log (may be empty)> (indented one)
--    <can have multiple lines in patch log,>
--    <as long as they're preceded by a space>
--    <and don't end with a square bracket.>
--   ]
--   
-- -- note that below I assume the name has no newline in it. See -- readPatchInfo for the inverse operation. showPatchInfo :: PatchInfo -> Doc isTag :: PatchInfo -> Bool readPatchInfos :: ByteString -> [PatchInfo] escapeXML :: String -> Doc instance Eq PatchInfo instance Ord PatchInfo instance Show PatchInfo instance HTML RepoPatchInfo module Darcs.Patch.Show class ShowPatchBasic p showPatch :: ShowPatchBasic p => p x y -> Doc class ShowPatchBasic p => ShowPatch p where showNicely = showPatch showContextPatch p = return $ showPatch p description = showPatch thing _ = "patch" things x = plural (Noun $ thing x) "" showNicely :: ShowPatch p => p x y -> Doc showContextPatch :: (ShowPatch p, Monad m, ApplyMonadTrans m (ApplyState p), ApplyMonad m (ApplyState p)) => p x y -> m Doc description :: ShowPatch p => p x y -> Doc summary :: ShowPatch p => p x y -> Doc summaryFL :: ShowPatch p => FL p x y -> Doc thing :: ShowPatch p => p x y -> String things :: ShowPatch p => p x y -> String showNamedPrefix :: PatchInfo -> [PatchInfo] -> Doc writePatch :: ShowPatchBasic p => FilePath -> p x y -> IO () gzWritePatch :: ShowPatchBasic p => FilePath -> p x y -> IO () formatFileName :: FileNameFormat -> FileName -> Doc module Darcs.Patch.Patchy class (MyEq p, Apply p, Commute p, PatchInspect p, ShowPatch p, ReadPatch p, Invert p) => Patchy p class Apply p where type family ApplyState p :: (* -> *) -> * apply :: (Apply p, ApplyMonad m (ApplyState p)) => p x y -> m () -- | Things that can commute. class Commute p commute :: Commute p => (p :> p) x y -> Maybe ((p :> p) x y) class Invert p invert :: Invert p => p x y -> p y x class PatchInspect p listTouchedFiles :: PatchInspect p => p x y -> [FilePath] hunkMatches :: PatchInspect p => (ByteString -> Bool) -> p x y -> Bool class ReadPatch p readPatch' :: (ReadPatch p, ParserM m) => m (Sealed (p x)) showPatch :: ShowPatchBasic p => p x y -> Doc class ShowPatchBasic p => ShowPatch p where showNicely = showPatch showContextPatch p = return $ showPatch p description = showPatch thing _ = "patch" things x = plural (Noun $ thing x) "" showNicely :: ShowPatch p => p x y -> Doc showContextPatch :: (ShowPatch p, Monad m, ApplyMonadTrans m (ApplyState p), ApplyMonad m (ApplyState p)) => p x y -> m Doc description :: ShowPatch p => p x y -> Doc summary :: ShowPatch p => p x y -> Doc summaryFL :: ShowPatch p => FL p x y -> Doc thing :: ShowPatch p => p x y -> String things :: ShowPatch p => p x y -> String module Darcs.Patch.FileHunk data FileHunk x y FileHunk :: !FileName -> !Int -> [ByteString] -> [ByteString] -> FileHunk x y class IsHunk p isHunk :: IsHunk p => p x y -> Maybe (FileHunk x y) showFileHunk :: FileNameFormat -> FileHunk x y -> Doc module Darcs.Patch.Prim.Class class PrimConstruct prim addfile :: PrimConstruct prim => FilePath -> prim x y rmfile :: PrimConstruct prim => FilePath -> prim x y adddir :: PrimConstruct prim => FilePath -> prim x y rmdir :: PrimConstruct prim => FilePath -> prim x y move :: PrimConstruct prim => FilePath -> FilePath -> prim x y changepref :: PrimConstruct prim => String -> String -> String -> prim x y hunk :: PrimConstruct prim => FilePath -> Int -> [ByteString] -> [ByteString] -> prim x y tokreplace :: PrimConstruct prim => FilePath -> String -> String -> String -> prim x y binary :: PrimConstruct prim => FilePath -> ByteString -> ByteString -> prim x y primFromHunk :: PrimConstruct prim => FileHunk x y -> prim x y anIdentity :: PrimConstruct prim => prim x x class PrimCanonize prim tryToShrink :: PrimCanonize prim => FL prim x y -> FL prim x y tryShrinkingInverse :: PrimCanonize prim => FL prim x y -> Maybe (FL prim x y) sortCoalesceFL :: PrimCanonize prim => FL prim x y -> FL prim x y canonize :: PrimCanonize prim => prim x y -> FL prim x y canonizeFL :: PrimCanonize prim => FL prim x y -> FL prim x y join :: PrimCanonize prim => (prim :> prim) x y -> Maybe (FL prim x y) class PrimClassify prim primIsAddfile :: PrimClassify prim => prim x y -> Bool primIsRmfile :: PrimClassify prim => prim x y -> Bool primIsAdddir :: PrimClassify prim => prim x y -> Bool primIsRmdir :: PrimClassify prim => prim x y -> Bool primIsMove :: PrimClassify prim => prim x y -> Bool primIsHunk :: PrimClassify prim => prim x y -> Bool primIsTokReplace :: PrimClassify prim => prim x y -> Bool primIsBinary :: PrimClassify prim => prim x y -> Bool primIsSetpref :: PrimClassify prim => prim x y -> Bool is_filepatch :: PrimClassify prim => prim x y -> Maybe FileName class PrimDetails prim summarizePrim :: PrimDetails prim => prim x y -> [SummDetail] class PrimShow prim showPrim :: PrimShow prim => FileNameFormat -> prim a b -> Doc showPrimFL :: PrimShow prim => FileNameFormat -> FL prim a b -> Doc class PrimRead prim readPrim :: (PrimRead prim, ParserM m) => FileNameFormat -> m (Sealed (prim x)) class PrimApply prim applyPrimFL :: (PrimApply prim, ApplyMonad m (ApplyState prim)) => FL prim x y -> m () class (Patchy prim, PatchListFormat prim, IsHunk prim, RepairToFL prim, PrimConstruct prim, PrimCanonize prim, PrimClassify prim, PrimDetails prim, PrimShow prim, PrimRead prim, PrimApply prim) => PrimPatch prim class PrimPatch (PrimOf p) => PrimPatchBase p where type family PrimOf (p :: * -> * -> *) :: * -> * -> * class FromPrim p fromPrim :: FromPrim p => PrimOf p x y -> p x y class FromPrims p fromPrims :: FromPrims p => FL (PrimOf p) x y -> p x y joinPatches :: FromPrims p => FL p x y -> p x y class FromPrim p => ToFromPrim p toPrim :: ToFromPrim p => p x y -> Maybe (PrimOf p x y) instance FromPrim p => FromPrims (RL p) instance FromPrim p => FromPrims (FL p) instance FromPrim p => FromPrim (FL p) instance PrimPatchBase p => PrimPatchBase (RL p) instance PrimPatchBase p => PrimPatchBase (FL p) module Darcs.Patch.Prim showPrim :: PrimShow prim => FileNameFormat -> prim a b -> Doc showPrimFL :: PrimShow prim => FileNameFormat -> FL prim a b -> Doc primIsAddfile :: PrimClassify prim => prim x y -> Bool primIsHunk :: PrimClassify prim => prim x y -> Bool primIsBinary :: PrimClassify prim => prim x y -> Bool primIsSetpref :: PrimClassify prim => prim x y -> Bool primIsAdddir :: PrimClassify prim => prim x y -> Bool is_filepatch :: PrimClassify prim => prim x y -> Maybe FileName -- | It can sometimes be handy to have a canonical representation of a -- given patch. We achieve this by defining a canonical form for each -- patch type, and a function canonize which takes a patch and -- puts it into canonical form. This routine is used by the diff function -- to create an optimal patch (based on an LCS algorithm) from a simple -- hunk describing the old and new version of a file. canonize :: PrimCanonize prim => prim x y -> FL prim x y tryToShrink :: PrimCanonize prim => FL prim x y -> FL prim x y -- | sortCoalesceFL ps coalesces as many patches in -- ps as possible, sorting the results in some standard order. sortCoalesceFL :: PrimCanonize prim => FL prim x y -> FL prim x y join :: PrimCanonize prim => (prim :> prim) x y -> Maybe (FL prim x y) -- | canonizeFL ps puts a sequence of primitive patches -- into canonical form. Even if the patches are just hunk patches, this -- is not necessarily the same set of results as you would get if you -- applied the sequence to a specific tree and recalculated a diff. -- -- Note that this process does not preserve the commutation behaviour of -- the patches and is therefore not appropriate for use when working with -- already recorded patches (unless doing amend-record or the like). canonizeFL :: PrimCanonize prim => FL prim x y -> FL prim x y tryShrinkingInverse :: PrimCanonize prim => FL prim x y -> Maybe (FL prim x y) summarizePrim :: PrimDetails prim => prim x y -> [SummDetail] applyPrimFL :: (PrimApply prim, ApplyMonad m (ApplyState prim)) => FL prim x y -> m () readPrim :: (PrimRead prim, ParserM m) => FileNameFormat -> m (Sealed (prim x)) class FromPrim p fromPrim :: FromPrim p => PrimOf p x y -> p x y class FromPrims p fromPrims :: FromPrims p => FL (PrimOf p) x y -> p x y joinPatches :: FromPrims p => FL p x y -> p x y class FromPrim p => ToFromPrim p toPrim :: ToFromPrim p => p x y -> Maybe (PrimOf p x y) class (Patchy prim, PatchListFormat prim, IsHunk prim, RepairToFL prim, PrimConstruct prim, PrimCanonize prim, PrimClassify prim, PrimDetails prim, PrimShow prim, PrimRead prim, PrimApply prim) => PrimPatch prim class PrimPatch (PrimOf p) => PrimPatchBase p where type family PrimOf (p :: * -> * -> *) :: * -> * -> * class PrimConstruct prim addfile :: PrimConstruct prim => FilePath -> prim x y rmfile :: PrimConstruct prim => FilePath -> prim x y adddir :: PrimConstruct prim => FilePath -> prim x y rmdir :: PrimConstruct prim => FilePath -> prim x y move :: PrimConstruct prim => FilePath -> FilePath -> prim x y changepref :: PrimConstruct prim => String -> String -> String -> prim x y hunk :: PrimConstruct prim => FilePath -> Int -> [ByteString] -> [ByteString] -> prim x y tokreplace :: PrimConstruct prim => FilePath -> String -> String -> String -> prim x y binary :: PrimConstruct prim => FilePath -> ByteString -> ByteString -> prim x y primFromHunk :: PrimConstruct prim => FileHunk x y -> prim x y anIdentity :: PrimConstruct prim => prim x x module Darcs.Patch.V1.Core data Patch prim x y PP :: prim x y -> Patch prim x y Merger :: FL (Patch prim) x y -> RL (Patch prim) x b -> Patch prim c b -> Patch prim c d -> Patch prim x y Regrem :: FL (Patch prim) x y -> RL (Patch prim) x b -> Patch prim c b -> Patch prim c a -> Patch prim y x isMerger :: Patch prim a b -> Bool mergerUndo :: Patch prim x y -> FL (Patch prim) x y instance Check (Patch prim) instance PatchListFormat (Patch prim) instance FromPrim (Patch prim) instance PrimPatch prim => PrimPatchBase (Patch prim) module Darcs.Patch.V1.Show showPatch_ :: PrimPatch prim => Patch prim a b -> Doc instance PrimPatch prim => Show2 (Patch prim) instance PrimPatch prim => Show1 (Patch prim x) instance PrimPatch prim => Show (Patch prim x y) module Darcs.Patch.Effect -- | Patches whose concrete effect which can be expressed as a list of -- primitive patches. -- -- A minimal definition would be either of effect or -- effectRL. class Effect p where effect = reverseRL . effectRL effectRL = reverseFL . effect effect :: Effect p => p x y -> FL (PrimOf p) x y effectRL :: Effect p => p x y -> RL (PrimOf p) x y instance Effect p => Effect (RL p) instance Effect p => Effect (FL p) module Darcs.Patch.Conflict class (Effect p, PatchInspect (PrimOf p)) => Conflict p where listConflictedFiles p = nubsort $ concatMap (unseal listTouchedFiles) $ concat $ resolveConflicts p conflictedEffect x = case listConflictedFiles x of { [] -> mapFL (IsC Okay) $ effect x _ -> mapFL (IsC Conflicted) $ effect x } listConflictedFiles :: Conflict p => p x y -> [FilePath] resolveConflicts :: Conflict p => p x y -> [[Sealed (FL (PrimOf p) y)]] conflictedEffect :: Conflict p => p x y -> [IsConflictedPrim (PrimOf p)] class CommuteNoConflicts p commuteNoConflicts :: CommuteNoConflicts p => (p :> p) x y -> Maybe ((p :> p) x y) data IsConflictedPrim prim IsC :: !ConflictState -> !(prim x y) -> IsConflictedPrim prim data ConflictState Okay :: ConflictState Conflicted :: ConflictState Duplicated :: ConflictState instance Eq ConflictState instance Ord ConflictState instance Show ConflictState instance Read ConflictState instance CommuteNoConflicts p => CommuteNoConflicts (RL p) instance (CommuteNoConflicts p, Conflict p) => Conflict (RL p) instance CommuteNoConflicts p => CommuteNoConflicts (FL p) instance (CommuteNoConflicts p, Conflict p) => Conflict (FL p) module Darcs.Patch.Summary plainSummary :: (Conflict e, Effect e, PrimPatchBase e) => e x y -> Doc plainSummaryPrim :: PrimDetails prim => prim x y -> Doc plainSummaryPrims :: PrimDetails prim => FL prim x y -> Doc xmlSummary :: (Effect p, Conflict p, PrimPatchBase p) => p x y -> Doc instance Ord SummChunk instance Eq SummChunk module Darcs.Patch.ConflictMarking mangleUnravelled :: PrimPatch prim => [Sealed (FL prim x)] -> Sealed (FL prim x) module Darcs.Patch.V1.Commute merge :: Merge p => (p :\/: p) x y -> (p :/\: p) x y merger :: PrimPatch prim => String -> Patch prim x y -> Patch prim x z -> Sealed (Patch prim y) unravel :: PrimPatch prim => Patch prim x y -> [Sealed (FL prim x)] publicUnravel :: PrimPatch prim => Patch prim x y -> [Sealed (FL prim y)] instance MyEq prim => Eq (Patch prim x y) instance MyEq prim => MyEq (Patch prim) instance Invert prim => Invert (Patch prim) instance IsHunk prim => IsHunk (Patch prim) instance PrimPatch prim => Effect (Patch prim) instance PrimPatch prim => Conflict (Patch prim) instance PrimPatch prim => CommuteNoConflicts (Patch prim) instance PrimPatch prim => PatchInspect (Patch prim) instance PrimPatch prim => Commute (Patch prim) instance PrimPatch prim => Merge (Patch prim) instance MonadPlus Perhaps instance Monad Perhaps module Darcs.Patch.V1.Apply instance PrimPatch prim => RepairToFL (Patch prim) instance PrimPatch prim => Apply (Patch prim) module Darcs.Patch.V1.Read instance PrimPatch prim => ReadPatch (Patch prim) module Darcs.Patch.Prim.V1.Core data Prim x y Move :: !FileName -> !FileName -> Prim x y DP :: !FileName -> !(DirPatchType x y) -> Prim x y FP :: !FileName -> !(FilePatchType x y) -> Prim x y ChangePref :: !String -> !String -> !String -> Prim x y data DirPatchType x y RmDir :: DirPatchType x y AddDir :: DirPatchType x y data FilePatchType x y RmFile :: FilePatchType x y AddFile :: FilePatchType x y Hunk :: !Int -> [ByteString] -> [ByteString] -> FilePatchType x y TokReplace :: !String -> !String -> !String -> FilePatchType x y Binary :: ByteString -> ByteString -> FilePatchType x y isIdentity :: Prim x y -> EqCheck x y -- | comparePrim p1 p2 is used to provide an arbitrary -- ordering between p1 and p2. Basically, identical -- patches are equal and Move < DP < FP < ChangePref. -- Everything else is compared in dictionary order of its arguments. comparePrim :: Prim x y -> Prim w z -> Ordering instance Eq (FilePatchType x y) instance Ord (FilePatchType x y) instance Eq (DirPatchType x y) instance Ord (DirPatchType x y) instance Eq (Prim x y) instance MyEq Prim instance PatchInspect Prim instance Invert Prim instance IsHunk Prim instance PrimConstruct Prim instance PrimClassify Prim instance MyEq DirPatchType instance MyEq FilePatchType module Darcs.Patch.Prim.V1.Commute data Perhaps a Unknown :: Perhaps a Failed :: Perhaps a Succeeded :: a -> Perhaps a subcommutes :: [(String, WrappedCommuteFunction)] newtype WrappedCommuteFunction WrappedCommuteFunction :: CommuteFunction -> WrappedCommuteFunction runWrappedCommuteFunction :: WrappedCommuteFunction -> CommuteFunction instance Commute Prim instance MonadPlus Perhaps instance Monad Perhaps module Darcs.Patch.Prim.V1.Details instance PrimDetails Prim module Darcs.Patch.Prim.V1.Read instance PrimRead Prim instance ReadPatch Prim module Darcs.Patch.Prim.V3.Core data Prim x y BinaryHunk :: !UUID -> Hunk x y -> Prim x y TextHunk :: !UUID -> Hunk x y -> Prim x y Manifest :: !UUID -> Location -> Prim x y Demanifest :: !UUID -> Location -> Prim x y Move :: !UUID -> Location -> Location -> Prim x y Identity :: Prim x x data Hunk x y Hunk :: !Int -> ByteString -> ByteString -> Hunk x y newtype UUID UUID :: ByteString -> UUID type Location = (UUID, ByteString) data Object (m :: * -> *) Directory :: DirContent -> Object Blob :: (m ByteString) -> !Hash -> Object touches :: Prim x y -> [UUID] hunkEdit :: Hunk x y -> ByteString -> ByteString instance Eq (Prim x y) instance MyEq Prim instance PatchInspect Prim instance Invert Prim instance IsHunk Prim instance PrimConstruct Prim instance PrimClassify Prim instance MyEq Hunk module Darcs.Patch.Prim.V3.Apply data ObjectMap (m :: * -> *) ObjectMap :: (UUID -> m (Maybe (Object m))) -> (UUID -> Object m -> m (ObjectMap m)) -> m [UUID] -> ObjectMap getObject :: ObjectMap -> UUID -> m (Maybe (Object m)) putObject :: ObjectMap -> UUID -> Object m -> m (ObjectMap m) listObjects :: ObjectMap -> m [UUID] instance (Functor m, Monad m) => ApplyMonadTrans m ObjectMap instance (Functor m, Monad m) => ApplyMonad (StateT (ObjectMap m) m) ObjectMap instance ToTree ObjectMap instance PrimApply Prim instance RepairToFL Prim instance Apply Prim module Darcs.Patch.Prim.V3.Coalesce instance PrimCanonize Prim module Darcs.Patch.Prim.V3.Commute class Monad m => CommuteMonad m commuteFail :: CommuteMonad m => m a instance Commute' Prim instance Commute Prim instance CommuteMonad Maybe module Darcs.Patch.Prim.V3.Details instance PrimDetails Prim module Darcs.Patch.Prim.V3.Read instance ReadPatch Prim instance PrimRead Prim module Darcs.Patch.Dummy data DummyPatch x y instance Patchy DummyPatch instance Apply DummyPatch instance Commute DummyPatch instance ShowPatch DummyPatch instance ShowPatchBasic DummyPatch instance ReadPatch DummyPatch instance PatchInspect DummyPatch instance Invert DummyPatch instance MyEq DummyPatch instance PatchListFormat DummyPatch instance IsHunk DummyPatch module Darcs.Patch.Bracketed.Instances instance ShowPatchBasic p => ShowPatchBasic (Bracketed p) module Darcs.Patch.Viewing showContextHunk :: ApplyMonad m Tree => FileHunk x y -> m Doc showContextSeries :: (Apply p, ShowPatch p, IsHunk p, ApplyMonadTrans m (ApplyState p), ApplyMonad m (ApplyState p)) => FL p x y -> m Doc instance (Apply p, IsHunk p, PatchListFormat p, ShowPatch p) => ShowPatch (RL p) instance (PatchListFormat p, ShowPatchBasic p) => ShowPatchBasic (RL p) instance (Apply p, IsHunk p, PatchListFormat p, ShowPatch p) => ShowPatch (FL p) instance (PatchListFormat p, ShowPatchBasic p) => ShowPatchBasic (FL p) module Darcs.Patch.Split -- | A splitter is something that can take a patch and (possibly) render it -- as text in some format of its own choosing. This text can then be -- presented to the user for editing, and the result given to the -- splitter for parsing. If the parse succeeds, the result is a list of -- patches that could replace the original patch in any context. -- Typically this list will contain the changed version of the patch, -- along with fixup pieces to ensure that the overall effect of the list -- is the same as the original patch. The individual elements of the list -- can then be offered separately to the user, allowing them to accept -- some and reject others. -- -- There's no immediate application for a splitter for anything other -- than Prim (you shouldn't go editing named patches, you'll break them!) -- However you might want to compose splitters for FilePatchType to make -- splitters for Prim etc, and the generality doesn't cost anything. data Splitter p Splitter :: (forall x y. p x y -> Maybe (ByteString, ByteString -> Maybe (FL p x y))) -> (forall x y. FL p x y -> FL p x y) -> Splitter p applySplitter :: Splitter p -> forall x y. p x y -> Maybe (ByteString, ByteString -> Maybe (FL p x y)) canonizeSplit :: Splitter p -> forall x y. FL p x y -> FL p x y -- | This generic splitter just lets the user edit the printed -- representation of the patch Should not be used expect for testing and -- experimentation. rawSplitter :: (ShowPatch p, ReadPatch p, Invert p) => Splitter p -- | Never splits. In other code we normally pass around Maybe Splitter -- instead of using this as the default, because it saves clients that -- don't care about splitting from having to import this module just to -- get noSplitter. noSplitter :: Splitter p -- | Split a primitive hunk patch up by allowing the user to edit both the -- before and after lines, then insert fixup patches to clean up the -- mess. primSplitter :: PrimPatch p => Splitter p reversePrimSplitter :: PrimPatch prim => Splitter prim module Darcs.Patch.Named -- | The Named type adds a patch info about a patch, that is a -- name. -- -- NamedP info deps p represents patch p with name -- info. deps is a list of dependencies added at the -- named patch level, compared with the unnamed level (ie, dependencies -- added with darcs record --ask-deps). data Named p x y NamedP :: !PatchInfo -> ![PatchInfo] -> !(FL p x y) -> Named p x y infopatch :: Patchy p => PatchInfo -> FL p x y -> Named p x y adddeps :: Named p x y -> [PatchInfo] -> Named p x y namepatch :: Patchy p => String -> String -> String -> [String] -> FL p x y -> IO (Named p x y) anonymous :: Patchy p => FL p x y -> IO (Named p x y) getdeps :: Named p x y -> [PatchInfo] patch2patchinfo :: Named p x y -> PatchInfo patchname :: Named p x y -> String patchcontents :: Named p x y -> FL p x y fmapNamed :: (forall a b. p a b -> q a b) -> Named p x y -> Named q x y fmapFL_Named :: (FL p x y -> FL q x y) -> Named p x y -> Named q x y instance (PatchListFormat p, ShowPatch p) => Show2 (Named p) instance (PatchListFormat p, ShowPatch p) => Show1 (Named p x) instance (PatchListFormat p, ShowPatch p) => Show (Named p x y) instance (Apply p, CommuteNoConflicts p, Conflict p, IsHunk p, PatchListFormat p, PrimPatchBase p, ShowPatch p) => ShowPatch (Named p) instance (PatchListFormat p, ShowPatchBasic p) => ShowPatchBasic (Named p) instance Check p => Check (Named p) instance (CommuteNoConflicts p, Conflict p) => Conflict (Named p) instance PatchInspect p => PatchInspect (Named p) instance Merge p => Merge (Named p) instance Commute p => Commute (Named p) instance (Commute p, Invert p) => Invert (Named p) instance (Commute p, MyEq p) => MyEq (Named p) instance RepairToFL p => Repair (Named p) instance Apply p => Apply (Named p) instance (ReadPatch p, PatchListFormat p) => ReadPatch (Named p) instance PatchListFormat (Named p) instance IsHunk (Named p) instance Effect p => Effect (Named p) instance PrimPatchBase p => PrimPatchBase (Named p) module Darcs.Patch.Patchy.Instances instance (IsHunk p, PatchListFormat p, Patchy p) => Patchy (RL p) instance (IsHunk p, PatchListFormat p, Patchy p) => Patchy (FL p) module Darcs.Patch.RepoPatch class (Patchy p, Merge p, Effect p, IsHunk p, FromPrim p, Conflict p, CommuteNoConflicts p, Check p, RepairToFL p, PatchListFormat p, PrimPatchBase p, Patchy (PrimOf p), IsHunk (PrimOf p)) => RepoPatch p module Darcs.Patch class (Patchy p, Merge p, Effect p, IsHunk p, FromPrim p, Conflict p, CommuteNoConflicts p, Check p, RepairToFL p, PatchListFormat p, PrimPatchBase p, Patchy (PrimOf p), IsHunk (PrimOf p)) => RepoPatch p -- | The Named type adds a patch info about a patch, that is a -- name. -- -- NamedP info deps p represents patch p with name -- info. deps is a list of dependencies added at the -- named patch level, compared with the unnamed level (ie, dependencies -- added with darcs record --ask-deps). data Named p x y class (MyEq p, Apply p, Commute p, PatchInspect p, ShowPatch p, ReadPatch p, Invert p) => Patchy p joinPatches :: FromPrims p => FL p x y -> p x y fromPrim :: FromPrim p => PrimOf p x y -> p x y fromPrims :: FromPrims p => FL (PrimOf p) x y -> p x y rmfile :: PrimConstruct prim => FilePath -> prim x y addfile :: PrimConstruct prim => FilePath -> prim x y rmdir :: PrimConstruct prim => FilePath -> prim x y adddir :: PrimConstruct prim => FilePath -> prim x y move :: PrimConstruct prim => FilePath -> FilePath -> prim x y hunk :: PrimConstruct prim => FilePath -> Int -> [ByteString] -> [ByteString] -> prim x y tokreplace :: PrimConstruct prim => FilePath -> String -> String -> String -> prim x y namepatch :: Patchy p => String -> String -> String -> [String] -> FL p x y -> IO (Named p x y) anonymous :: Patchy p => FL p x y -> IO (Named p x y) binary :: PrimConstruct prim => FilePath -> ByteString -> ByteString -> prim x y description :: ShowPatch p => p x y -> Doc -- | showContextPatch is used to add context to a patch, as diff -u does. -- Thus, it differs from showPatch only for hunks. It is used for -- instance before putting it into a bundle. As this unified context is -- not included in patch representation, this requires access to the -- tree. showContextPatch :: (ShowPatch p, Monad m, ApplyMonadTrans m (ApplyState p), ApplyMonad m (ApplyState p)) => p x y -> m Doc showPatch :: ShowPatchBasic p => p x y -> Doc showNicely :: ShowPatch p => p x y -> Doc infopatch :: Patchy p => PatchInfo -> FL p x y -> Named p x y changepref :: PrimConstruct prim => String -> String -> String -> prim x y thing :: ShowPatch p => p x y -> String things :: ShowPatch p => p x y -> String primIsAddfile :: PrimClassify prim => prim x y -> Bool primIsHunk :: PrimClassify prim => prim x y -> Bool primIsSetpref :: PrimClassify prim => prim x y -> Bool merge :: Merge p => (p :\/: p) x y -> (p :/\: p) x y commute :: Commute p => (p :> p) x y -> Maybe ((p :> p) x y) listTouchedFiles :: PatchInspect p => p x y -> [FilePath] hunkMatches :: PatchInspect p => (ByteString -> Bool) -> p x y -> Bool forceTokReplace :: String -> String -> String -> ByteString -> Maybe ByteString class (Patchy prim, PatchListFormat prim, IsHunk prim, RepairToFL prim, PrimConstruct prim, PrimCanonize prim, PrimClassify prim, PrimDetails prim, PrimShow prim, PrimRead prim, PrimApply prim) => PrimPatch prim resolveConflicts :: Conflict p => p x y -> [[Sealed (FL (PrimOf p) y)]] -- | Patches whose concrete effect which can be expressed as a list of -- primitive patches. -- -- A minimal definition would be either of effect or -- effectRL. class Effect p where effect = reverseRL . effectRL effectRL = reverseFL . effect effect :: Effect p => p x y -> FL (PrimOf p) x y primIsBinary :: PrimClassify prim => prim x y -> Bool gzWritePatch :: ShowPatchBasic p => FilePath -> p x y -> IO () writePatch :: ShowPatchBasic p => FilePath -> p x y -> IO () primIsAdddir :: PrimClassify prim => prim x y -> Bool invert :: Invert p => p x y -> p y x invertFL :: Invert p => FL p x y -> RL p y x invertRL :: Invert p => RL p x y -> FL p y x commuteFLorComplain :: Commute p => (p :> FL p) x y -> Either (Sealed2 p) ((FL p :> p) x y) commuteRL :: Commute p => (RL p :> p) x y -> Maybe ((p :> RL p) x y) readPatch :: ReadPatch p => ByteString -> Maybe (Sealed (p x)) readPatchPartial :: ReadPatch p => ByteString -> Maybe (Sealed (p x), ByteString) -- | It can sometimes be handy to have a canonical representation of a -- given patch. We achieve this by defining a canonical form for each -- patch type, and a function canonize which takes a patch and -- puts it into canonical form. This routine is used by the diff function -- to create an optimal patch (based on an LCS algorithm) from a simple -- hunk describing the old and new version of a file. canonize :: PrimCanonize prim => prim x y -> FL prim x y -- | sortCoalesceFL ps coalesces as many patches in -- ps as possible, sorting the results in some standard order. sortCoalesceFL :: PrimCanonize prim => FL prim x y -> FL prim x y tryToShrink :: PrimCanonize prim => FL prim x y -> FL prim x y patchname :: Named p x y -> String patchcontents :: Named p x y -> FL p x y applyToFilePaths :: (Apply p, ApplyState p ~ Tree) => p x y -> Maybe [(FilePath, FilePath)] -> [FilePath] -> ([FilePath], [FilePath], [(FilePath, FilePath)]) apply :: (Apply p, ApplyMonad m (ApplyState p)) => p x y -> m () -- | Apply a patch to a Tree, yielding a new Tree. applyToTree :: (Apply p, Functor m, Monad m, ApplyState p ~ Tree) => p x y -> Tree m -> m (Tree m) effectOnFilePaths :: (Apply p, ApplyState p ~ Tree) => p x y -> [FilePath] -> [FilePath] patch2patchinfo :: Named p x y -> PatchInfo summary :: ShowPatch p => p x y -> Doc summaryFL :: ShowPatch p => FL p x y -> Doc plainSummary :: (Conflict e, Effect e, PrimPatchBase e) => e x y -> Doc xmlSummary :: (Effect p, Conflict p, PrimPatchBase p) => p x y -> Doc plainSummaryPrims :: PrimDetails prim => FL prim x y -> Doc adddeps :: Named p x y -> [PatchInfo] -> Named p x y getdeps :: Named p x y -> [PatchInfo] listConflictedFiles :: Conflict p => p x y -> [FilePath] isInconsistent :: Check p => p x y -> Maybe Doc instance (CommuteNoConflicts p, Conflict p, IsHunk p, PatchListFormat p, PrimPatchBase p, Patchy p, ApplyState p ~ Tree) => Patchy (Named p) module Darcs.Patch.PatchInfoAnd -- | Hopefully p C (x y) is Either -- String (p C (x y)) in a form adapted to darcs patches. -- The C (x y) represents the type witness for the -- patch that should be there. The Hopefully type just tells -- whether we expect the patch to be hashed or not, and -- SimpleHopefully does the real work of emulating Either. -- Hopefully sh represents an expected unhashed patch, and -- Hashed hash sh represents an expected hashed patch with its -- hash. data Hopefully a x y -- | PatchInfoAnd p a b represents a hope we have to get a -- patch through its info. We're not sure we have the patch, but we know -- its info. data PatchInfoAnd p a b -- | WPatchInfo a b represents the info of a patch, marked -- with the patch's witnesses. data WPatchInfo a b unWPatchInfo :: WPatchInfo a b -> PatchInfo compareWPatchInfo :: WPatchInfo a b -> WPatchInfo c d -> EqCheck (a, b) (c, d) -- | piap i p creates a PatchInfoAnd containing p with info -- i. piap :: PatchInfo -> Named p a b -> PatchInfoAnd p a b -- | n2pia creates a PatchInfoAnd representing a Named -- patch. n2pia :: Named p x y -> PatchInfoAnd p x y patchInfoAndPatch :: PatchInfo -> Hopefully (Named p) a b -> PatchInfoAnd p a b fmapPIAP :: (forall a b. p a b -> q a b) -> PatchInfoAnd p x y -> PatchInfoAnd q x y fmapFL_PIAP :: (FL p x y -> FL q x y) -> PatchInfoAnd p x y -> PatchInfoAnd q x y -- | conscientiously er hp tries to extract a patch from a -- PatchInfoAnd. If it fails, it applies the error handling -- function er to a description of the patch info component of -- hp. conscientiously :: (Doc -> Doc) -> PatchInfoAnd p a b -> Named p a b -- | hopefully hp tries to get a patch from a -- PatchInfoAnd value. If it fails, it outputs an error "failed to -- read patch: <description of the patch>". We get the description -- of the patch from the info part of hp hopefully :: PatchInfoAnd p a b -> Named p a b info :: PatchInfoAnd p a b -> PatchInfo winfo :: PatchInfoAnd p a b -> WPatchInfo a b -- | hopefullyM is a version of hopefully which calls -- fail in a monad instead of erroring. hopefullyM :: Monad m => PatchInfoAnd p a b -> m (Named p a b) createHashed :: String -> (String -> IO (Sealed (a x))) -> IO (Sealed (Hopefully a x)) extractHash :: PatchInfoAnd p a b -> Either (Named p a b) String actually :: a x y -> Hopefully a x y unavailable :: String -> Hopefully a x y patchDesc :: PatchInfoAnd p x y -> String instance (RepoPatch p, ApplyState p ~ Tree) => Patchy (PatchInfoAnd p) instance IsHunk (PatchInfoAnd p) instance Effect p => Effect (PatchInfoAnd p) instance (ReadPatch p, PatchListFormat p) => ReadPatch (PatchInfoAnd p) instance RepairToFL p => Repair (PatchInfoAnd p) instance Apply p => Apply (PatchInfoAnd p) instance PatchInspect p => PatchInspect (PatchInfoAnd p) instance Merge p => Merge (PatchInfoAnd p) instance Commute p => Commute (PatchInfoAnd p) instance (Apply p, Conflict p, CommuteNoConflicts p, IsHunk p, PatchListFormat p, PrimPatchBase p, ShowPatch p, ApplyState p ~ Tree) => ShowPatch (PatchInfoAnd p) instance (PatchListFormat p, ShowPatchBasic p) => ShowPatchBasic (PatchInfoAnd p) instance PatchListFormat (PatchInfoAnd p) instance (Commute p, Invert p) => Invert (PatchInfoAnd p) instance (Commute p, MyEq p) => MyEq (PatchInfoAnd p) instance MyEq WPatchInfo instance PrimPatchBase p => PrimPatchBase (PatchInfoAnd p) module Darcs.Annotate annotate :: (Apply p, ApplyState p ~ Tree) => FL (PatchInfoAnd p) x y -> FileName -> ByteString -> Annotated annotateDirectory :: (Apply p, ApplyState p ~ Tree) => FL (PatchInfoAnd p) x y -> FileName -> [FileName] -> Annotated format :: ByteString -> Annotated -> String machineFormat :: ByteString -> Annotated -> String instance Show FileOrDirectory instance Eq FileOrDirectory instance Show Annotated instance ApplyMonad AnnotatedM Tree module Darcs.Patch.Set data PatchSet p start y PatchSet :: RL (PatchInfoAnd p) x y -> RL (Tagged p) start x -> PatchSet p start y data Tagged p x z Tagged :: PatchInfoAnd p y z -> Maybe String -> RL (PatchInfoAnd p) x y -> Tagged p x z type SealedPatchSet p start = Sealed ((PatchSet p) start) data Origin -- | Runs a progress action for each tag and patch in a given PatchSet, -- using the passed progress message. Does not alter the PatchSet. progressPatchSet :: String -> PatchSet p start x -> PatchSet p start x -- | tags returns the PatchInfos corresponding to the tags of a given -- PatchSet. tags :: PatchSet p start x -> [PatchInfo] -- | appendPSFL takes a PatchSet and a FL of patches that follow -- the PatchSet, and concatenates the patches into the PatchSet. appendPSFL :: PatchSet p start x -> FL (PatchInfoAnd p) x y -> PatchSet p start y -- | newset2RL takes a PatchSet and returns an equivalent, linear RL of -- patches. newset2RL :: PatchSet p start x -> RL (PatchInfoAnd p) start x -- | newset2FL takes a PatchSet and returns an equivalent, linear FL of -- patches. newset2FL :: PatchSet p start x -> FL (PatchInfoAnd p) start x module Darcs.ProgressPatches -- | Evaluate an RL list and report progress. progressRL :: String -> RL a x y -> RL a x y -- | Evaluate an FL list and report progress. progressFL :: String -> FL a x y -> FL a x y -- | Evaluate an RL list and report progress. In addition to -- printing the number of patches we got, show the name of the last tag -- we got. progressRLShowTags :: String -> RL (PatchInfoAnd p) x y -> RL (PatchInfoAnd p) x y module Darcs.CommandsAux -- | A convenience function to call from all darcs command functions before -- applying any patches. It checks for malicious paths in patches, and -- prints an error message and fails if it finds one. checkPaths :: Patchy p => [DarcsFlag] -> FL p x y -> IO () -- | Filter out patches that contains some malicious file path maliciousPatches :: Patchy p => [Sealed2 p] -> [Sealed2 p] hasMaliciousPath :: Patchy p => p x y -> Bool -- | What is a malicious path? -- -- A spoofed path is a malicious path. -- --
    --
  1. Darcs only creates explicitly relative paths (beginning with -- "./"), so any not explicitly relative path is surely -- spoofed.
  2. --
  3. Darcs normalizes paths so they never contain "/../", so -- paths with "/../" are surely spoofed.
  4. --
-- -- A path to a darcs repository's meta data can modify "trusted" patches -- or change safety defaults in that repository, so we check for paths -- containing "/_darcs/" which is the entry to darcs meta data. -- -- To do? -- -- isMaliciousPath :: String -> Bool -- | Warning : this is less rigorous than isMaliciousPath but it's to allow -- for subpath representations that don't start with ./ isMaliciousSubPath :: String -> Bool module Darcs.Patch.Depends -- | getTagsRight ps returns the PatchInfo for all the -- patches in ps that are not depended on by anything else -- *through explicit dependencies*. Tags are a likely candidate, although -- we may also find some non-tag patches in this list. -- -- Keep in mind that in a typical repository with a lot of tags, only a -- small fraction of tags would be returned as they would be at least -- indirectly depended on by the topmost ones. getTagsRight :: PatchSet p start x -> [PatchInfo] areUnrelatedRepos :: RepoPatch p => PatchSet p start x -> PatchSet p start y -> Bool mergeThem :: RepoPatch p => PatchSet p start x -> PatchSet p start y -> Sealed (FL (PatchInfoAnd p) x) findCommonWithThem :: RepoPatch p => PatchSet p start x -> PatchSet p start y -> (PatchSet p :> FL (PatchInfoAnd p)) start x countUsThem :: RepoPatch p => PatchSet p start x -> PatchSet p start y -> (Int, Int) removeFromPatchSet :: RepoPatch p => FL (PatchInfoAnd p) x y -> PatchSet p start y -> Maybe (PatchSet p start x) -- | optimizePatchset is similar to -- slightlyOptimizePatchset in that it only works on the surface -- inventory (see below), but it works a bit harder and can optimize -- several tags. -- -- optimizePatchset :: PatchSet p start x -> PatchSet p start x -- | deepOptimizePatchset runs through all patches whether they -- are in the surface inventory or the deep one. deepOptimizePatchset :: PatchSet p start x -> PatchSet p start x -- | slightlyOptimizePatchset only works on the surface inventory -- (see optimizePatchset) and only optimises at most one tag in -- there, going for the most recent tag which has no non-depended patch -- after it. Older tags won't be clean, which means the PatchSet -- will not be in 'unclean :< clean' state. slightlyOptimizePatchset :: PatchSet p start x -> PatchSet p start x getPatchesBeyondTag :: RepoPatch p => PatchInfo -> PatchSet p start x -> FlippedSeal (RL (PatchInfoAnd p)) x -- | getPatchesInTag t ps returns a SealedPatchSet of all -- patches in ps which are contained in t. getPatchesInTag :: RepoPatch p => PatchInfo -> PatchSet p start x -> SealedPatchSet p start splitOnTag :: RepoPatch p => PatchInfo -> PatchSet p start x -> (PatchSet p :> RL (PatchInfoAnd p)) start x newsetUnion :: RepoPatch p => [SealedPatchSet p start] -> SealedPatchSet p start newsetIntersection :: RepoPatch p => [SealedPatchSet p start] -> SealedPatchSet p start commuteToEnd :: RepoPatch p => RL (PatchInfoAnd p) x y -> PatchSet p start y -> (PatchSet p :> RL (PatchInfoAnd p)) start x findUncommon :: RepoPatch p => PatchSet p start x -> PatchSet p start y -> (FL (PatchInfoAnd p) :\/: FL (PatchInfoAnd p)) x y -- | Merge two FLs (say L and R), starting in a common context. The result -- is a FL starting in the original end context of L, going to a new -- context that is the result of applying all patches from R on top of -- patches from L. -- -- While this function is similar to mergeFL, there are three -- important differences to keep in mind: -- -- merge2FL :: RepoPatch p => FL (PatchInfoAnd p) x y -> FL (PatchInfoAnd p) x z -> Sealed (FL (PatchInfoAnd p) y) module Darcs.Patch.Match data PatchMatch -- | A Matcher is made of a MatchFun which we will use to -- match patches and a String representing it. data Matcher p -- | A type for predicates over patches which do not care about contexts type MatchFun p = Sealed2 (PatchInfoAnd p) -> Bool patchMatch :: String -> PatchMatch matchPattern :: Patchy p => PatchMatch -> Matcher p -- | applyMatcher applies a matcher to a patch. applyMatcher :: Matcher p -> PatchInfoAnd p x y -> Bool makeMatcher :: String -> (Sealed2 (PatchInfoAnd p) -> Bool) -> Matcher p parseMatch :: Patchy p => PatchMatch -> Either String (MatchFun p) matchParser :: Patchy p => CharParser st (MatchFun p) -- | The string that is emitted when the user runs darcs help -- --match. helpOnMatchers :: String instance Show (Matcher p) module Darcs.Repository.Old readOldRepo :: RepoPatch p => String -> IO (SealedPatchSet p Origin) revertTentativeChanges :: IO () oldRepoFailMsg :: String -- | PatchChoices divides a sequence of patches into three sets: -- first, middle and last, such that all patches can -- be applied, if you first apply the first ones then the middle ones and -- then the last ones. Obviously if there are dependencies between the -- patches that will put a constraint on how you can choose to divide -- them up. The PatchChoices data type and associated functions are here -- to deal with many of the common cases that come up when choosing a -- subset of a group of patches. -- -- forceLast tells PatchChoices that a particular patch is -- required to be in the last group, which also means that any -- patches that depend on it must be in the last group. -- -- Internally, a PatchChoices doesn't always reorder the patches until it -- is asked for the final output (e.g. by get_first_choice). -- Instead, each patch is placed in a state of definitely first, -- definitely last and undecided; undecided leans towards middle. -- The patches that are first are commuted to the head immediately, but -- patches that are middle and last are mixed together. In case you're -- wondering about the first-middle-last language, it's because in some -- cases the yes answers will be last (as is the case for the -- revert command), and in others first (as in record, pull and push). -- -- Some patch marked middle may in fact be unselectable because of -- dependencies: when a patch is marked last, its dependencies are -- not updated until patchSlot is called on them. module Darcs.Patch.Choices data PatchChoices p x y patchChoices :: Patchy p => FL p x y -> PatchChoices p x y -- | Tag a sequence of patches. patchChoicesTps :: Patchy p => FL p x y -> (PatchChoices p x y, FL (TaggedPatch p) x y) -- | Tag a sequence of patches as subpatches of an existing tag. This is -- intended for use when substituting a patch for an equivalent patch or -- patches. patchChoicesTpsSub :: Patchy p => Maybe Tag -> FL p x y -> (PatchChoices p x y, FL (TaggedPatch p) x y) patchSlot :: Patchy p => TaggedPatch p a b -> PatchChoices p x y -> (Slot, PatchChoices p x y) patchSlot' :: Patchy p => TaggedPatch p a b -> StateT (PatchChoices p x y) Identity Slot -- | getChoices evaluates a PatchChoices into the first, -- middle and last sequences by doing the commutes that were needed. getChoices :: Patchy p => PatchChoices p x y -> (FL (TaggedPatch p) :> (FL (TaggedPatch p) :> FL (TaggedPatch p))) x y -- | refineChoices act performs act on the middle part of -- a sequence of choices, in order to hopefully get more patches into the -- first and last parts of a PatchChoices. refineChoices :: (Patchy p, Monad m, Functor m) => (forall u v. FL (TaggedPatch p) u v -> PatchChoices p u v -> m (PatchChoices p u v)) -> PatchChoices p x y -> m (PatchChoices p x y) separateFirstMiddleFromLast :: Patchy p => PatchChoices p x z -> (FL (TaggedPatch p) :> FL (TaggedPatch p)) x z separateFirstFromMiddleLast :: Patchy p => PatchChoices p x z -> (FL (TaggedPatch p) :> FL (TaggedPatch p)) x z forceFirst :: Patchy p => Tag -> PatchChoices p a b -> PatchChoices p a b forceFirsts :: Patchy p => [Tag] -> PatchChoices p a b -> PatchChoices p a b forceLast :: Patchy p => Tag -> PatchChoices p a b -> PatchChoices p a b forceLasts :: Patchy p => [Tag] -> PatchChoices p a b -> PatchChoices p a b forceMatchingFirst :: Patchy p => (forall x y. TaggedPatch p x y -> Bool) -> PatchChoices p a b -> PatchChoices p a b forceMatchingLast :: Patchy p => (forall x y. TaggedPatch p x y -> Bool) -> PatchChoices p a b -> PatchChoices p a b selectAllMiddles :: Patchy p => Bool -> PatchChoices p x y -> PatchChoices p x y makeUncertain :: Patchy p => Tag -> PatchChoices p a b -> PatchChoices p a b makeEverythingLater :: Patchy p => PatchChoices p x y -> PatchChoices p x y makeEverythingSooner :: Patchy p => PatchChoices p x y -> PatchChoices p x y data TaggedPatch p x y -- | TG mp i acts as a temporary identifier to help us keep -- track of patches during the selection process. These are useful for -- finding patches that may have moved around during patch selection -- (being pushed forwards or backwards as dependencies arise). -- -- The identifier is implemented as a tuple TG mp i. The -- i is just some arbitrary label, expected to be unique within -- the patches being scrutinised. The mp is motivated by patch -- splitting; it provides a convenient way to generate a new identifier -- from the patch being split. For example, if we split a patch -- identified as TG Nothing 5, the resulting sub-patches could -- be identified as TG (TG Nothing 5) 1, TG (TG Nothing 5) -- 2, etc. data Tag tag :: TaggedPatch p x y -> Tag tpPatch :: TaggedPatch p x y -> p x y -- | See module documentation for Choices data Slot InFirst :: Slot InMiddle :: Slot InLast :: Slot -- | substitute (a :||: bs) pcs replaces -- a with bs in pcs preserving the choice -- associated with a substitute :: Patchy p => Sealed2 (TaggedPatch p :||: FL (TaggedPatch p)) -> PatchChoices p x y -> PatchChoices p x y instance Eq Tag instance Ord Tag instance MyEq p => MyEq (PatchChoice p) instance Merge p => Merge (PatchChoice p) instance PatchInspect p => PatchInspect (PatchChoice p) instance Commute p => Commute (PatchChoice p) instance Merge p => Merge (TaggedPatch p) instance PatchInspect p => PatchInspect (TaggedPatch p) instance Commute p => Commute (TaggedPatch p) instance Invert p => Invert (TaggedPatch p) instance MyEq p => MyEq (TaggedPatch p) module Darcs.Patch.TouchesFiles lookTouch :: (Patchy p, ApplyState p ~ Tree) => Maybe [(FilePath, FilePath)] -> [FilePath] -> p x y -> (Bool, [FilePath], [FilePath], [(FilePath, FilePath)]) chooseTouching :: (Patchy p, ApplyState p ~ Tree) => Maybe [FilePath] -> FL p x y -> Sealed (FL p x) choosePreTouching :: (Patchy p, ApplyState p ~ Tree) => Maybe [FilePath] -> FL p x y -> Sealed (FL p x) selectTouching :: (Patchy p, ApplyState p ~ Tree) => Maybe [FilePath] -> PatchChoices p x y -> PatchChoices p x y deselectNotTouching :: (Patchy p, ApplyState p ~ Tree) => Maybe [FilePath] -> PatchChoices p x y -> PatchChoices p x y selectNotTouching :: (Patchy p, ApplyState p ~ Tree) => Maybe [FilePath] -> PatchChoices p x y -> PatchChoices p x y module Darcs.Patch.Prim.V1.Show showHunk :: FileNameFormat -> FileName -> Int -> [ByteString] -> [ByteString] -> Doc instance PrimShow Prim instance Show (DirPatchType x y) instance Show (FilePatchType x y) instance Show1 (Prim x) instance Show2 Prim instance Show (Prim x y) instance ApplyState Prim ~ Tree => ShowPatch Prim instance ShowPatchBasic Prim instance PatchListFormat Prim module Darcs.Patch.Prim.V1.Apply instance PrimApply Prim instance RepairToFL Prim instance Apply Prim module Darcs.Patch.Prim.V1.Coalesce instance Show (Simple x y) instance PrimCanonize Prim module Darcs.Patch.Prim.V1 data Prim x y instance FromPrim Prim instance PrimPatchBase Prim instance Patchy Prim instance PrimPatch Prim module Darcs.Patch.Prim.V3.Show showHunk :: String -> UUID -> Hunk x y -> Doc instance PrimShow Prim instance Show1 (Prim x) instance Show2 Prim instance Show (Prim x y) instance ShowPatch Prim instance ShowPatchBasic Prim instance PatchListFormat Prim module Darcs.Patch.Prim.V3 data Prim x y instance FromPrim Prim instance PrimPatchBase Prim instance Patchy Prim instance PrimPatch Prim module Darcs.Patch.V1.Viewing instance PrimPatch prim => ShowPatch (Patch prim) instance PrimPatch prim => ShowPatchBasic (Patch prim) module Darcs.Patch.V1 data Patch prim x y instance PrimPatch prim => RepoPatch (Patch prim) instance PrimPatch prim => Patchy (Patch prim) module Darcs.Patch.V2.Non -- | A Non stores a context with a Prim patch. It is a -- patch whose effect isn't visible - a Non-affecting patch. data Non p x Non :: FL p x y -> PrimOf p y z -> Non p x -- | Nonable represents the class of patches that can be turned into a Non. class Nonable p non :: Nonable p => p x y -> Non p x -- | unNon converts a Non into a FL of its context followed by the -- primitive patch. unNon :: FromPrim p => Non p x -> Sealed (FL p x) -- | showNon creates a Doc representing a Non. showNon :: (ShowPatchBasic p, PatchListFormat p, PrimPatchBase p) => Non p x -> Doc -- | showNons creates a Doc representing a list of Nons. showNons :: (ShowPatchBasic p, PatchListFormat p, PrimPatchBase p) => [Non p x] -> Doc -- | readNon is a parser that attempts to read a single Non. readNon :: (ReadPatch p, PatchListFormat p, PrimPatchBase p, ParserM m) => m (Non p x) -- | readNons is a parser that attempts to read a list of Nons. readNons :: (ReadPatch p, PatchListFormat p, PrimPatchBase p, ParserM m) => m [Non p x] -- | commutePrimsOrAddToCtx takes a WL of prims and attempts to commute -- them past a Non. commutePrimsOrAddToCtx :: (WL l, Patchy p, ToFromPrim p) => l (PrimOf p) x y -> Non p y -> Non p x -- | commuteOrAddToCtx x cy tries to commute x -- past cy and always returns some variant cy'. If -- commutation suceeds, the variant is just straightforwardly the -- commuted version. If commutation fails, the variant consists of -- x prepended to the context of cy. commuteOrAddToCtx :: (Patchy p, ToFromPrim p) => p x y -> Non p y -> Non p x -- | commuteOrRemFromCtx attempts to remove a given patch from a Non. If -- the patch was not in the Non, then the commute will succeed and the -- modified Non will be returned. If the commute fails then the patch is -- either in the Non context, or the Non patch itself; we attempt to -- remove the patch from the context and then return the non with the -- updated context. -- -- TODO: understand if there is any case where p is equal to the prim -- patch of the Non, in which case, we return the original Non, is that -- right? commuteOrRemFromCtx :: (Patchy p, ToFromPrim p) => p x y -> Non p x -> Maybe (Non p y) -- | commuteOrAddToCtxRL xs cy commutes as many patches of -- xs past cy as possible, adding any that don't -- commute to the context of cy. Suppose we have -- --
--   x1 x2 x3 [c1 c2 y]
--   
-- -- and that in our example x1 fails to commute past c1, -- this function would commute down to -- --
--   x1 [c1'' c2'' y''] x2' x3'
--   
-- -- and return [x1 c1'' c2'' y''] commuteOrAddToCtxRL :: (Patchy p, ToFromPrim p) => RL p x y -> Non p y -> Non p x -- | commuteOrRemFromCtxFL attempts to remove a FL of patches from a Non, -- returning Nothing if any of the individual removes fail. commuteOrRemFromCtxFL :: (Patchy p, ToFromPrim p) => FL p x y -> Non p x -> Maybe (Non p y) remNons :: (Nonable p, Effect p, Patchy p, ToFromPrim p, PrimPatchBase p, MyEq (PrimOf p)) => [Non p x] -> Non p x -> Non p x -- | (*>) attemts to modify a Non by commuting it past a given patch. (*>) :: (Patchy p, ToFromPrim p) => Non p x -> p x y -> Maybe (Non p y) -- | (>*) attempts to modify a Non, by commuting a given patch past it. (>*) :: (Patchy p, ToFromPrim p) => p x y -> Non p y -> Maybe (Non p x) -- | (*>>) attempts to modify a Non by commuting it past a given WL -- of patches. (*>>) :: (WL l, Patchy p, ToFromPrim p, PrimPatchBase p) => Non p x -> l (PrimOf p) x y -> Maybe (Non p y) -- | (>>*) attempts to modify a Non by commuting a given WL of -- patches past it. (>>*) :: (WL l, Patchy p, ToFromPrim p) => l (PrimOf p) x y -> Non p y -> Maybe (Non p x) instance WL RL instance WL FL instance (Commute p, MyEq p, MyEq (PrimOf p)) => Eq (Non p x) instance (Show2 p, Show2 (PrimOf p)) => Show1 (Non p) instance (Show2 p, Show2 (PrimOf p)) => Show (Non p x) module Darcs.Patch.V2.Real -- | RealPatch is used to represents prim patches that are -- duplicates of, or conflict with, another prim patch in the repository. -- -- Normal prim: A primitive patch -- -- Duplicate x: This patch has no effect since x is -- already present in the repository. -- --
--   Etacilpud x: invert (Duplicate x)
--   
-- -- Conflictor ix xx x: ix is the set of patches: * that -- conflict with x and also conflict with another patch in the -- repository. * that conflict with a patch that conflict with x -- -- xx is the sequence of patches that conflict *only* with -- x -- -- x is the original, conflicting patch. -- -- ix and x are stored as Non objects, which -- include any necessary context to uniquely define the patch that is -- referred to. -- -- The intuition is that a Conflictor should have the effect of inverting -- any patches that x conflicts with, that haven't already been -- undone by another Conflictor in the repository. Therefore, the effect -- of a Conflictor is invert xx. -- -- InvConflictor ix xx x: like invert (Conflictor ix xx -- x) data RealPatch prim x y Duplicate :: Non (RealPatch prim) x -> RealPatch prim x x Etacilpud :: Non (RealPatch prim) x -> RealPatch prim x x Normal :: prim x y -> RealPatch prim x y Conflictor :: [Non (RealPatch prim) x] -> FL prim x y -> Non (RealPatch prim) x -> RealPatch prim y x InvConflictor :: [Non (RealPatch prim) x] -> FL prim x y -> Non (RealPatch prim) x -> RealPatch prim x y prim2real :: prim x y -> RealPatch prim x y -- | This is used for unit-testing and for internal sanity checks isConsistent :: PrimPatch prim => RealPatch prim x y -> Maybe Doc -- | isForward p is True if p is either -- an InvConflictor or Etacilpud. isForward :: PrimPatch prim => RealPatch prim s y -> Maybe Doc -- | isDuplicate p is True if p is either -- a Duplicate or Etacilpud patch. isDuplicate :: RealPatch prim s y -> Bool -- | mergeUnravelled is used when converting from Darcs V1 patches -- (Mergers) to Darcs V2 patches (Conflictors). mergeUnravelled :: PrimPatch prim => [Sealed ((FL prim) x)] -> Maybe (FlippedSeal (RealPatch prim) x) instance IsHunk prim => IsHunk (RealPatch prim) instance PrimPatch prim => Effect (RealPatch prim) instance PrimPatch prim => Nonable (RealPatch prim) instance PrimPatch prim => Show2 (RealPatch prim) instance PrimPatch prim => Show (RealPatch prim x y) instance PrimPatch prim => ReadPatch (RealPatch prim) instance PrimPatch prim => ShowPatch (RealPatch prim) instance PrimPatch prim => ShowPatchBasic (RealPatch prim) instance PatchListFormat (RealPatch prim) instance PrimPatch prim => RepairToFL (RealPatch prim) instance PrimPatch prim => Apply (RealPatch prim) instance PatchInspect prim => PatchInspect (RealPatch prim) instance PrimPatch prim => Merge (RealPatch prim) instance PrimPatch prim => Commute (RealPatch prim) instance Invert prim => Invert (RealPatch prim) instance PrimPatch prim => MyEq (RealPatch prim) instance ToFromPrim (RealPatch prim) instance FromPrim (RealPatch prim) instance PrimPatch prim => Check (RealPatch prim) instance PrimPatch prim => CommuteNoConflicts (RealPatch prim) instance PrimPatch prim => Conflict (RealPatch prim) instance PrimPatch prim => Patchy (RealPatch prim) instance PrimPatch prim => PrimPatchBase (RealPatch prim) module Darcs.Patch.V2 -- | RealPatch is used to represents prim patches that are -- duplicates of, or conflict with, another prim patch in the repository. -- -- Normal prim: A primitive patch -- -- Duplicate x: This patch has no effect since x is -- already present in the repository. -- --
--   Etacilpud x: invert (Duplicate x)
--   
-- -- Conflictor ix xx x: ix is the set of patches: * that -- conflict with x and also conflict with another patch in the -- repository. * that conflict with a patch that conflict with x -- -- xx is the sequence of patches that conflict *only* with -- x -- -- x is the original, conflicting patch. -- -- ix and x are stored as Non objects, which -- include any necessary context to uniquely define the patch that is -- referred to. -- -- The intuition is that a Conflictor should have the effect of inverting -- any patches that x conflicts with, that haven't already been -- undone by another Conflictor in the repository. Therefore, the effect -- of a Conflictor is invert xx. -- -- InvConflictor ix xx x: like invert (Conflictor ix xx -- x) data RealPatch prim x y prim2real :: prim x y -> RealPatch prim x y instance PrimPatch prim => RepoPatch (RealPatch prim) module Darcs.Patch.Bundle -- | hashBundle creates a SHA1 string of a given a FL of named patches. -- This allows us to ensure that the patches in a received patchBundle -- have not been modified in transit. hashBundle :: (PatchListFormat p, ShowPatchBasic p) => FL (Named p) x y -> String -- | In makeBundle2, it is presumed that the two patch sequences are -- identical, but that they may be lazily generated. If two different -- patch sequences are passed, a bundle with a mismatched hash will be -- generated, which is not the end of the world, but isn't very useful -- either. makeBundle2 :: (ApplyState p ~ Tree, RepoPatch p) => Maybe (Tree IO) -> RL (PatchInfoAnd p) start x -> FL (Named p) x y -> FL (Named p) x y -> IO Doc makeBundleN :: (ApplyState p ~ Tree, RepoPatch p) => Maybe (Tree IO) -> PatchSet p start x -> FL (Named p) x y -> IO Doc scanBundle :: RepoPatch p => ByteString -> Either String (SealedPatchSet p Origin) contextPatches :: RepoPatch p => PatchSet p Origin x -> (PatchSet p :> (RL (PatchInfoAnd p))) Origin x scanContext :: RepoPatch p => ByteString -> PatchSet p Origin x -- | patchFilename maps a patch description string to a safe (lowercased, -- spaces removed and ascii-only characters) patch filename. patchFilename :: String -> String -- | getContext parses a context list, returning a tuple containing the -- list, and remaining ByteString input. getContext :: ByteString -> ([PatchInfo], ByteString) parseBundle :: RepoPatch p => ByteString -> Either String (Sealed ((PatchSet p :> FL (PatchInfoAnd p)) Origin)) module Darcs.Repository.Cache -- | cacheHash computes the cache hash (i.e. filename) of a packed -- string. cacheHash :: ByteString -> String okayHash :: String -> Bool takeHash :: ByteString -> Maybe (String, ByteString) newtype Cache Ca :: [CacheLoc] -> Cache data CacheType Repo :: CacheType Directory :: CacheType data CacheLoc Cache :: !CacheType -> !WritableOrNot -> !String -> CacheLoc cacheType :: CacheLoc -> !CacheType cacheWritable :: CacheLoc -> !WritableOrNot cacheSource :: CacheLoc -> !String data WritableOrNot Writable :: WritableOrNot NotWritable :: WritableOrNot data HashedDir HashedPristineDir :: HashedDir HashedPatchesDir :: HashedDir HashedInventoriesDir :: HashedDir hashedDir :: HashedDir -> String unionCaches :: Cache -> Cache -> Cache -- | unionRemoteCaches merges caches. It tries to do better than just -- blindly copying remote cache entries: -- -- -- -- This approach should save us from bogus cache entries. One case it -- does not work very well is when you fetch from partial repository over -- network. Hopefully this is not a common case. unionRemoteCaches :: Cache -> Cache -> String -> IO (Cache) cleanCaches :: Cache -> HashedDir -> IO () cleanCachesWithHint :: Cache -> HashedDir -> [String] -> IO () -- | fetchFileUsingCache cache dir hash receives a list of caches -- cache, the directory for which that file belongs dir -- and the hash of the file to fetch. It tries to fetch the file -- from one of the sources, trying them in order one by one. If the file -- cannot be fetched from any of the sources, this operation fails. fetchFileUsingCache :: Cache -> HashedDir -> String -> IO (String, ByteString) -- | speculateFileUsingCache cache subdirectory name takes note -- that the file name is likely to be useful soon: pipelined -- downloads will add it to the (low-priority) queue, for the rest it is -- a noop. speculateFileUsingCache :: Cache -> HashedDir -> String -> IO () -- | Note that the files are likely to be useful soon: pipelined downloads -- will add them to the (low-priority) queue, for the rest it is a noop. speculateFilesUsingCache :: Cache -> HashedDir -> [String] -> IO () -- | writeFileUsingCache cache compression subdir contents write -- the string contents to the directory subdir, except if it is -- already in the cache, in which case it is a noop. Warning (?) this -- means that in case of a hash collision, writing using -- writeFileUsingCache is a noop. The returned value is the filename that -- was given to the string. writeFileUsingCache :: Cache -> Compression -> HashedDir -> ByteString -> IO String -- | peekInCache cache subdir hash tells whether cache -- and contains an object with hash hash in a writable position. -- Florent: why do we want it to be in a writable position? peekInCache :: Cache -> HashedDir -> String -> IO Bool repo2cache :: String -> Cache writable :: CacheLoc -> Bool isthisrepo :: CacheLoc -> Bool -- | hashedFilePath cachelocation subdir hash returns the physical -- filename of hash hash in the subdir section of -- cachelocation. hashedFilePath :: CacheLoc -> HashedDir -> String -> String allHashedDirs :: [HashedDir] -- | Compares two caches, a remote cache is greater than a local one. The -- order of the comparison is given by: local < http < ssh compareByLocality :: CacheLoc -> CacheLoc -> Ordering -- | Prints an error message with a list of bad caches. reportBadSources :: IO () instance Show WritableOrNot instance Eq CacheType instance Show CacheType instance Eq OrOnlySpeculate instance Eq FromWhere instance Show Cache instance Show CacheLoc instance Eq CacheLoc module Darcs.Repository.Prefs addToPreflist :: String -> String -> IO () getPreflist :: String -> IO [String] setPreflist :: String -> [String] -> IO () getGlobal :: String -> IO [String] environmentHelpHome :: ([String], [String]) defaultrepo :: [DarcsFlag] -> AbsolutePath -> [String] -> IO [String] setDefaultrepo :: String -> [DarcsFlag] -> IO () getPrefval :: String -> IO (Maybe String) setPrefval :: String -> String -> IO () changePrefval :: String -> String -> String -> IO () defPrefval :: String -> String -> IO String writeDefaultPrefs :: IO () boringRegexps :: IO [Regex] boringFileFilter :: IO ([FilePath] -> [FilePath]) darcsdirFilter :: [FilePath] -> [FilePath] data FileType BinaryFile :: FileType TextFile :: FileType filetypeFunction :: IO (FilePath -> FileType) getCaches :: [DarcsFlag] -> String -> IO Cache binariesFileHelp :: [String] boringFileHelp :: [String] globalCacheDir :: IO (Maybe FilePath) -- | The relative path of the global preference directory; -- ~/.darcs on Unix, and %APPDATA%/darcs on Windows. -- This is used for online documentation. globalPrefsDirDoc :: String instance Eq FileType module Darcs.Diff treeDiff :: (Functor m, Monad m, Gap w, PrimPatch prim) => (FilePath -> FileType) -> Tree m -> Tree m -> m (w (FL prim)) module Darcs.Resolution standardResolution :: RepoPatch p => FL p x y -> Sealed (FL (PrimOf p) y) externalResolution :: (RepoPatch p, ApplyState p ~ Tree) => Tree IO -> String -> [DarcsFlag] -> FL (PrimOf p) x y -> FL (PrimOf p) x z -> FL p y a -> IO (Sealed (FL (PrimOf p) a)) patchsetConflictResolutions :: RepoPatch p => PatchSet p Origin x -> Sealed (FL (PrimOf p) x) module Darcs.IO runTolerantly :: TolerantIO a -> IO a runSilently :: SilentIO a -> IO a instance ApplyMonad SilentIO Tree instance ApplyMonad TolerantIO Tree instance Monad SilentIO instance Functor SilentIO instance Monad TolerantIO instance Functor TolerantIO instance TolerantMonad SilentIO instance TolerantMonad TolerantIO instance ApplyMonad IO Tree module Darcs.Repository.ApplyPatches applyPatches :: (MonadProgress m, ApplyMonad m (ApplyState p), Patchy p) => FL (PatchInfoAnd p) x y -> m () module Darcs.Repository.InternalTypes data Repository (p :: * -> * -> *) recordedstate unrecordedstate tentativestate Repo :: !String -> ![DarcsFlag] -> !RepoFormat -> !(RepoType p) -> Repository recordedstate unrecordedstate tentativestate data RepoType (p :: * -> * -> *) DarcsRepository :: !Pristine -> Cache -> RepoType data Pristine NoPristine :: Pristine PlainPristine :: Pristine HashedPristine :: Pristine extractCache :: Repository p r u t -> Cache extractOptions :: Repository p r u t -> [DarcsFlag] -- | modifyCache repository function modifies the cache of -- repository with function, remove duplicates and sort -- the results with compareByLocality. modifyCache :: RepoPatch p => Repository p r u t -> (Cache -> Cache) -> Repository p r u t instance Show Pristine instance Eq Pristine instance Show (RepoType p) instance Show (Repository p recordedstate unrecordedstate tentativestate) module Darcs.Repository.LowLevel -- | Read the contents of pending. CWD should be the repository directory. -- The return type is currently incorrect as it refers to the tentative -- state rather than the recorded state. readPending :: RepoPatch p => Repository p r u t -> IO (Sealed (FL (PrimOf p) t)) -- | Read the contents of tentative pending. CWD should be the repository -- directory. readTentativePending :: RepoPatch p => Repository p r u t -> IO (Sealed (FL (PrimOf p) t)) -- | Read the contents of tentative pending. CWD should be the repository -- directory. writeTentativePending :: RepoPatch p => Repository p r u t -> FL (PrimOf p) t y -> IO () -- | Read the contents of tentative pending. CWD should be the repository -- directory. readNewPending :: RepoPatch p => Repository p r u t -> IO (Sealed (FL (PrimOf p) t)) -- | Read the contents of new pending. CWD should be the repository -- directory. writeNewPending :: RepoPatch p => Repository p r u t -> FL (PrimOf p) t y -> IO () pendingName :: RepoType p -> String instance ShowPatchBasic p => ShowPatchBasic (FLM p) instance ReadPatch p => ReadPatch (FLM p) module Darcs.Repository.State -- | From a repository and a list of SubPath's, construct a filter that can -- be used on a Tree (recorded or unrecorded state) of this repository. -- This constructed filter will take pending into account, so the -- subpaths will be translated correctly relative to pending move -- patches. restrictSubpaths :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> [SubPath] -> IO (TreeFilter m) -- | Construct a Tree filter that removes any boring files the Tree might -- have contained. Additionally, you should (in most cases) pass an -- (expanded) Tree that corresponds to the recorded content of the -- repository. This is important in the cases when the repository -- contains files that would be boring otherwise. (If you pass emptyTree -- instead, such files will simply be discarded by the filter, which is -- usually not what you want.) -- -- This function is most useful when you have a plain Tree corresponding -- to the full working copy of the repository, including untracked files. -- Cf. whatsnew, record --look-for-adds. NB. Assumes that our CWD is the -- repository root. restrictBoring :: Tree m -> IO (TreeFilter m) newtype TreeFilter m TreeFilter :: (forall tr. FilterTree tr m => tr m -> tr m) -> TreeFilter m applyTreeFilter :: TreeFilter m -> forall tr. FilterTree tr m => tr m -> tr m -- | For a repository and an optional list of paths (when Nothing, take -- everything) compute a (forward) list of prims (i.e. a patch) going -- from the recorded state of the repository (pristine) to the unrecorded -- state of the repository (the working copy + pending). When a list of -- paths is given, at least the files that live under any of these paths -- in either recorded or unrecorded will be included in the resulting -- patch. NB. More patches may be included in this list, eg. the full -- contents of the pending patch. This is usually not a problem, since -- selectChanges will properly filter the results anyway. -- -- This also depends on the options given: with LookForAdds, we will -- include any non-boring files (i.e. also those that do not exist in the -- recorded state) in the working in the unrecorded state, -- and therefore they will show up in the patches as addfiles. -- -- The IgnoreTimes option disables index usage completely -- for each -- file, we read both the unrecorded and the recorded copy and run a diff -- on them. This is very inefficient, although in extremely rare cases, -- the index could go out of sync (file is modified, index is updated and -- file is modified again within a single second). unrecordedChanges :: (RepoPatch p, ApplyState p ~ Tree) => (UseIndex, ScanKnown) -> Repository p r u t -> Maybe [SubPath] -> IO (FL (PrimOf p) t u) readPending :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> IO (Tree IO, Sealed (FL p t)) -- | Obtains a Tree corresponding to the recorded state of the -- repository: this is the same as the pristine cache, which is the same -- as the result of applying all the repository's patches to an empty -- directory. -- -- Handles the plain and hashed pristine cases. Currently does not handle -- the no-pristine case, as that requires replaying patches. Cf. -- readDarcsHashed and readPlainTree in hashed-storage that -- are used to do the actual Tree construction. readRecorded :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> IO (Tree IO) -- | Obtains a Tree corresponding to the unrecorded state of the -- repository: the working tree plus the pending patch. The -- optional list of paths allows to restrict the query to a subtree. -- -- Limiting the query may be more efficient, since hashes on the -- uninteresting parts of the index do not need to go through an -- up-to-date check (which involves a relatively expensive lstat(2) per -- file. readUnrecorded :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> Maybe [SubPath] -> IO (Tree IO) readRecordedAndPending :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> IO (Tree IO) -- | Obtains a Tree corresponding to the working copy of the repository. -- NB. Almost always, using readUnrecorded is the right choice. This -- function is only useful in not-completely-constructed repositories. readWorking :: IO (Tree IO) readIndex :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> IO Index -- | Mark the existing index as invalid. This has to be called whenever the -- listing of pristine changes and will cause darcs to update the index -- next time it tries to read it. (NB. This is about files added and -- removed from pristine: changes to file content in either pristine or -- working are handled transparently by the index reading code.) invalidateIndex :: t -> IO () data UseIndex UseIndex :: UseIndex IgnoreIndex :: UseIndex data ScanKnown -- | Just files already known to darcs ScanKnown :: ScanKnown -- | All files, i.e. look for new ones ScanAll :: ScanKnown -- | All files, even boring ones ScanBoring :: ScanKnown module Darcs.Repository.HashedIO type HashedIO p = StateT (HashDir RW p) IO copyHashed :: String -> Cache -> Compression -> String -> IO () copyPartialsHashed :: FilePathLike fp => Cache -> Compression -> String -> [fp] -> IO () cleanHashdir :: Cache -> HashedDir -> [String] -> IO () data RW RW :: RW instance Eq ObjType instance ApplyMonad (HashedIO p) Tree module Darcs.Repository.HashedRepo revertTentativeChanges :: IO () finalizeTentativeChanges :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> Compression -> IO () cleanPristine :: Repository p r u t -> IO () copyPristine :: Cache -> Compression -> String -> String -> IO () copyPartialsPristine :: FilePathLike fp => Cache -> Compression -> String -> String -> [fp] -> IO () applyToTentativePristine :: (ApplyState q ~ Tree, Patchy q) => q x y -> IO () addToSpecificInventory :: RepoPatch p => String -> Cache -> Compression -> PatchInfoAnd p x y -> IO FilePath addToTentativeInventory :: RepoPatch p => Cache -> Compression -> PatchInfoAnd p x y -> IO FilePath removeFromTentativeInventory :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> Compression -> FL (PatchInfoAnd p) x t -> IO () readRepo :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> String -> IO (PatchSet p Origin r) readTentativeRepo :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> String -> IO (PatchSet p Origin t) readRepoUsingSpecificInventory :: (RepoPatch p, ApplyState p ~ Tree) => String -> Repository p r u t -> String -> IO (PatchSet p Origin s) writeAndReadPatch :: RepoPatch p => Cache -> Compression -> PatchInfoAnd p x y -> IO (PatchInfoAnd p x y) writeTentativeInventory :: RepoPatch p => Cache -> Compression -> PatchSet p Origin x -> IO () copyRepo :: RepoPatch p => Repository p r u t -> RemoteDarcs -> String -> IO () readHashedPristineRoot :: Repository p r u t -> IO (Maybe String) pris2inv :: String -> ByteString -> Doc -- | copySources copies the prefs/sources file to the local repo, -- from the remote, having first filtered the local filesystem sources. copySources :: RepoPatch p => Repository p r u t -> String -> IO () listInventories :: IO [String] writePatchIfNecessary :: RepoPatch p => Cache -> Compression -> PatchInfoAnd p x y -> IO (PatchInfo, String) readRepoFromInventoryList :: (RepoPatch p, ApplyState p ~ Tree) => Cache -> (Maybe String, [(PatchInfo, String)]) -> IO (SealedPatchSet p Origin) -- | 'readPatchIds inventory' parses the content of a hashed_inventory file -- after the pristine: and Starting with inventory: header -- lines have been removed. The second value in the resulting tuples is -- the file hash of the associated patch (the hash: line). readPatchIds :: ByteString -> [(PatchInfo, String)] module Darcs.Repository.Internal data Repository (p :: * -> * -> *) recordedstate unrecordedstate tentativestate Repo :: !String -> ![DarcsFlag] -> !RepoFormat -> !(RepoType p) -> Repository recordedstate unrecordedstate tentativestate data RepoType (p :: * -> * -> *) DarcsRepository :: !Pristine -> Cache -> RepoType -- | Repository IO monad. This monad-like datatype is responsible for -- sequencing IO actions that modify the tentative recorded state of the -- repository. data RIO p r u t t1 a data RepoJob a RepoJob :: (forall p r u. (RepoPatch p, ApplyState p ~ Tree, ApplyState (PrimOf p) ~ Tree) => Repository p r u r -> IO a) -> RepoJob a V1Job :: (forall r u. Repository (Patch Prim) r u r -> IO a) -> RepoJob a V2Job :: (forall r u. Repository (RealPatch Prim) r u r -> IO a) -> RepoJob a PrimV1Job :: (forall p r u. (RepoPatch p, ApplyState p ~ Tree, PrimOf p ~ Prim) => Repository p r u r -> IO a) -> RepoJob a -- | Tries to identify the repository in a given directory maybeIdentifyRepository :: [DarcsFlag] -> String -> IO (IdentifyRepo p r u t) -- | identifyDarcsRepository identifies the repo at url. Warning: -- you have to know what kind of patches are found in that repo. identifyDarcsRepository :: [DarcsFlag] -> String -> IO (Repository p r u t) -- | identifyRepositoryFor repo url identifies (and returns) the -- repo at url, but fails if it is not compatible for reading -- from and writing to. identifyRepositoryFor :: RepoPatch p => Repository p r u t -> String -> IO (Repository p r u t) -- | The status of a given directory: is it a darcs repository? data IdentifyRepo p r u t -- | looks like a repository with some error BadRepository :: String -> IdentifyRepo p r u t -- | safest guess NonRepository :: String -> IdentifyRepo p r u t GoodRepository :: (Repository p r u t) -> IdentifyRepo p r u t findRepository :: [DarcsFlag] -> IO (Either String ()) amInRepository :: [DarcsFlag] -> IO (Either String ()) amNotInRepository :: [DarcsFlag] -> IO (Either String ()) amInHashedRepository :: [DarcsFlag] -> IO (Either String ()) revertRepositoryChanges :: RepoPatch p => Repository p r u t -> IO () announceMergeConflicts :: (PrimPatch p, PatchInspect p) => String -> [DarcsFlag] -> FL p x y -> IO Bool -- | setTentativePending is basically unsafe. It overwrites the pending -- state with a new one, not related to the repository state. setTentativePending :: RepoPatch p => Repository p r u t -> FL (PrimOf p) x y -> IO () checkUnrecordedConflicts :: RepoPatch p => [DarcsFlag] -> FL (Named p) t y -> IO Bool withRecorded :: RepoPatch p => Repository p r u t -> ((AbsolutePath -> IO a) -> IO a) -> (AbsolutePath -> IO a) -> IO a readRepo :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> IO (PatchSet p Origin r) readTentativeRepo :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> IO (PatchSet p Origin t) readRepoUsingSpecificInventory :: (RepoPatch p, ApplyState p ~ Tree) => String -> Repository p r u t -> IO (PatchSet p Origin t) prefsUrl :: Repository p r u t -> String makePatchLazy :: RepoPatch p => Repository p r u t -> PatchInfoAnd p x y -> IO (PatchInfoAnd p x y) withRepoLock :: [DarcsFlag] -> RepoJob a -> IO a withRepoReadLock :: [DarcsFlag] -> RepoJob a -> IO a withRepository :: [DarcsFlag] -> RepoJob a -> IO a withRepositoryDirectory :: [DarcsFlag] -> String -> RepoJob a -> IO a withGutsOf :: Repository p r u t -> IO a -> IO a tentativelyAddPatch :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> Compression -> PatchInfoAnd p t y -> IO (Repository p r u y) tentativelyRemovePatches :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> Compression -> FL (PatchInfoAnd p) x t -> IO (Repository p r u x) -- | This fuction is unsafe because it accepts a patch that works on the -- tentative pending and we don't currently track the state of the -- tentative pending. tentativelyAddToPending :: RepoPatch p => Repository p r u t -> [DarcsFlag] -> FL (PrimOf p) x y -> IO () tentativelyAddPatch_ :: (RepoPatch p, ApplyState p ~ Tree) => UpdatePristine -> Repository p r u t -> Compression -> PatchInfoAnd p t y -> IO (Repository p r u y) tentativelyReplacePatches :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> Compression -> FL (PatchInfoAnd p) x t -> IO (Repository p r u t) finalizeRepositoryChanges :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> IO () unrevertUrl :: Repository p r u t -> String applyToWorking :: (ApplyState (PrimOf p) ~ Tree, RepoPatch p) => Repository p r u t -> [DarcsFlag] -> FL (PrimOf p) u y -> IO (Repository p r y t) patchSetToPatches :: RepoPatch p => PatchSet p x y -> FL (Named p) x y createPristineDirectoryTree :: RepoPatch p => Repository p r u t -> FilePath -> IO () -- | Used by the commands dist and diff createPartialsPristineDirectoryTree :: (FilePathLike fp, RepoPatch p) => Repository p r u t -> [fp] -> FilePath -> IO () -- | Writes out a fresh copy of the inventory that minimizes the amount of -- inventory that need be downloaded when people pull from the -- repository. -- -- Specifically, it breaks up the inventory on the most recent tag. This -- speeds up most commands when run remotely, both because a smaller file -- needs to be transfered (only the most recent inventory). It also gives -- a guarantee that all the patches prior to a given tag are included in -- that tag, so less commutation and history traversal is needed. This -- latter issue can become very important in large repositories. optimizeInventory :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> IO () cleanRepository :: RepoPatch p => Repository p r u t -> IO () setScriptsExecutable :: IO () setScriptsExecutablePatches :: Patchy p => p x y -> IO () -- | Similar to the ask function of the MonadReader class. This -- allows actions in the RIO monad to get the current repository. FIXME: -- Don't export this. If we don't export this it makes it harder for -- arbitrary IO actions to access the repository and hence our code is -- easier to audit. getRepository :: RIO p r u t t (Repository p r u t) -- | This the RIO equivalent of liftIO. rIO :: IO a -> RIO p r u t t a testTentative :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> IO (ExitCode) testRecorded :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> IO (ExitCode) data UpdatePristine UpdatePristine :: UpdatePristine DontUpdatePristine :: UpdatePristine data MakeChanges MakeChanges :: MakeChanges DontMakeChanges :: MakeChanges applyToTentativePristine :: (ApplyState q ~ Tree, Effect q, Patchy q, PrimPatchBase q) => Repository p r u t -> q t y -> IO () makeNewPending :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> FL (PrimOf p) t y -> IO () -- | hunt upwards for the darcs repository This keeps changing up one -- parent directory, testing at each step if the current directory is a -- repository or not. $ The result is: Nothing, if no repository found -- Just (Left errorMessage), if bad repository found Just (Right ()), if -- good repository found. WARNING this changes the current directory for -- good if matchFn succeeds seekRepo :: IO (Maybe (Either String ())) instance Eq MakeChanges instance Eq UpdatePristine instance Monad (RIO p r u t t) instance Functor (RIO p r u t t) module Darcs.Repository.Merge tentativelyMergePatches :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> String -> [DarcsFlag] -> FL (PatchInfoAnd p) x t -> FL (PatchInfoAnd p) x y -> IO (Sealed (FL (PrimOf p) u)) considerMergeToWorking :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> String -> [DarcsFlag] -> FL (PatchInfoAnd p) x t -> FL (PatchInfoAnd p) x y -> IO (Sealed (FL (PrimOf p) u)) module Darcs.Repository data Repository (p :: * -> * -> *) recordedstate unrecordedstate tentativestate data HashedDir HashedPristineDir :: HashedDir HashedPatchesDir :: HashedDir HashedInventoriesDir :: HashedDir newtype Cache Ca :: [CacheLoc] -> Cache data CacheLoc Cache :: !CacheType -> !WritableOrNot -> !String -> CacheLoc cacheType :: CacheLoc -> !CacheType cacheWritable :: CacheLoc -> !WritableOrNot cacheSource :: CacheLoc -> !String data WritableOrNot Writable :: WritableOrNot NotWritable :: WritableOrNot data RepoJob a RepoJob :: (forall p r u. (RepoPatch p, ApplyState p ~ Tree, ApplyState (PrimOf p) ~ Tree) => Repository p r u r -> IO a) -> RepoJob a V1Job :: (forall r u. Repository (Patch Prim) r u r -> IO a) -> RepoJob a V2Job :: (forall r u. Repository (RealPatch Prim) r u r -> IO a) -> RepoJob a PrimV1Job :: (forall p r u. (RepoPatch p, ApplyState p ~ Tree, PrimOf p ~ Prim) => Repository p r u r -> IO a) -> RepoJob a -- | Tries to identify the repository in a given directory maybeIdentifyRepository :: [DarcsFlag] -> String -> IO (IdentifyRepo p r u t) -- | identifyRepositoryFor repo url identifies (and returns) the -- repo at url, but fails if it is not compatible for reading -- from and writing to. identifyRepositoryFor :: RepoPatch p => Repository p r u t -> String -> IO (Repository p r u t) withRepoLock :: [DarcsFlag] -> RepoJob a -> IO a withRepoReadLock :: [DarcsFlag] -> RepoJob a -> IO a withRepository :: [DarcsFlag] -> RepoJob a -> IO a withRepositoryDirectory :: [DarcsFlag] -> String -> RepoJob a -> IO a withGutsOf :: Repository p r u t -> IO a -> IO a makePatchLazy :: RepoPatch p => Repository p r u t -> PatchInfoAnd p x y -> IO (PatchInfoAnd p x y) -- | writePatchSet is like patchSetToRepository, except that it doesn't -- touch the working directory or pristine cache. writePatchSet :: (RepoPatch p, ApplyState p ~ Tree) => PatchSet p Origin x -> [DarcsFlag] -> IO (Repository p r u t) findRepository :: [DarcsFlag] -> IO (Either String ()) amInRepository :: [DarcsFlag] -> IO (Either String ()) amNotInRepository :: [DarcsFlag] -> IO (Either String ()) amInHashedRepository :: [DarcsFlag] -> IO (Either String ()) -- | Replace the existing pristine with a new one (loaded up in a Tree -- object). replacePristine :: Repository p r u t -> Tree IO -> IO () withRecorded :: RepoPatch p => Repository p r u t -> ((AbsolutePath -> IO a) -> IO a) -> (AbsolutePath -> IO a) -> IO a readRepo :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> IO (PatchSet p Origin r) prefsUrl :: Repository p r u t -> String readRepoUsingSpecificInventory :: (RepoPatch p, ApplyState p ~ Tree) => String -> Repository p r u t -> IO (PatchSet p Origin t) addToPending :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> FL (PrimOf p) u y -> IO () tentativelyAddPatch :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> Compression -> PatchInfoAnd p t y -> IO (Repository p r u y) tentativelyRemovePatches :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> Compression -> FL (PatchInfoAnd p) x t -> IO (Repository p r u x) -- | This fuction is unsafe because it accepts a patch that works on the -- tentative pending and we don't currently track the state of the -- tentative pending. tentativelyAddToPending :: RepoPatch p => Repository p r u t -> [DarcsFlag] -> FL (PrimOf p) x y -> IO () tentativelyReplacePatches :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> Compression -> FL (PatchInfoAnd p) x t -> IO (Repository p r u t) readTentativeRepo :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> IO (PatchSet p Origin t) tentativelyMergePatches :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> String -> [DarcsFlag] -> FL (PatchInfoAnd p) x t -> FL (PatchInfoAnd p) x y -> IO (Sealed (FL (PrimOf p) u)) considerMergeToWorking :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> String -> [DarcsFlag] -> FL (PatchInfoAnd p) x t -> FL (PatchInfoAnd p) x y -> IO (Sealed (FL (PrimOf p) u)) revertRepositoryChanges :: RepoPatch p => Repository p r u t -> IO () finalizeRepositoryChanges :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> IO () createRepository :: [DarcsFlag] -> IO () copyRepository :: (RepoPatch p, ApplyState (PrimOf p) ~ Tree, ApplyState p ~ Tree) => Repository p r u t -> Bool -> IO () -- | patchSetToRepository takes a patch set, and writes a new repository in -- the current directory that contains all the patches in the patch set. -- This function is used when 'darcs get'ing a repository with the -- --to-match flag and the new repository is not in hashed format. This -- function does not (yet) work for hashed repositories. If the passed -- DarcsFlags tell darcs to create a hashed repository, this -- function will call error. patchSetToRepository :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r1 u1 r1 -> PatchSet p Origin x -> [DarcsFlag] -> IO (Repository p r u t) unrevertUrl :: Repository p r u t -> String applyToWorking :: (ApplyState (PrimOf p) ~ Tree, RepoPatch p) => Repository p r u t -> [DarcsFlag] -> FL (PrimOf p) u y -> IO (Repository p r y t) patchSetToPatches :: RepoPatch p => PatchSet p x y -> FL (Named p) x y createPristineDirectoryTree :: RepoPatch p => Repository p r u t -> FilePath -> IO () -- | Used by the commands dist and diff createPartialsPristineDirectoryTree :: (FilePathLike fp, RepoPatch p) => Repository p r u t -> [fp] -> FilePath -> IO () -- | Writes out a fresh copy of the inventory that minimizes the amount of -- inventory that need be downloaded when people pull from the -- repository. -- -- Specifically, it breaks up the inventory on the most recent tag. This -- speeds up most commands when run remotely, both because a smaller file -- needs to be transfered (only the most recent inventory). It also gives -- a guarantee that all the patches prior to a given tag are included in -- that tag, so less commutation and history traversal is needed. This -- latter issue can become very important in large repositories. optimizeInventory :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> IO () cleanRepository :: RepoPatch p => Repository p r u t -> IO () data PatchSet p start y type SealedPatchSet p start = Sealed ((PatchSet p) start) -- | PatchInfoAnd p a b represents a hope we have to get a -- patch through its info. We're not sure we have the patch, but we know -- its info. data PatchInfoAnd p a b setScriptsExecutable :: IO () setScriptsExecutablePatches :: Patchy p => p x y -> IO () checkUnrelatedRepos :: RepoPatch p => [DarcsFlag] -> PatchSet p start x -> PatchSet p start y -> IO () testTentative :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> IO (ExitCode) testRecorded :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> IO (ExitCode) extractOptions :: Repository p r u t -> [DarcsFlag] -- | modifyCache repository function modifies the cache of -- repository with function, remove duplicates and sort -- the results with compareByLocality. modifyCache :: RepoPatch p => Repository p r u t -> (Cache -> Cache) -> Repository p r u t -- | Prints an error message with a list of bad caches. reportBadSources :: IO () -- | Obtains a Tree corresponding to the recorded state of the -- repository: this is the same as the pristine cache, which is the same -- as the result of applying all the repository's patches to an empty -- directory. -- -- Handles the plain and hashed pristine cases. Currently does not handle -- the no-pristine case, as that requires replaying patches. Cf. -- readDarcsHashed and readPlainTree in hashed-storage that -- are used to do the actual Tree construction. readRecorded :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> IO (Tree IO) -- | Obtains a Tree corresponding to the unrecorded state of the -- repository: the working tree plus the pending patch. The -- optional list of paths allows to restrict the query to a subtree. -- -- Limiting the query may be more efficient, since hashes on the -- uninteresting parts of the index do not need to go through an -- up-to-date check (which involves a relatively expensive lstat(2) per -- file. readUnrecorded :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> Maybe [SubPath] -> IO (Tree IO) -- | For a repository and an optional list of paths (when Nothing, take -- everything) compute a (forward) list of prims (i.e. a patch) going -- from the recorded state of the repository (pristine) to the unrecorded -- state of the repository (the working copy + pending). When a list of -- paths is given, at least the files that live under any of these paths -- in either recorded or unrecorded will be included in the resulting -- patch. NB. More patches may be included in this list, eg. the full -- contents of the pending patch. This is usually not a problem, since -- selectChanges will properly filter the results anyway. -- -- This also depends on the options given: with LookForAdds, we will -- include any non-boring files (i.e. also those that do not exist in the -- recorded state) in the working in the unrecorded state, -- and therefore they will show up in the patches as addfiles. -- -- The IgnoreTimes option disables index usage completely -- for each -- file, we read both the unrecorded and the recorded copy and run a diff -- on them. This is very inefficient, although in extremely rare cases, -- the index could go out of sync (file is modified, index is updated and -- file is modified again within a single second). unrecordedChanges :: (RepoPatch p, ApplyState p ~ Tree) => (UseIndex, ScanKnown) -> Repository p r u t -> Maybe [SubPath] -> IO (FL (PrimOf p) t u) readPending :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> IO (Tree IO, Sealed (FL p t)) readRecordedAndPending :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> IO (Tree IO) readIndex :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> IO Index -- | Mark the existing index as invalid. This has to be called whenever the -- listing of pristine changes and will cause darcs to update the index -- next time it tries to read it. (NB. This is about files added and -- removed from pristine: changes to file content in either pristine or -- working are handled transparently by the index reading code.) invalidateIndex :: t -> IO () module Darcs.Arguments -- | The DarcsFlag type is a list of all flags that can ever be -- passed to darcs, or to one of its commands. data DarcsFlag Help :: DarcsFlag ListOptions :: DarcsFlag NoTest :: DarcsFlag Test :: DarcsFlag OnlyChangesToFiles :: DarcsFlag ChangesToAllFiles :: DarcsFlag LeaveTestDir :: DarcsFlag NoLeaveTestDir :: DarcsFlag Timings :: DarcsFlag Debug :: DarcsFlag DebugVerbose :: DarcsFlag DebugHTTP :: DarcsFlag Verbose :: DarcsFlag NormalVerbosity :: DarcsFlag Quiet :: DarcsFlag Target :: String -> DarcsFlag Cc :: String -> DarcsFlag Output :: AbsolutePathOrStd -> DarcsFlag OutputAutoName :: AbsolutePath -> DarcsFlag Subject :: String -> DarcsFlag InReplyTo :: String -> DarcsFlag Charset :: String -> DarcsFlag SendmailCmd :: String -> DarcsFlag Author :: String -> DarcsFlag PatchName :: String -> DarcsFlag OnePatch :: String -> DarcsFlag SeveralPatch :: String -> DarcsFlag AfterPatch :: String -> DarcsFlag UpToPatch :: String -> DarcsFlag TagName :: String -> DarcsFlag LastN :: Int -> DarcsFlag MaxCount :: Int -> DarcsFlag PatchIndexRange :: Int -> Int -> DarcsFlag NumberPatches :: DarcsFlag OneTag :: String -> DarcsFlag AfterTag :: String -> DarcsFlag UpToTag :: String -> DarcsFlag GenContext :: DarcsFlag Context :: AbsolutePath -> DarcsFlag Count :: DarcsFlag LogFile :: AbsolutePath -> DarcsFlag RmLogFile :: DarcsFlag DontRmLogFile :: DarcsFlag DistName :: String -> DarcsFlag All :: DarcsFlag Recursive :: DarcsFlag NoRecursive :: DarcsFlag Reorder :: DarcsFlag RestrictPaths :: DarcsFlag DontRestrictPaths :: DarcsFlag AskDeps :: DarcsFlag NoAskDeps :: DarcsFlag IgnoreTimes :: DarcsFlag DontIgnoreTimes :: DarcsFlag LookForAdds :: DarcsFlag NoLookForAdds :: DarcsFlag AnyOrder :: DarcsFlag CreatorHash :: String -> DarcsFlag Intersection :: DarcsFlag Union :: DarcsFlag Complement :: DarcsFlag Sign :: DarcsFlag SignAs :: String -> DarcsFlag NoSign :: DarcsFlag SignSSL :: String -> DarcsFlag HappyForwarding :: DarcsFlag NoHappyForwarding :: DarcsFlag Verify :: AbsolutePath -> DarcsFlag VerifySSL :: AbsolutePath -> DarcsFlag RemoteDarcsOpt :: String -> DarcsFlag EditDescription :: DarcsFlag NoEditDescription :: DarcsFlag Toks :: String -> DarcsFlag EditLongComment :: DarcsFlag NoEditLongComment :: DarcsFlag PromptLongComment :: DarcsFlag KeepDate :: DarcsFlag NoKeepDate :: DarcsFlag AllowConflicts :: DarcsFlag MarkConflicts :: DarcsFlag NoAllowConflicts :: DarcsFlag SkipConflicts :: DarcsFlag Boring :: DarcsFlag SkipBoring :: DarcsFlag AllowCaseOnly :: DarcsFlag DontAllowCaseOnly :: DarcsFlag AllowWindowsReserved :: DarcsFlag DontAllowWindowsReserved :: DarcsFlag DontGrabDeps :: DarcsFlag DontPromptForDependencies :: DarcsFlag PromptForDependencies :: DarcsFlag Compress :: DarcsFlag NoCompress :: DarcsFlag UnCompress :: DarcsFlag WorkRepoDir :: String -> DarcsFlag WorkRepoUrl :: String -> DarcsFlag RemoteRepo :: String -> DarcsFlag NewRepo :: String -> DarcsFlag Reply :: String -> DarcsFlag ApplyAs :: String -> DarcsFlag MachineReadable :: DarcsFlag HumanReadable :: DarcsFlag Pipe :: DarcsFlag Interactive :: DarcsFlag DiffCmd :: String -> DarcsFlag ExternalMerge :: String -> DarcsFlag Summary :: DarcsFlag NoSummary :: DarcsFlag PauseForGui :: DarcsFlag NoPauseForGui :: DarcsFlag Unified :: DarcsFlag NonUnified :: DarcsFlag Reverse :: DarcsFlag Forward :: DarcsFlag Complete :: DarcsFlag Lazy :: DarcsFlag FixFilePath :: AbsolutePath -> AbsolutePath -> DarcsFlag DiffFlags :: String -> DarcsFlag XMLOutput :: DarcsFlag ForceReplace :: DarcsFlag OnePattern :: PatchMatch -> DarcsFlag SeveralPattern :: PatchMatch -> DarcsFlag AfterPattern :: PatchMatch -> DarcsFlag UpToPattern :: PatchMatch -> DarcsFlag NonApply :: DarcsFlag NonVerify :: DarcsFlag NonForce :: DarcsFlag DryRun :: DarcsFlag SetDefault :: Bool -> DarcsFlag NoSetDefault :: Bool -> DarcsFlag Disable :: DarcsFlag SetScriptsExecutable :: DarcsFlag DontSetScriptsExecutable :: DarcsFlag Bisect :: DarcsFlag UseHashedInventory :: DarcsFlag UseFormat2 :: DarcsFlag UseNoWorkingDir :: DarcsFlag UseWorkingDir :: DarcsFlag NoUpdateWorking :: DarcsFlag Sibling :: AbsolutePath -> DarcsFlag Relink :: DarcsFlag OptimizePristine :: DarcsFlag OptimizeHTTP :: DarcsFlag UpgradeFormat :: DarcsFlag Files :: DarcsFlag NoFiles :: DarcsFlag Directories :: DarcsFlag NoDirectories :: DarcsFlag Pending :: DarcsFlag NoPending :: DarcsFlag PosthookCmd :: String -> DarcsFlag NoPosthook :: DarcsFlag AskPosthook :: DarcsFlag RunPosthook :: DarcsFlag PrehookCmd :: String -> DarcsFlag NoPrehook :: DarcsFlag AskPrehook :: DarcsFlag RunPrehook :: DarcsFlag UMask :: String -> DarcsFlag StoreInMemory :: DarcsFlag ApplyOnDisk :: DarcsFlag NoHTTPPipelining :: DarcsFlag Packs :: DarcsFlag NoPacks :: DarcsFlag NoCache :: DarcsFlag AllowUnrelatedRepos :: DarcsFlag Check :: DarcsFlag Repair :: DarcsFlag JustThisRepo :: DarcsFlag NullFlag :: DarcsFlag RecordRollback :: DarcsFlag NoRecordRollback :: DarcsFlag NoAmendUnrecord :: DarcsFlag AmendUnrecord :: DarcsFlag flagToString :: [DarcsOption] -> DarcsFlag -> Maybe String applyDefaults :: [DarcsOption] -> [DarcsFlag] -> [DarcsFlag] nubOptions :: [DarcsOption] -> [DarcsFlag] -> [DarcsFlag] maxCount :: [DarcsFlag] -> Maybe Int isin :: DarcsAtomicOption -> [DarcsFlag] -> Bool arein :: DarcsOption -> [DarcsFlag] -> Bool -- | Set the DARCS_PATCHES and DARCS_PATCHES_XML environment variables with -- info about the given patches, for use in post-hooks. setEnvDarcsPatches :: (RepoPatch p, ApplyState p ~ Tree) => FL (PatchInfoAnd p) x y -> IO () -- | Set the DARCS_FILES environment variable to the files touched by the -- given patch, one per line, for use in post-hooks. setEnvDarcsFiles :: Patchy p => p x y -> IO () fixFilePathOrStd :: [DarcsFlag] -> FilePath -> IO AbsolutePathOrStd fixUrl :: [DarcsFlag] -> String -> IO String fixUrlFlag :: [DarcsFlag] -> DarcsFlag -> IO DarcsFlag -- | fixSubPaths files returns the SubPaths for the paths -- in files that are inside the repository, preserving their -- order. Paths in files that are outside the repository -- directory are not in the result. -- -- When converting a relative path to an absolute one, this function -- first tries to interpret the relative path with respect to the current -- working directory. If that fails, it tries to interpret it with -- respect to the repository directory. Only when that fails does it omit -- the path from the result. -- -- It is intended for validating file arguments to darcs commands. fixSubPaths :: [DarcsFlag] -> [FilePath] -> IO [SubPath] -- | maybeFixSubPaths files tries to turn the file paths in its -- argument into SubPaths. -- -- When converting a relative path to an absolute one, this function -- first tries to interpret the relative path with respect to the current -- working directory. If that fails, it tries to interpret it with -- respect to the repository directory. Only when that fails does it put -- a Nothing in the result at the position of the path that -- cannot be converted. -- -- It is intended for validating file arguments to darcs commands. maybeFixSubPaths :: [DarcsFlag] -> [FilePath] -> IO [Maybe SubPath] -- | A type for darcs' options. The value contains the command line -- switch(es) for the option, a help string, and a function to build a -- DarcsFlag from the command line arguments. for each -- constructor, shortSwitches represents the list of short -- command line switches which invoke the option, longSwitches the list -- of long command line switches, optDescr the description of the option, -- and argDescr the description of its argument, if any. mkFlag is a -- function which makes a DarcsFlag from the arguments of the -- option. data DarcsAtomicOption -- | DarcsArgOption shortSwitches longSwitches mkFlag ArgDescr -- OptDescr The constructor for options with a string argument, such -- as --tag DarcsArgOption :: [Char] -> [String] -> (String -> DarcsFlag) -> String -> String -> DarcsAtomicOption -- | DarcsAbsPathOption shortSwitches longSwitches mkFlag ArgDescr -- OptDescr The constructor for options with an absolute path -- argument, such as --sibling DarcsAbsPathOption :: [Char] -> [String] -> (AbsolutePath -> DarcsFlag) -> String -> String -> DarcsAtomicOption -- | DarcsAbsPathOrStdOption shortSwitches longSwitches mkFlag ArgDescr -- OptDescr The constructor for options with a path argument, such -- as -o DarcsAbsPathOrStdOption :: [Char] -> [String] -> (AbsolutePathOrStd -> DarcsFlag) -> String -> String -> DarcsAtomicOption -- | DarcsOptAbsPathOrStdOption shortSwitches longSwitches defaultPath -- mkFlag ArgDescr OptDescr where defaultPath is a default value for -- the Path, as a string to be parsed as if it had been given on the -- command line. The constructor for options with an optional path -- argument, such as -O DarcsOptAbsPathOption :: [Char] -> [String] -> String -> (AbsolutePath -> DarcsFlag) -> String -> String -> DarcsAtomicOption -- | DarcsNoArgOption shortSwitches longSwitches mkFlag optDescr -- The constructon fon options with no arguments. DarcsNoArgOption :: [Char] -> [String] -> DarcsFlag -> String -> DarcsAtomicOption -- | DarcsInternalOption An option just for internal use (e.g. -- defaulting), not directly available to the user. DarcsInternalOption :: DarcsFlag -> DarcsAtomicOption atomicOptions :: DarcsOption -> [DarcsAtomicOption] data DarcsOption DarcsSingleOption :: DarcsAtomicOption -> DarcsOption -- | A constructor for grouping related options together, such as -- --hashed and --darcs-2. DarcsMultipleChoiceOption :: [DarcsAtomicOption] -> DarcsOption DarcsMutuallyExclusive :: [DarcsAtomicOption] -> ([DarcsFlag] -> [DarcsFlag]) -> DarcsOption optionFromDarcsOption :: AbsolutePath -> DarcsOption -> [OptDescr DarcsFlag] help :: DarcsOption -- | list_option is an option which lists the command's arguments listOptions :: DarcsOption -- | Get a list of all non-boring files and directories in the working -- copy. listFiles :: IO [String] anyVerbosity :: [DarcsOption] disable :: DarcsOption restrictPaths :: DarcsOption notest :: DarcsOption test :: DarcsOption workingRepoDir :: DarcsOption -- | remoteRepo is the option used to specify the URL of the remote -- repository to work with remoteRepo :: DarcsOption leaveTestDir :: DarcsOption possiblyRemoteRepoDir :: DarcsOption -- | getRepourl takes a list of flags and returns the url of the -- repository specified by Repodir "directory" in that list of -- flags, if any. This flag is present if darcs was invoked with -- --repodir=DIRECTORY getRepourl :: [DarcsFlag] -> Maybe String -- | listRegisteredFiles returns the list of all registered files in -- the repository. listRegisteredFiles :: IO [String] -- | listUnregisteredFiles returns the list of all non-boring -- unregistered files in the repository. listUnregisteredFiles :: IO [String] author :: DarcsOption -- | getAuthor takes a list of flags and returns the author of the -- change specified by Author "Leo Tolstoy" in that list of -- flags, if any. Otherwise, if Pipe is present, asks the user -- who is the author and returns the answer. If neither are present, try -- to guess the author, from _darcs/prefs, and if it's not -- possible, ask the user. getAuthor :: [DarcsFlag] -> IO String -- | getEasyAuthor tries to get the author name first from the -- repository preferences, then from global preferences, then from -- environment variables. Returns [] if it could not get it. -- Note that it may only return multiple possibilities when reading from -- global preferences getEasyAuthor :: IO [String] -- | getSendmailCmd takes a list of flags and returns the sendmail -- command to be used by darcs send. Looks for a command -- specified by SendmailCmd "command" in that list of flags, if -- any. This flag is present if darcs was invoked with -- --sendmail-command=COMMAND Alternatively the user can set -- $SENDMAIL which will be used as a fallback if -- present. getSendmailCmd :: [DarcsFlag] -> IO String fileHelpAuthor :: [String] environmentHelpEmail :: ([String], [String]) patchnameOption :: DarcsOption distnameOption :: DarcsOption logfile :: DarcsOption rmlogfile :: DarcsOption fromOpt :: DarcsOption subject :: DarcsOption -- | getSubject takes a list of flags and returns the subject of the -- mail to be sent by darcs send. Looks for a subject specified -- by Subject "subject" in that list of flags, if any. This flag -- is present if darcs was invoked with --subject=SUBJECT getSubject :: [DarcsFlag] -> Maybe String charset :: DarcsOption getCharset :: [DarcsFlag] -> Maybe String inReplyTo :: DarcsOption getInReplyTo :: [DarcsFlag] -> Maybe String target :: DarcsOption ccSend :: DarcsOption ccApply :: DarcsOption -- | getCc takes a list of flags and returns the addresses to send a -- copy of the patch bundle to when using darcs send. looks for -- a cc address specified by Cc "address" in that list of flags. -- Returns the addresses as a comma separated string. getCc :: [DarcsFlag] -> String output :: DarcsOption outputAutoName :: DarcsOption recursive :: String -> DarcsOption patchFormatChoices :: DarcsOption upgradeFormat :: DarcsOption useWorkingDir :: DarcsOption askdeps :: DarcsOption ignoretimes :: DarcsOption lookforadds :: DarcsOption askLongComment :: DarcsOption keepDate :: DarcsOption sendmailCmd :: DarcsOption environmentHelpSendmail :: ([String], [String]) sign :: DarcsOption verify :: DarcsOption editDescription :: DarcsOption reponame :: DarcsOption creatorhash :: DarcsOption applyConflictOptions :: DarcsOption reply :: DarcsOption pullConflictOptions :: DarcsOption useExternalMerge :: DarcsOption depsSel :: DarcsOption nocompress :: DarcsOption uncompressNocompress :: DarcsOption repoCombinator :: DarcsOption optionsLatex :: [DarcsOption] -> String reorderPatches :: DarcsOption noskipBoring :: DarcsOption allowProblematicFilenames :: DarcsOption applyas :: DarcsOption humanReadable :: DarcsOption machineReadable :: DarcsOption changesReverse :: DarcsOption onlyToFiles :: DarcsOption changesFormat :: DarcsOption matchOneContext :: DarcsOption matchOneNontag :: DarcsOption matchMaxcount :: DarcsOption sendToContext :: DarcsOption -- | getContext takes a list of flags and returns the context -- specified by Context c in that list of flags, if any. This -- flag is present if darcs was invoked with --context=FILE getContext :: [DarcsFlag] -> Maybe AbsolutePath pipeInteractive :: DarcsOption allInteractive :: DarcsOption allPipeInteractive :: DarcsOption summary :: DarcsOption unified :: DarcsOption tokens :: DarcsOption partial :: DarcsOption diffCmdFlag :: DarcsOption diffflags :: DarcsOption unidiff :: DarcsOption xmloutput :: DarcsOption pauseForGui :: DarcsOption forceReplace :: DarcsOption dryRun :: [DarcsOption] dryRunNoxml :: DarcsOption -- | printDryRunMessageAndExit action opts patches prints a -- string representing the action that would be taken if the -- --dry-run option had not been passed to darcs. Then darcs -- exits successfully. action is the name of the action being -- taken, like "push" opts is the list of flags which -- were sent to darcs patches is the sequence of patches which -- would be touched by action. printDryRunMessageAndExit :: (RepoPatch p, ApplyState p ~ Tree) => String -> [DarcsFlag] -> FL (PatchInfoAnd p) x y -> IO () -- | showFriendly flags patch returns a Doc -- representing the right way to show patch given the list -- flags of flags darcs was invoked with. showFriendly :: Patchy p => [DarcsFlag] -> p x y -> Doc matchOne :: DarcsOption matchSeveral :: DarcsOption matchRange :: DarcsOption matchSeveralOrRange :: DarcsOption happyForwarding :: DarcsOption matchSeveralOrLast :: DarcsOption setDefault :: Bool -> DarcsOption setScriptsExecutableOption :: DarcsOption bisect :: DarcsOption sibling :: DarcsOption -- | flagsToSiblings collects the contents of all Sibling -- flags in a list of flags. flagsToSiblings :: [DarcsFlag] -> [AbsolutePath] relink :: DarcsOption files :: DarcsOption directories :: DarcsOption pending :: DarcsOption posthookCmd :: DarcsOption posthookPrompt :: DarcsOption -- | getPosthookCmd takes a list of flags and returns the posthook -- command specified by PosthookCmd a in that list of flags, if -- any. getPosthookCmd :: [DarcsFlag] -> Maybe String prehookCmd :: DarcsOption prehookPrompt :: DarcsOption -- | getPrehookCmd takes a list of flags and returns the prehook -- command specified by PrehookCmd a in that list of flags, if -- any. getPrehookCmd :: [DarcsFlag] -> Maybe String nullFlag :: DarcsOption umaskOption :: DarcsOption storeInMemory :: DarcsOption -- | patchSelectFlag f holds whenever f is a way -- of selecting patches such as PatchName n. patchSelectFlag :: DarcsFlag -> Bool networkOptions :: [DarcsOption] noCache :: DarcsOption allowUnrelatedRepos :: DarcsOption checkOrRepair :: DarcsOption justThisRepo :: DarcsOption optimizePristine :: DarcsOption optimizeHTTP :: DarcsOption getOutput :: [DarcsFlag] -> FilePath -> Maybe AbsolutePathOrStd makeScriptsExecutable :: Patchy p => [DarcsFlag] -> p x y -> IO () usePacks :: DarcsOption recordRollback :: DarcsOption amendUnrecord :: DarcsOption instance Eq FlagContent instance Show FlagContent instance Ord FlagContent module Darcs.Commands data CommandControl CommandData :: DarcsCommand -> CommandControl HiddenCommand :: DarcsCommand -> CommandControl GroupName :: String -> CommandControl data DarcsCommand DarcsCommand :: String -> String -> String -> String -> Int -> [String] -> ([DarcsFlag] -> [String] -> IO ()) -> ([DarcsFlag] -> IO (Either String ())) -> IO [String] -> ([DarcsFlag] -> AbsolutePath -> [String] -> IO [String]) -> [DarcsOption] -> [DarcsOption] -> DarcsCommand commandProgramName :: DarcsCommand -> String commandName :: DarcsCommand -> String commandHelp :: DarcsCommand -> String commandDescription :: DarcsCommand -> String commandExtraArgs :: DarcsCommand -> Int commandExtraArgHelp :: DarcsCommand -> [String] commandCommand :: DarcsCommand -> [DarcsFlag] -> [String] -> IO () commandPrereq :: DarcsCommand -> [DarcsFlag] -> IO (Either String ()) commandGetArgPossibilities :: DarcsCommand -> IO [String] commandArgdefaults :: DarcsCommand -> [DarcsFlag] -> AbsolutePath -> [String] -> IO [String] commandBasicOptions :: DarcsCommand -> [DarcsOption] commandAdvancedOptions :: DarcsCommand -> [DarcsOption] SuperCommand :: String -> String -> String -> String -> ([DarcsFlag] -> IO (Either String ())) -> [CommandControl] -> DarcsCommand commandProgramName :: DarcsCommand -> String commandName :: DarcsCommand -> String commandHelp :: DarcsCommand -> String commandDescription :: DarcsCommand -> String commandPrereq :: DarcsCommand -> [DarcsFlag] -> IO (Either String ()) commandSubCommands :: DarcsCommand -> [CommandControl] commandAlias :: String -> Maybe DarcsCommand -> DarcsCommand -> DarcsCommand commandStub :: String -> String -> String -> DarcsCommand -> DarcsCommand commandOptions :: AbsolutePath -> DarcsCommand -> ([OptDescr DarcsFlag], [OptDescr DarcsFlag]) commandAlloptions :: DarcsCommand -> ([DarcsOption], [DarcsOption]) disambiguateCommands :: [CommandControl] -> String -> [String] -> Either String (CommandArgs, [String]) data CommandArgs CommandOnly :: DarcsCommand -> CommandArgs SuperCommandOnly :: DarcsCommand -> CommandArgs SuperCommandSub :: DarcsCommand -> DarcsCommand -> CommandArgs getCommandHelp :: Maybe DarcsCommand -> DarcsCommand -> String getCommandMiniHelp :: Maybe DarcsCommand -> DarcsCommand -> String getSubcommands :: DarcsCommand -> [CommandControl] usage :: [CommandControl] -> String usageHelper :: [CommandControl] -> String subusage :: DarcsCommand -> String chompNewline :: String -> String extractCommands :: [CommandControl] -> [DarcsCommand] superName :: Maybe DarcsCommand -> String nodefaults :: [DarcsFlag] -> AbsolutePath -> [String] -> IO [String] putInfo :: [DarcsFlag] -> Doc -> IO () putVerbose :: [DarcsFlag] -> Doc -> IO () putWarning :: [DarcsFlag] -> Doc -> IO () abortRun :: [DarcsFlag] -> Doc -> IO () module Darcs.PrintPatch -- | printPatch prints a patch on standard output. printPatch :: Patchy p => p x y -> IO () -- | contextualPrintPatch prints a patch, together with its context, -- on standard output. contextualPrintPatch :: (Patchy p, ApplyState p ~ Tree) => Tree IO -> p x y -> IO () -- | printPatchPager runs '$PAGER' and shows a patch in it. printPatchPager :: Patchy p => p x y -> IO () -- | printFriendly opts patch prints patch in -- accordance with the flags in opts, ie, whether --verbose or -- --summary were passed at the command-line. printFriendly :: (Patchy p, ApplyState p ~ Tree) => (Maybe (Tree IO)) -> [DarcsFlag] -> p x y -> IO () module Darcs.Test getTest :: [DarcsFlag] -> IO (IO ExitCode) runPosthook :: [DarcsFlag] -> AbsolutePath -> IO ExitCode runPrehook :: [DarcsFlag] -> AbsolutePath -> IO ExitCode module Darcs.Commands.Add add :: DarcsCommand expandDirs :: [SubPath] -> IO [SubPath] module Darcs.Commands.Util announceFiles :: Maybe [SubPath] -> String -> IO () filterExistingFiles :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> [SubPath] -> IO [SubPath] -- | First matcher, Second matcher and Nonrange matcher -- -- When we match for patches, we have a PatchSet, of which we want a -- subset. This subset is formed by the patches in a given interval which -- match a given criterion. If we represent time going left to right, -- then we have (up to) three Matchers: -- -- module Darcs.Match -- | matchFirstPatchset fs ps returns the part of ps -- before its first matcher, ie the one that comes first dependencywise. -- Hence, patches in matchFirstPatchset fs ps are the context -- for the ones we don't want. matchFirstPatchset :: RepoPatch p => [DarcsFlag] -> PatchSet p start x -> SealedPatchSet p start -- | matchSecondPatchset fs ps returns the part of ps -- before its second matcher, ie the one that comes last dependencywise. matchSecondPatchset :: RepoPatch p => [DarcsFlag] -> PatchSet p start x -> SealedPatchSet p start matchPatch :: RepoPatch p => [DarcsFlag] -> PatchSet p start x -> Sealed2 (Named p) -- | matchAPatch fs p tells whether p matches the -- matchers in the flags fs matchAPatch :: Patchy p => [DarcsFlag] -> Named p x y -> Bool -- | matchAPatchread fs p tells whether p matches the -- matchers in the flags listed in fs. matchAPatchread :: Patchy p => [DarcsFlag] -> PatchInfoAnd p x y -> Bool getFirstMatch :: (ApplyMonad IO (ApplyState p), RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> [DarcsFlag] -> IO () getNonrangeMatch :: (ApplyMonad IO (ApplyState p), RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> [DarcsFlag] -> IO () getNonrangeMatchS :: (ApplyMonad m (ApplyState p), MonadProgress m, RepoPatch p, ApplyState p ~ Tree) => [DarcsFlag] -> PatchSet p Origin x -> m () getPartialFirstMatch :: (RepoPatch p, ApplyMonad IO (ApplyState p), ApplyState p ~ Tree) => Repository p r u t -> [DarcsFlag] -> Maybe [FileName] -> IO () getPartialSecondMatch :: (RepoPatch p, ApplyMonad IO (ApplyState p), ApplyState p ~ Tree) => Repository p r u t -> [DarcsFlag] -> Maybe [FileName] -> IO () getPartialNonrangeMatch :: (RepoPatch p, ApplyMonad IO (ApplyState p), ApplyState p ~ Tree) => Repository p r u t -> [DarcsFlag] -> [FileName] -> IO () -- | firstMatch fs tells whether fs implies a first -- match, that is if we match against patches from a point in the -- past on, rather than against all patches since the creation of the -- repository. firstMatch :: [DarcsFlag] -> Bool -- | secondMatch fs tells whether fs implies a second -- match, that is if we match against patches up to a point in the -- past on, rather than against all patches until now. secondMatch :: [DarcsFlag] -> Bool -- | haveNonrangeMatch flags tells whether there is a flag in -- flags which corresponds to a match that is non-range. -- Thus, --match, --patch and --index make -- haveNonrangeMatch true, but not --from-patch or -- --to-patch. haveNonrangeMatch :: [DarcsFlag] -> Bool -- | havePatchsetMatch flags tells whether there is a patchset -- match in the flag list. A patchset match is --match or -- --patch, or --context, but not --from-patch -- nor (!) --index. Question: Is it supposed not to be a subset -- of haveNonrangeMatch? havePatchsetMatch :: [DarcsFlag] -> Bool getOnePatchset :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> [DarcsFlag] -> IO (SealedPatchSet p Origin) checkMatchSyntax :: [DarcsFlag] -> IO () applyInvToMatcher :: (RepoPatch p, ApplyMonad m (ApplyState p)) => InclusiveOrExclusive -> Matcher p -> PatchSet p Origin x -> m () -- | nonrangeMatcher is the criterion that is used to match -- against patches in the interval. It is 'Just m' when the -- --patch, --match, --tag options are passed -- (or their plural variants). nonrangeMatcher :: Patchy p => [DarcsFlag] -> Maybe (Matcher p) data InclusiveOrExclusive Inclusive :: InclusiveOrExclusive Exclusive :: InclusiveOrExclusive -- | matchExists m ps tells whether there is a patch matching -- m in ps matchExists :: Matcher p -> PatchSet p start x -> Bool -- | applyNInv n ps applies the inverse of the last n -- patches of ps. applyNInv :: (RepoPatch p, ApplyMonad m (ApplyState p)) => Int -> PatchSet p Origin x -> m () hasIndexRange :: [DarcsFlag] -> Maybe (Int, Int) instance Eq InclusiveOrExclusive module Darcs.SelectChanges -- | Select patches from a FL. selectChanges :: (Patchy p, ApplyState p ~ Tree) => WhichChanges -> FL p x y -> PatchSelection p x y -- | When asking about patches, we either ask about them in oldest-first or -- newest first (with respect to the current ordering of the repository), -- and we either want an initial segment or a final segment of the poset -- of patches. -- -- First: ask for an initial segment, first patches first -- (default for all pull-like commands) -- -- FirstReversed: ask for an initial segment, last patches first -- (used to ask about dependencies in record, and for pull-like commands -- with the --reverse flag). -- -- LastReversed: ask for a final segment, last patches first. -- (default for unpull-like commands, except for selecting *primitive* -- patches in rollback) -- -- Last: ask for a final segment, first patches first. (used for -- selecting primitive patches in rollback, and for unpull-like commands -- with the --reverse flag data WhichChanges Last :: WhichChanges LastReversed :: WhichChanges First :: WhichChanges FirstReversed :: WhichChanges -- | The equivalent of selectChanges for the darcs changes -- command viewChanges :: (Patchy p, ApplyState p ~ Tree) => [DarcsFlag] -> [Sealed2 p] -> IO () -- | The function for selecting a patch to amend record. Read at your own -- risks. withSelectedPatchFromRepo :: (RepoPatch p, ApplyState p ~ Tree) => String -> Repository p r u t -> [DarcsFlag] -> (forall a. (FL (PatchInfoAnd p) :> PatchInfoAnd p) a r -> IO ()) -> IO () -- | Optionally remove any patches (+dependencies) from a sequence that -- conflict with the recorded or unrecorded changes in a repo filterOutConflicts :: (RepoPatch p, ApplyState p ~ Tree) => [DarcsFlag] -> RL (PatchInfoAnd p) x t -> Repository p r u t -> FL (PatchInfoAnd p) x z -> IO (Bool, Sealed (FL (PatchInfoAnd p) x)) -- | runs a PatchSelection action in the given -- PatchSelectionContext. runSelection :: Patchy p => PatchSelection p x y -> PatchSelectionContext p -> IO ((FL p :> FL p) x y) -- | A PatchSelectionContext for selecting Prim patches. selectionContextPrim :: PrimPatch prim => String -> [DarcsFlag] -> Maybe (Splitter prim) -> Maybe [FilePath] -> Maybe (Tree IO) -> PatchSelectionContext prim -- | A PatchSelectionContext for selecting full patches -- (PatchInfoAnd patches) selectionContext :: RepoPatch p => String -> [DarcsFlag] -> Maybe (Splitter (PatchInfoAnd p)) -> Maybe [FilePath] -> PatchSelectionContext (PatchInfoAnd p) instance Eq WhichChanges instance Show WhichChanges module Darcs.Commands.Record record :: DarcsCommand commit :: DarcsCommand getDate :: [DarcsFlag] -> IO String getLog :: (Patchy prim, PrimPatch prim) => [DarcsFlag] -> Maybe (String, [String]) -> IO String -> FL prim x y -> IO (String, [String], Maybe String) askAboutDepends :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> FL (PrimOf p) t y -> [DarcsFlag] -> [PatchInfo] -> IO [PatchInfo] module Darcs.Commands.AmendRecord amendrecord :: DarcsCommand amendunrecord :: DarcsCommand module Darcs.Commands.Annotate annotate :: DarcsCommand module Darcs.Commands.Apply apply :: DarcsCommand getPatchBundle :: RepoPatch p => [DarcsFlag] -> ByteString -> IO (Either String (SealedPatchSet p Origin)) module Darcs.Commands.Changes changes :: DarcsCommand log :: DarcsCommand module Darcs.Repository.Repair replayRepository :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> [DarcsFlag] -> (RepositoryConsistency p r -> IO a) -> IO a checkIndex :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> Bool -> IO Bool replayRepositoryInTemp :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> [DarcsFlag] -> IO (RepositoryConsistency p r) data RepositoryConsistency p x RepositoryConsistent :: RepositoryConsistency p x BrokenPristine :: (Tree IO) -> RepositoryConsistency p x BrokenPatches :: (Tree IO) -> (PatchSet p Origin x) -> RepositoryConsistency p x module Darcs.Commands.Check check :: DarcsCommand repair :: DarcsCommand module Darcs.Commands.Convert convert :: DarcsCommand module Darcs.Commands.Diff diffCommand :: DarcsCommand module Darcs.Commands.Dist dist :: DarcsCommand module Darcs.Commands.Get get :: DarcsCommand clone :: DarcsCommand module Darcs.Commands.GZCRCs gzcrcs :: DarcsCommand -- | This is designed for use in an atexit handler, e.g. in -- Darcs.RunCommand doCRCWarnings :: Bool -> IO () module Darcs.Commands.Init initialize :: DarcsCommand initializeCmd :: [DarcsFlag] -> [String] -> IO () module Darcs.Commands.MarkConflicts markconflicts :: DarcsCommand module Darcs.Commands.Move move :: DarcsCommand mv :: DarcsCommand instance Show FileKind instance Eq FileKind instance Show FileStatus module Darcs.Commands.Optimize optimize :: DarcsCommand module Darcs.Commands.Push push :: DarcsCommand module Darcs.Commands.Put put :: DarcsCommand module Darcs.Commands.Remove remove :: DarcsCommand rm :: DarcsCommand unadd :: DarcsCommand module Darcs.Commands.Replace replace :: DarcsCommand defaultToks :: String module Darcs.Commands.Unrevert unrevert :: DarcsCommand writeUnrevert :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> FL (PrimOf p) x y -> Tree IO -> FL (PrimOf p) r x -> IO () module Darcs.Commands.Revert revert :: DarcsCommand module Darcs.Commands.Unrecord unrecord :: DarcsCommand unpull :: DarcsCommand obliterate :: DarcsCommand getLastPatches :: RepoPatch p => [DarcsFlag] -> PatchSet p Origin r -> ((PatchSet p) :> (FL (PatchInfoAnd p))) Origin r module Darcs.Commands.Rollback rollback :: DarcsCommand module Darcs.Commands.SetPref setpref :: DarcsCommand module Darcs.Commands.ShowAuthors showAuthors :: DarcsCommand module Darcs.Commands.ShowBug showBug :: DarcsCommand module Darcs.Commands.ShowContents showContents :: DarcsCommand module Darcs.Commands.ShowFiles showFiles :: DarcsCommand manifestCmd :: ([DarcsFlag] -> Tree IO -> [FilePath]) -> [DarcsFlag] -> [String] -> IO () toListManifest :: [DarcsFlag] -> Tree m -> [FilePath] manifest :: [DarcsFlag] -> [String] -> IO [FilePath] module Darcs.Commands.ShowTags showTags :: DarcsCommand module Darcs.Commands.ShowIndex showIndex :: DarcsCommand showPristineCmd :: [DarcsFlag] -> [String] -> IO () module Darcs.Commands.Tag tag :: DarcsCommand module Darcs.Commands.Test test :: DarcsCommand module Darcs.Commands.TrackDown trackdown :: DarcsCommand instance Show BisectDir module Darcs.Commands.TransferMode transferMode :: DarcsCommand module Darcs.Commands.WhatsNew whatsnew :: DarcsCommand -- | status is an alias for whatsnew, with implicit Summary and LookForAdds -- flags. We override the default description, to include the implicit -- flags. status :: DarcsCommand module Darcs.Commands.Pull pull :: DarcsCommand fetch :: DarcsCommand module Darcs.Commands.ShowRepo showRepo :: DarcsCommand module Darcs.Commands.Show showCommand :: DarcsCommand list :: DarcsCommand query :: DarcsCommand module URL.HTTP fetchUrl :: String -> IO String postUrl :: String -> String -> String -> IO () requestUrl :: String -> FilePath -> a -> IO String waitNextUrl :: IO (String, String, Maybe ConnectionError) module Darcs.Commands.Send send :: DarcsCommand module Darcs.TheCommands -- | The commands that darcs knows about (e.g. whatsnew, record), organized -- into thematic groups. Note that hidden commands are also listed here. commandControlList :: [CommandControl] module Darcs.Commands.Help helpCmd :: [DarcsFlag] -> [String] -> IO () commandControlList :: [CommandControl] -- | Help on each environment variable in which Darcs is interested. environmentHelp :: [([String], [String])] printVersion :: IO () listAvailableCommands :: IO () module Darcs.ArgumentDefaults getDefaultFlags :: String -> [DarcsOption] -> [DarcsFlag] -> IO [DarcsFlag] module Darcs.RunCommand runTheCommand :: [CommandControl] -> String -> [String] -> IO ()