License | BSD-style |
---|---|
Maintainer | Vincent Hanquez <vincent@snarc.org> |
Stability | experimental |
Portability | unix |
Safe Haskell | None |
Language | Haskell98 |
Synopsis
- data Ref hash
- newtype RefName = RefName {
- refNameRaw :: String
- data Commit hash = Commit {
- commitTreeish :: !(Ref hash)
- commitParents :: [Ref hash]
- commitAuthor :: !Person
- commitCommitter :: !Person
- commitEncoding :: Maybe ByteString
- commitExtras :: [CommitExtra]
- commitMessage :: !ByteString
- data Person = Person {
- personName :: !ByteString
- personEmail :: !ByteString
- personTime :: !GitTime
- data CommitExtra = CommitExtra {}
- newtype Tree hash = Tree {
- treeGetEnts :: [TreeEnt hash]
- newtype Blob hash = Blob {}
- data Tag hash = Tag {
- tagRef :: !(Ref hash)
- tagObjectType :: !ObjectType
- tagBlob :: !ByteString
- tagName :: !Person
- tagS :: !ByteString
- data GitTime
- newtype ModePerm = ModePerm Word32
- data EntName
- type EntPath = [EntName]
- entName :: ByteString -> EntName
- entPathAppend :: EntPath -> EntName -> EntPath
- data ObjectFileType
- data FilePermissions = FilePermissions {
- getOwnerPerm :: !Perm
- getGroupPerm :: !Perm
- getOtherPerm :: !Perm
- getPermission :: ModePerm -> FilePermissions
- getFiletype :: ModePerm -> ObjectFileType
- data Revision
- resolveRevision :: (Typeable hash, HashAlgorithm hash) => Git hash -> Revision -> IO (Maybe (Ref hash))
- resolveTreeish :: HashAlgorithm hash => Git hash -> Ref hash -> IO (Maybe (Tree hash))
- resolvePath :: (Typeable hash, HashAlgorithm hash) => Git hash -> Ref hash -> EntPath -> IO (Maybe (Ref hash))
- data Git hash
- withCurrentRepo :: (Git SHA1 -> IO a) -> IO a
- withRepo :: LocalPath -> (Git SHA1 -> IO c) -> IO c
- findRepo :: IO LocalPath
- initRepo :: LocalPath -> IO ()
- isRepo :: LocalPath -> IO Bool
- rewrite :: (Typeable hash, HashAlgorithm hash) => Git hash -> (Commit hash -> IO (Commit hash)) -> Revision -> Int -> IO (Ref hash)
- getObject :: HashAlgorithm hash => Git hash -> Ref hash -> Bool -> IO (Maybe (Object hash))
- getCommit :: (Typeable hash, HashAlgorithm hash) => Git hash -> Ref hash -> IO (Commit hash)
- getTree :: (Typeable hash, HashAlgorithm hash) => Git hash -> Ref hash -> IO (Tree hash)
- setObject :: HashAlgorithm hash => Git hash -> Object hash -> IO (Ref hash)
- toObject :: Objectable a => a hash -> Object hash
- type WorkTree hash = MVar (TreeSt hash)
- data EntType
- workTreeNew :: IO (WorkTree hash)
- workTreeFrom :: Ref hash -> IO (WorkTree hash)
- workTreeDelete :: (Typeable hash, HashAlgorithm hash) => Git hash -> WorkTree hash -> EntPath -> IO ()
- workTreeSet :: (Typeable hash, HashAlgorithm hash) => Git hash -> WorkTree hash -> EntPath -> (EntType, Ref hash) -> IO ()
- workTreeFlush :: HashAlgorithm hash => Git hash -> WorkTree hash -> IO (Ref hash)
- branchWrite :: Git hash -> RefName -> Ref hash -> IO ()
- branchList :: Git hash -> IO (Set RefName)
- tagWrite :: Git hash -> RefName -> Ref hash -> IO ()
- tagList :: Git hash -> IO (Set RefName)
- headSet :: Git hash -> Either (Ref hash) RefName -> IO ()
- headGet :: HashAlgorithm hash => Git hash -> IO (Either (Ref hash) RefName)
Basic types
represent a git reference (SHA1)
Represent a commit object.
Commit | |
|
an author or committer line has the format: name email time timezone FIXME: should be a string, but I don't know if the data is stored consistantly in one encoding (UTF8)
Person | |
|
data CommitExtra Source #
Instances
Eq CommitExtra Source # | |
Defined in Data.Git.Types (==) :: CommitExtra -> CommitExtra -> Bool # (/=) :: CommitExtra -> CommitExtra -> Bool # | |
Show CommitExtra Source # | |
Defined in Data.Git.Types showsPrec :: Int -> CommitExtra -> ShowS # show :: CommitExtra -> String # showList :: [CommitExtra] -> ShowS # |
Represent a root tree with zero to many tree entries.
Tree | |
|
Represent a binary blob.
Represent a signed tag.
Tag | |
|
Git time is number of seconds since unix epoch in the UTC zone with the current timezone associated
Instances
Eq GitTime Source # | |
Show GitTime Source # | |
Timeable GitTime Source # | |
Defined in Data.Git.Types timeGetElapsedP :: GitTime -> ElapsedP # timeGetElapsed :: GitTime -> Elapsed # | |
Time GitTime Source # | |
Defined in Data.Git.Types timeFromElapsedP :: ElapsedP -> GitTime # timeFromElapsed :: Elapsed -> GitTime # |
Entity name
entName :: ByteString -> EntName Source #
Helper & type related to ModePerm
data ObjectFileType Source #
Git object file type
Instances
Eq ObjectFileType Source # | |
Defined in Data.Git.Types (==) :: ObjectFileType -> ObjectFileType -> Bool # (/=) :: ObjectFileType -> ObjectFileType -> Bool # | |
Show ObjectFileType Source # | |
Defined in Data.Git.Types showsPrec :: Int -> ObjectFileType -> ShowS # show :: ObjectFileType -> String # showList :: [ObjectFileType] -> ShowS # |
data FilePermissions Source #
traditional unix permission for owner, group and permissions
FilePermissions | |
|
Instances
Eq FilePermissions Source # | |
Defined in Data.Git.Types (==) :: FilePermissions -> FilePermissions -> Bool # (/=) :: FilePermissions -> FilePermissions -> Bool # | |
Show FilePermissions Source # | |
Defined in Data.Git.Types showsPrec :: Int -> FilePermissions -> ShowS # show :: FilePermissions -> String # showList :: [FilePermissions] -> ShowS # |
getFiletype :: ModePerm -> ObjectFileType Source #
Revision
A git revision. this can be many things:
* a shorten ref
* a ref
* a named branch or tag
followed by optional modifiers RevModifier
that can represent:
* parenting
* type
* date
Instances
Eq Revision Source # | |
Data Revision Source # | |
Defined in Data.Git.Revision gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Revision -> c Revision # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Revision # toConstr :: Revision -> Constr # dataTypeOf :: Revision -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Revision) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Revision) # gmapT :: (forall b. Data b => b -> b) -> Revision -> Revision # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Revision -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Revision -> r # gmapQ :: (forall d. Data d => d -> u) -> Revision -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Revision -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Revision -> m Revision # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Revision -> m Revision # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Revision -> m Revision # | |
Show Revision Source # | |
IsString Revision Source # | |
Defined in Data.Git.Revision fromString :: String -> Revision # | |
Resolvable Revision Source # | |
resolveRevision :: (Typeable hash, HashAlgorithm hash) => Git hash -> Revision -> IO (Maybe (Ref hash)) Source #
try to resolve a string to a specific commit ref for example: HEAD, HEAD^, master~3, shortRef
Object resolution
resolveTreeish :: HashAlgorithm hash => Git hash -> Ref hash -> IO (Maybe (Tree hash)) Source #
returns a tree from a ref that might be either a commit, a tree or a tag.
:: (Typeable hash, HashAlgorithm hash) | |
=> Git hash | repository |
-> Ref hash | commit reference |
-> EntPath | paths |
-> IO (Maybe (Ref hash)) |
resolve the ref (tree or blob) related to a path at a specific commit ref
repo context
represent a git repo, with possibly already opened filereaders for indexes and packs
withCurrentRepo :: (Git SHA1 -> IO a) -> IO a Source #
execute a function on the current repository.
check findRepo to see how the git repository is found.
withRepo :: LocalPath -> (Git SHA1 -> IO c) -> IO c Source #
execute a function f with a git context.
findRepo :: IO LocalPath Source #
Find the git repository from the current directory.
If the environment variable GIT_DIR is set then it's used, otherwise iterate from current directory, up to 128 parents for a .git directory
Repository queries and creation
isRepo :: LocalPath -> IO Bool Source #
basic checks to see if a specific path looks like a git repo.
Context operations
:: (Typeable hash, HashAlgorithm hash) | |
=> Git hash | Repository |
-> (Commit hash -> IO (Commit hash)) | Mapping function |
-> Revision | revision to start from |
-> Int | the number of parents to map |
-> IO (Ref hash) | return the new head REF |
Rewrite a set of commits from a revision and returns the new ref.
If during revision traversal (diving) there's a commit with zero or multiple parents then the traversal will stop regardless of the amount of parent requested.
calling "rewrite f 2 (revisionOf d)" on the following tree:
a <-- b <-- c <-- d
result in the following tree after mapping with f:
a <-- f(b) <-- f(c) <-- f(d)
Get objects
:: HashAlgorithm hash | |
=> Git hash | repository |
-> Ref hash | the object's reference to |
-> Bool | whether to resolve deltas if found |
-> IO (Maybe (Object hash)) | returned object if found |
get an object from repository using a ref.
getCommit :: (Typeable hash, HashAlgorithm hash) => Git hash -> Ref hash -> IO (Commit hash) Source #
get a specified commit but raises an exception if doesn't exists or type is not appropriate
getTree :: (Typeable hash, HashAlgorithm hash) => Git hash -> Ref hash -> IO (Tree hash) Source #
get a specified tree but raise
Set objects
setObject :: HashAlgorithm hash => Git hash -> Object hash -> IO (Ref hash) Source #
set an object in the store and returns the new ref this is always going to create a loose object.
toObject :: Objectable a => a hash -> Object hash Source #
Work trees
workTreeNew :: IO (WorkTree hash) Source #
Create a new worktree
workTreeDelete :: (Typeable hash, HashAlgorithm hash) => Git hash -> WorkTree hash -> EntPath -> IO () Source #
delete a path from a working tree
if the path doesn't exist, no error is raised
workTreeSet :: (Typeable hash, HashAlgorithm hash) => Git hash -> WorkTree hash -> EntPath -> (EntType, Ref hash) -> IO () Source #
Set a file in this working tree to a specific ref.
The ref should point to a valid blob or tree object, and it's safer to write the referenced tree or blob object first.
workTreeFlush :: HashAlgorithm hash => Git hash -> WorkTree hash -> IO (Ref hash) Source #
Flush the worktree by creating all the necessary trees in the git store and return the root ref of the work tree.
Named refs
:: Git hash | repository |
-> RefName | the name of the branch to write |
-> Ref hash | the reference to set |
-> IO () |
Write a branch to point to a specific reference
Write a tag to point to a specific reference
Set head to point to either a reference or a branch name.