Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data Repository (rt :: AccessType) (p :: * -> * -> *) wU wR
- data PristineType
- data AccessType
- data SAccessType (rt :: AccessType) where
- SRO :: SAccessType 'RO
- SRW :: SAccessType 'RW
- repoAccessType :: Repository rt p wU wR -> SAccessType rt
- repoCache :: Repository rt p wU wR -> Cache
- modifyCache :: (Cache -> Cache) -> Repository rt p wU wR -> Repository rt p wU wR
- repoFormat :: Repository rt p wU wR -> RepoFormat
- modifyRepoFormat :: (RepoFormat -> RepoFormat) -> Repository 'RW p wU wR -> IO (Repository 'RW p wU wR)
- repoLocation :: Repository rt p wU wR -> String
- withRepoDir :: Repository rt p wU wR -> IO a -> IO a
- repoPristineType :: Repository rt p wU wR -> PristineType
- unsafeCoerceRepoType :: Repository rt p wU wR -> Repository rt' p wU wR
- unsafeCoercePatchType :: Repository rt p wU wR -> Repository rt p' wU wR
- unsafeCoerceR :: Repository rt p wU wR -> Repository rt p wU wR'
- unsafeCoerceU :: Repository rt p wU wR -> Repository rt p wU' wR
- unsafeEndTransaction :: Repository 'RW p wU wR -> Repository 'RO p wU wR
- unsafeStartTransaction :: Repository 'RO p wU wR -> Repository 'RW p wU wR
- mkRepo :: AbsoluteOrRemotePath -> RepoFormat -> PristineType -> Cache -> Repository 'RO p wU wR
Documentation
data Repository (rt :: AccessType) (p :: * -> * -> *) wU wR Source #
A Repository
is a token representing the state of a repository on disk.
It is parameterized by
rt
- the access type (whether we are in a transaction or not),
p
- the patch type,
wU
- the witness for the unrecorded state (what's in the working tree now).
wR
- the witness for
- the recorded state when outside a transaction, or
- the tentative state when inside a transaction.
data PristineType Source #
Instances
Show PristineType Source # | |
Defined in Darcs.Repository.InternalTypes showsPrec :: Int -> PristineType -> ShowS # show :: PristineType -> String # showList :: [PristineType] -> ShowS # | |
Eq PristineType Source # | |
Defined in Darcs.Repository.InternalTypes (==) :: PristineType -> PristineType -> Bool # (/=) :: PristineType -> PristineType -> Bool # |
data AccessType Source #
Instances
Eq AccessType Source # | |
Defined in Darcs.Repository.InternalTypes (==) :: AccessType -> AccessType -> Bool # (/=) :: AccessType -> AccessType -> Bool # |
data SAccessType (rt :: AccessType) where Source #
SRO :: SAccessType 'RO | |
SRW :: SAccessType 'RW |
repoAccessType :: Repository rt p wU wR -> SAccessType rt Source #
repoCache :: Repository rt p wU wR -> Cache Source #
modifyCache :: (Cache -> Cache) -> Repository rt p wU wR -> Repository rt p wU wR Source #
repoFormat :: Repository rt p wU wR -> RepoFormat Source #
modifyRepoFormat :: (RepoFormat -> RepoFormat) -> Repository 'RW p wU wR -> IO (Repository 'RW p wU wR) Source #
repoLocation :: Repository rt p wU wR -> String Source #
withRepoDir :: Repository rt p wU wR -> IO a -> IO a Source #
Perform an action with the current working directory set to the
repoLocation
.
repoPristineType :: Repository rt p wU wR -> PristineType Source #
unsafeCoerceRepoType :: Repository rt p wU wR -> Repository rt' p wU wR Source #
unsafeCoercePatchType :: Repository rt p wU wR -> Repository rt p' wU wR Source #
unsafeCoerceR :: Repository rt p wU wR -> Repository rt p wU wR' Source #
unsafeCoerceU :: Repository rt p wU wR -> Repository rt p wU' wR Source #
unsafeEndTransaction :: Repository 'RW p wU wR -> Repository 'RO p wU wR Source #
unsafeStartTransaction :: Repository 'RO p wU wR -> Repository 'RW p wU wR Source #
Both unsafeStartTransaction
and unsafeEndTransaction
are "unsafe" in
the sense that they merely "coerce" the type but do not actually perform the
steps (IO
actions) required to start or end a transaction (this is done by
revertRepositoryChanges
and finalizeRepositoryChanges
). Technically this
is not an actual coercion like with e.g. unsafeCoerceR
, due to the
singleton typed member, but in practical terms it is no less unsafe, because
RO
vs. RW
changes whether wR
refers to the recorded or the tentative
state, respectively. In particular, you will get different results if you
are inside a transaction and read the patchset with a "coerced" Repository
of access type 'RO. The same holds for other state that is modified in a
transaction, like the pending patch or the rebase state.
mkRepo :: AbsoluteOrRemotePath -> RepoFormat -> PristineType -> Cache -> Repository 'RO p wU wR Source #