move hashObject to HashObject library and generalize it to support all git object types

This commit is contained in:
Joey Hess 2012-06-06 02:31:31 -04:00
parent f1bd72ea54
commit f596084a59
4 changed files with 36 additions and 22 deletions

View file

@ -21,6 +21,7 @@ import Common
import Git import Git
import Git.Sha import Git.Sha
import Git.Command import Git.Command
import Git.Types
import qualified Utility.CoProcess as CoProcess import qualified Utility.CoProcess as CoProcess
type CatFileHandle = CoProcess.CoProcessHandle type CatFileHandle = CoProcess.CoProcessHandle
@ -52,7 +53,7 @@ catObject h object = CoProcess.query h send receive
case words header of case words header of
[sha, objtype, size] [sha, objtype, size]
| length sha == shaSize && | length sha == shaSize &&
validobjtype objtype -> isJust (readObjectType objtype) ->
case reads size of case reads size of
[(bytes, "")] -> readcontent bytes from [(bytes, "")] -> readcontent bytes from
_ -> dne _ -> dne
@ -67,8 +68,3 @@ catObject h object = CoProcess.query h send receive
error "missing newline from git cat-file" error "missing newline from git cat-file"
return $ L.fromChunks [content] return $ L.fromChunks [content]
dne = return L.empty dne = return L.empty
validobjtype t
| t == "blob" = True
| t == "commit" = True
| t == "tree" = True
| otherwise = False

View file

@ -9,7 +9,9 @@ module Git.HashObject where
import Common import Common
import Git import Git
import Git.Sha
import Git.Command import Git.Command
import Git.Types
import qualified Utility.CoProcess as CoProcess import qualified Utility.CoProcess as CoProcess
type HashObjectHandle = CoProcess.CoProcessHandle type HashObjectHandle = CoProcess.CoProcessHandle
@ -24,11 +26,23 @@ hashObjectStart = CoProcess.start "git" . toCommand . gitCommandLine
hashObjectStop :: HashObjectHandle -> IO () hashObjectStop :: HashObjectHandle -> IO ()
hashObjectStop = CoProcess.stop hashObjectStop = CoProcess.stop
{- Injects a file into git, returning the shas of the objects. -} {- Injects a file into git, returning the Sha of the object. -}
hashFile :: HashObjectHandle -> FilePath -> IO Sha hashFile :: HashObjectHandle -> FilePath -> IO Sha
hashFile h file = CoProcess.query h send receive hashFile h file = CoProcess.query h send receive
where where
send to = do send to = do
fileEncoding to fileEncoding to
hPutStrLn to file hPutStrLn to file
receive from = Ref <$> hGetLine from receive from = getSha "hash-object" $ hGetLine from
{- Injects some content into git, returning its Sha. -}
hashObject :: Repo -> ObjectType -> String -> IO Sha
hashObject repo objtype content = getSha subcmd $ do
(h, s) <- pipeWriteRead (map Param params) content repo
length s `seq` do
forceSuccess h
reap -- XXX unsure why this is needed
return s
where
subcmd = "hash-object"
params = [subcmd, "-t", show objtype, "-w", "--stdin"]

View file

@ -48,3 +48,18 @@ instance Show Ref where
type Branch = Ref type Branch = Ref
type Sha = Ref type Sha = Ref
type Tag = Ref type Tag = Ref
{- Types of objects that can be stored in git. -}
data ObjectType = BlobObject | CommitObject | TreeObject
instance Show ObjectType where
show BlobObject = "blob"
show CommitObject = "commit"
show TreeObject = "tree"
readObjectType :: String -> Maybe ObjectType
readObjectType "blob" = Just BlobObject
readObjectType "commit" = Just CommitObject
readObjectType "tree" = Just TreeObject
readObjectType _ = Nothing

View file

@ -10,7 +10,6 @@ module Git.UnionMerge (
merge_index merge_index
) where ) where
import System.Cmd.Utils
import qualified Data.Text.Lazy as L import qualified Data.Text.Lazy as L
import qualified Data.Text.Lazy.Encoding as L import qualified Data.Text.Lazy.Encoding as L
import qualified Data.Set as S import qualified Data.Set as S
@ -21,6 +20,8 @@ import Git.Sha
import Git.CatFile import Git.CatFile
import Git.Command import Git.Command
import Git.UpdateIndex import Git.UpdateIndex
import Git.HashObject
import Git.Types
{- Performs a union merge between two branches, staging it in the index. {- Performs a union merge between two branches, staging it in the index.
- Any previously staged changes in the index will be lost. - Any previously staged changes in the index will be lost.
@ -72,7 +73,7 @@ mergeFile :: String -> FilePath -> CatFileHandle -> Repo -> IO (Maybe String)
mergeFile info file h repo = case filter (/= nullSha) [Ref asha, Ref bsha] of mergeFile info file h repo = case filter (/= nullSha) [Ref asha, Ref bsha] of
[] -> return Nothing [] -> return Nothing
(sha:[]) -> use sha (sha:[]) -> use sha
shas -> use =<< either return (hashObject repo . unlines) =<< shas -> use =<< either return (hashObject repo BlobObject . unlines) =<<
calcMerge . zip shas <$> mapM getcontents shas calcMerge . zip shas <$> mapM getcontents shas
where where
[_colonmode, _bmode, asha, bsha, _status] = words info [_colonmode, _bmode, asha, bsha, _status] = words info
@ -80,18 +81,6 @@ mergeFile info file h repo = case filter (/= nullSha) [Ref asha, Ref bsha] of
L.decodeUtf8 <$> catObject h s L.decodeUtf8 <$> catObject h s
use sha = return $ Just $ update_index_line sha file use sha = return $ Just $ update_index_line sha file
{- Injects some content into git, returning its Sha. -}
hashObject :: Repo -> String -> IO Sha
hashObject repo content = getSha subcmd $ do
(h, s) <- pipeWriteRead (map Param params) content repo
length s `seq` do
forceSuccess h
reap -- XXX unsure why this is needed
return s
where
subcmd = "hash-object"
params = [subcmd, "-w", "--stdin"]
{- Calculates a union merge between a list of refs, with contents. {- Calculates a union merge between a list of refs, with contents.
- -
- When possible, reuses the content of an existing ref, rather than - When possible, reuses the content of an existing ref, rather than