License | BSD-style |
---|---|
Maintainer | Vincent Hanquez <vincent@snarc.org> |
Stability | experimental |
Portability | unix |
Safe Haskell | None |
Language | Haskell98 |
Data.Git.Types
Contents
Description
Synopsis
- data ObjectType
- newtype Tree hash = Tree {
- treeGetEnts :: [TreeEnt hash]
- data Commit hash = Commit {
- commitTreeish :: !(Ref hash)
- commitParents :: [Ref hash]
- commitAuthor :: !Person
- commitCommitter :: !Person
- commitEncoding :: Maybe ByteString
- commitExtras :: [CommitExtra]
- commitMessage :: !ByteString
- data CommitExtra = CommitExtra {}
- newtype Blob hash = Blob {}
- data Tag hash = Tag {
- tagRef :: !(Ref hash)
- tagObjectType :: !ObjectType
- tagBlob :: !ByteString
- tagName :: !Person
- tagS :: !ByteString
- data Person = Person {
- personName :: !ByteString
- personEmail :: !ByteString
- personTime :: !GitTime
- data EntName
- entName :: ByteString -> EntName
- getEntNameBytes :: EntName -> ByteString
- type EntPath = [EntName]
- entPathAppend :: EntPath -> EntName -> EntPath
- newtype ModePerm = ModePerm Word32
- data FilePermissions = FilePermissions {
- getOwnerPerm :: !Perm
- getGroupPerm :: !Perm
- getOtherPerm :: !Perm
- data ObjectFileType
- getPermission :: ModePerm -> FilePermissions
- getFiletype :: ModePerm -> ObjectFileType
- data GitTime = GitTime {}
- gitTime :: Integer -> Int -> GitTime
- gitTimeToLocal :: GitTime -> LocalTime Elapsed
- data DeltaOfs hash = DeltaOfs !Word64 !Delta
- data DeltaRef hash = DeltaRef !(Ref hash) !Delta
- type TreeEnt hash = (ModePerm, EntName, Ref hash)
Type of types
data ObjectType Source #
type of a git object.
Constructors
TypeTree | |
TypeBlob | |
TypeCommit | |
TypeTag | |
TypeDeltaOff | |
TypeDeltaRef |
Instances
Enum ObjectType Source # | the enum instance is useful when marshalling to pack file. |
Defined in Data.Git.Types Methods succ :: ObjectType -> ObjectType # pred :: ObjectType -> ObjectType # toEnum :: Int -> ObjectType # fromEnum :: ObjectType -> Int # enumFrom :: ObjectType -> [ObjectType] # enumFromThen :: ObjectType -> ObjectType -> [ObjectType] # enumFromTo :: ObjectType -> ObjectType -> [ObjectType] # enumFromThenTo :: ObjectType -> ObjectType -> ObjectType -> [ObjectType] # | |
Eq ObjectType Source # | |
Defined in Data.Git.Types | |
Data ObjectType Source # | |
Defined in Data.Git.Types Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ObjectType -> c ObjectType # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ObjectType # toConstr :: ObjectType -> Constr # dataTypeOf :: ObjectType -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ObjectType) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ObjectType) # gmapT :: (forall b. Data b => b -> b) -> ObjectType -> ObjectType # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ObjectType -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ObjectType -> r # gmapQ :: (forall d. Data d => d -> u) -> ObjectType -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ObjectType -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ObjectType -> m ObjectType # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ObjectType -> m ObjectType # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ObjectType -> m ObjectType # | |
Show ObjectType Source # | |
Defined in Data.Git.Types Methods showsPrec :: Int -> ObjectType -> ShowS # show :: ObjectType -> String # showList :: [ObjectType] -> ShowS # |
Main git types
Represent a root tree with zero to many tree entries.
Constructors
Tree | |
Fields
|
Represent a commit object.
Constructors
Commit | |
Fields
|
data CommitExtra Source #
Constructors
CommitExtra | |
Fields |
Instances
Eq CommitExtra Source # | |
Defined in Data.Git.Types | |
Show CommitExtra Source # | |
Defined in Data.Git.Types Methods showsPrec :: Int -> CommitExtra -> ShowS # show :: CommitExtra -> String # showList :: [CommitExtra] -> ShowS # |
Represent a binary blob.
Constructors
Blob | |
Fields |
Represent a signed tag.
Constructors
Tag | |
Fields
|
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)
Constructors
Person | |
Fields
|
Entity name
entName :: ByteString -> EntName Source #
getEntNameBytes :: EntName -> ByteString Source #
modeperm type
data FilePermissions Source #
traditional unix permission for owner, group and permissions
Constructors
FilePermissions | |
Fields
|
Instances
Eq FilePermissions Source # | |
Defined in Data.Git.Types Methods (==) :: FilePermissions -> FilePermissions -> Bool # (/=) :: FilePermissions -> FilePermissions -> Bool # | |
Show FilePermissions Source # | |
Defined in Data.Git.Types Methods showsPrec :: Int -> FilePermissions -> ShowS # show :: FilePermissions -> String # showList :: [FilePermissions] -> ShowS # |
data ObjectFileType Source #
Git object file type
Instances
Eq ObjectFileType Source # | |
Defined in Data.Git.Types Methods (==) :: ObjectFileType -> ObjectFileType -> Bool # (/=) :: ObjectFileType -> ObjectFileType -> Bool # | |
Show ObjectFileType Source # | |
Defined in Data.Git.Types Methods showsPrec :: Int -> ObjectFileType -> ShowS # show :: ObjectFileType -> String # showList :: [ObjectFileType] -> ShowS # |
getFiletype :: ModePerm -> ObjectFileType Source #
time type
Git time is number of seconds since unix epoch in the UTC zone with the current timezone associated
Constructors
GitTime | |
Fields |
Pack delta types
Delta pointing to an offset.
Delta pointing to a ref.