git-0.1: Git operations in haskell

LicenseBSD-style
MaintainerNicolas DI PRIMA <nicolas@di-prima.fr>
Stabilityexperimental
Portabilityunix
Safe HaskellNone
LanguageHaskell98

Data.Git.Monad

Contents

Description

Simplifies the Git operation presents in this package.

You can easily access to the usual Git general informations:

  • access to Head, Branches or Tags
  • direct access to a Commit

This module also defines a convenient Monad to access the whole information from a Commit: see CommitAccessMonad and withCommit.

You can also easily create a new commit: see CommitM and withNewCommit

Synopsis

GitMonad

class (Functor m, Applicative m, Monad m) => GitMonad m where Source

Basic operations common between the different Monads defined in this package.

Methods

getGit :: m Git Source

the current Monad must allow access to the current Git

liftGit :: IO a -> m a Source

withRepo :: LocalPath -> GitM a -> IO (Either String a) Source

Operations

class Resolvable rev where Source

this is a convenient class to allow a common interface for what user may need to optain a Ref from a given Resolvable object.

each of this instances is a convenient implementation of what a user would have to do in order to resolve a branch, a tag or a String.

resolve (Ref "2ad98b90...2ca") === Ref "2ad98b90...2ca"
resolve "master"
resolve "HEAD^^^"

Methods

resolve :: GitMonad m => rev -> m (Maybe Ref) Source

branchWrite :: GitMonad git => RefName -> Ref -> git () Source

tagWrite :: GitMonad git => RefName -> Ref -> git () Source

headSet :: GitMonad git => Either Ref RefName -> git () Source

getCommit :: (GitMonad git, Resolvable ref) => ref -> git (Maybe Commit) Source

Read a commit

withCommit Source

Arguments

:: (Resolvable ref, GitMonad git) 
=> ref

the commit revision or reference to open

-> CommitAccessM a 
-> git a 

open a commit in the current GitMonad

Read commit's info (Author, Committer, message...) or Commit's Tree.

withCurrentRepo $
   withCommit "master" $ do
       -- print the commit's author information
       author <- getAuthor
       liftGit $ print author

       -- print the list of files|dirs in the root directory
       l <- getDir []
       liftGit $ print l

Operations

getFile :: EntPath -> CommitAccessM (Maybe ByteString) Source

get the content of the file at the given Path

if the given Path is not a file or does not exist, the function returns Nothing.

getDir :: EntPath -> CommitAccessM (Maybe [EntName]) Source

list the element present in the Given Directory Path

if the given Path is not a directory or does not exist, the function returns Nothing.

Create a new Commit

withNewCommit Source

Arguments

:: (GitMonad git, Resolvable rev) 
=> Person

by default a commit must have an Author and a Committer.

The given value will be given to both Author and Committer.

-> Maybe rev

it is possible to prepopulate the Working Tree with a given Ref's Tree.

-> CommitM a

the action to perform in the new commit (set files, Person, encoding or extras)

-> git (Ref, a) 

create a new commit in the current GitMonad

The commit is pre-filled with the following default values:

  • author and committer are the same
  • the commit's parents is an empty list
  • there is no commit encoding
  • the commit's extras is an empty list
  • the commit message is an empty ByteString
  • the working tree is a new empty Tree or the Tree associated to the given Revision or Ref.

You can update these values with the commit setters (setFile, setAuthor...)

Example:

withCurrentRepo $
   (r, ()) <- withNewCommit person Nothing $ do
       setMessage "inital commit"
       setFile ["README.md"] "# My awesome project\n\nthis is a new project\n"
   branchWrite "master" r

you can also continue the work on a same branch. In this case the commit's parent is already set to the Reference associated to the revision. You can, change the parents if you wish to erase, or replace, this value.

withCurrentRepo $
   readmeContent <- withCommit (Just "master") $ getFile ["README.md"]
   (r, ()) <- withNewCommit person (Just "master") $ do
       setMessage "update the README"
       setFile ["README.md"] $ readmeContent <> "just add some more description\n"
   branchWrite "master" r

withBranch Source

Arguments

:: GitMonad git 
=> Person

the default Author and Committer (see withNewCommit)

-> RefName

the branch to work on

-> Bool

propopulate the parent's tree (if it exists) in the new created commit.

In any cases, if the branch already exists, the new commit parent will be filled with the result of (resolv "branchName")

-> CommitAccessM a

the action to performs in the parent's new commit if it exists.

-> (Maybe a -> CommitM b)

the action to performs in the new commit

the argument is the result of the action on the parent commit.

Nothing if the parent does not exist.

-> git (Ref, b) 

create or continue to work on a branch

This is a convenient function to create or to linearily work on a branch. This function applies a first Collect of information on the parent commit (the actual branch's commit). Then it creates a new commit and update the branch to point to this commit.

for example:

withCurrentRepo $
    withBranch person "master" True
        (getAuthor)
        (maybe (setMessage "initial commit on this branch")
               (author -> setMessage $ "continue the great work of " ++ show (personName author))
        )

Operations

setAuthor :: Person -> CommitM () Source

replace the Commit's Author

setCommitter :: Person -> CommitM () Source

replace the Commit's Committer

setParents :: [Ref] -> CommitM () Source

replace the Commit's Parents

setExtras :: [CommitExtra] -> CommitM () Source

replace the Commit's Extras

setEncoding :: Maybe ByteString -> CommitM () Source

replace the Commit's encoding

setMessage :: ByteString -> CommitM () Source

replace the Commit's message with the new given message.

setFile :: EntPath -> ByteString -> CommitM () Source

add a new file in in the Commit's Working Tree

deleteFile :: EntPath -> CommitM () Source

delete a file from the Commit's Working Tree.

convenients re-exports

data Git Source

represent a git repo, with possibly already opened filereaders for indexes and packs

data Ref Source

represent a git reference (SHA1)

data Person Source

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)