Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
The format file.
The purpose of the format file is to check compatibility between repositories in different formats and to allow the addition of new features without risking corruption by old darcs versions that do not yet know about these features.
This allows a limited form of forward compatibility between darcs versions. Old versions of darcs that are unaware of features added in later versions will fail with a decent error message instead of crashing or misbehaving or even corrupting new repos.
The format file lives at _darcs/format and must only contain printable ASCII
characters and must not contain the characters <
and >
.
(We currently do not strip whitespace from the lines, but may want to do so in the future.)
The file consists of format properties. A format property can contain any
allowed ASCII character except the vertical bar (|
) and newlines. Empty
lines are ignored and multiple properties on the same line are separated
with a |
.
If multiple properties appear on the same line (separated by vertical bars), then this indicates alternative format properties. These have a generic meaning:
- If we know *any* of these properties, then we can read the repo.
- If we know *all* of them, we can also write the repo.
The above rules are necessary conditions, not sufficient ones. It is allowed
to further restrict read and/or write access for specific commands, but care
should be taken to not unnecessarily break forward compatibility. It is not
recommended, but sometimes necessary, to impose ad-hoc restrictions on the
format, see transferProblem
and readProblem
for examples.
The no-working-dir property is an example for how to use alternative properties. An old darcs version that does not know this format can perform most read-only operations correctly even if there is no working tree; however, whatsnew will report that the whole tree was removed, so the solution is not perfect.
When you add a new property as an alternative to an existing one, you should make sure that the old format remains to be updated in parallel to the new one, so that reading the repo with old darcs versions behaves correctly. If this cannot be guaranteed, it is better to add the new format on a separate line.
It is not advisable for commands to modify an existing format file. However, sometimes compatibility requirements may leave us no other choice. In this case make sure to write the format file only after having checked that the existing repo format allows modification of the repo, and that you have taken the repo lock.
Synopsis
- newtype RepoFormat = RF [[RepoProperty]]
- data RepoProperty
- identifyRepoFormat :: String -> IO RepoFormat
- tryIdentifyRepoFormat :: String -> IO (Either String RepoFormat)
- createRepoFormat :: PatchFormat -> WithWorkingDir -> RepoFormat
- unsafeWriteRepoFormat :: RepoFormat -> FilePath -> IO ()
- writeProblem :: RepoFormat -> Maybe String
- readProblem :: RepoFormat -> Maybe String
- transferProblem :: RepoFormat -> RepoFormat -> Maybe String
- formatHas :: RepoProperty -> RepoFormat -> Bool
- addToFormat :: RepoProperty -> RepoFormat -> RepoFormat
- removeFromFormat :: RepoProperty -> RepoFormat -> RepoFormat
Documentation
newtype RepoFormat Source #
Representation of the format of a repository. Each sublist corresponds to a line in the format file.
RF [[RepoProperty]] |
Instances
Show RepoFormat Source # | |
Defined in Darcs.Repository.Format showsPrec :: Int -> RepoFormat -> ShowS # show :: RepoFormat -> String # showList :: [RepoFormat] -> ShowS # |
data RepoProperty Source #
Darcs1 | |
Darcs2 | |
Darcs3 | |
HashedInventory | |
NoWorkingDir | |
RebaseInProgress | |
RebaseInProgress_2_16 | |
UnknownFormat ByteString |
Instances
Show RepoProperty Source # | |
Defined in Darcs.Repository.Format showsPrec :: Int -> RepoProperty -> ShowS # show :: RepoProperty -> String # showList :: [RepoProperty] -> ShowS # | |
Eq RepoProperty Source # | |
Defined in Darcs.Repository.Format (==) :: RepoProperty -> RepoProperty -> Bool # (/=) :: RepoProperty -> RepoProperty -> Bool # |
identifyRepoFormat :: String -> IO RepoFormat Source #
Identify the format of the repository at the given location (directory, URL, or SSH path). Fails if we weren't able to identify the format.
tryIdentifyRepoFormat :: String -> IO (Either String RepoFormat) Source #
Identify the format of the repository at the
given location (directory, URL, or SSH path).
Return
if it fails, where Left
reasonreason
explains why
we weren't able to identify the format. Note that we do no verification of
the format, which is handled by readProblem
or writeProblem
on the
resulting RepoFormat
.
createRepoFormat :: PatchFormat -> WithWorkingDir -> RepoFormat Source #
Create a repo format. The first argument specifies the patch format; the second says whether the repo has a working tree.
unsafeWriteRepoFormat :: RepoFormat -> FilePath -> IO () Source #
Write the repo format to the given file. This is unsafe because we don't check that we are allowed to write to the repo.
writeProblem :: RepoFormat -> Maybe String Source #
returns writeProblem
sourceJust
an error message if we cannot write
to a repo in format source
, or Nothing
if there's no such problem.
readProblem :: RepoFormat -> Maybe String Source #
returns readProblem
sourceJust
an error message if we cannot read
from a repo in format source
, or Nothing
if there's no such problem.
transferProblem :: RepoFormat -> RepoFormat -> Maybe String Source #
returns transferProblem
source targetJust
an error message if we
cannot transfer patches from a repo in format source
to a repo in format
target
, or Nothing
if there are no such problem.
formatHas :: RepoProperty -> RepoFormat -> Bool Source #
Is a given property contained within a given format?
addToFormat :: RepoProperty -> RepoFormat -> RepoFormat Source #
Add a single property to an existing format.
removeFromFormat :: RepoProperty -> RepoFormat -> RepoFormat Source #
Remove a single property from an existing format.