diff options
author | Joey Hess <joey@kitenet.net> | 2014-02-19 01:09:17 -0400 |
---|---|---|
committer | Joey Hess <joey@kitenet.net> | 2014-02-19 01:19:57 -0400 |
commit | 51c12a76ef54affaf9428232fde4f2c3e30e7488 (patch) | |
tree | 4cb2699e2b410260e383d3bf6da14d502aa0d0dc /Git | |
parent | b5b5ead4b28fd08100bcac9cb9482263bac3a64e (diff) |
remove Read instance for Ref
Removed instance, got it all to build using fromRef. (With a few things
that really need to show something using a ref for debugging stubbed out.)
Then added back Read instance, and made Logs.View use it for serialization.
This changes the view log format.
Diffstat (limited to 'Git')
-rw-r--r-- | Git/Branch.hs | 20 | ||||
-rw-r--r-- | Git/CatFile.hs | 8 | ||||
-rw-r--r-- | Git/DiffTree.hs | 6 | ||||
-rw-r--r-- | Git/Fsck.hs | 2 | ||||
-rw-r--r-- | Git/LsTree.hs | 4 | ||||
-rw-r--r-- | Git/Merge.hs | 4 | ||||
-rw-r--r-- | Git/Objects.hs | 2 | ||||
-rw-r--r-- | Git/Ref.hs | 20 | ||||
-rw-r--r-- | Git/RefLog.hs | 2 | ||||
-rw-r--r-- | Git/Repair.hs | 24 | ||||
-rw-r--r-- | Git/Types.hs | 6 | ||||
-rw-r--r-- | Git/UpdateIndex.hs | 4 |
12 files changed, 51 insertions, 51 deletions
diff --git a/Git/Branch.hs b/Git/Branch.hs index 405fa108f..d182ceb39 100644 --- a/Git/Branch.hs +++ b/Git/Branch.hs @@ -28,7 +28,7 @@ current r = do case v of Nothing -> return Nothing Just branch -> - ifM (null <$> pipeReadStrict [Param "show-ref", Param $ show branch] r) + ifM (null <$> pipeReadStrict [Param "show-ref", Param $ fromRef branch] r) ( return Nothing , return v ) @@ -36,7 +36,7 @@ current r = do {- The current branch, which may not really exist yet. -} currentUnsafe :: Repo -> IO (Maybe Git.Ref) currentUnsafe r = parse . firstLine - <$> pipeReadStrict [Param "symbolic-ref", Param $ show Git.Ref.headRef] r + <$> pipeReadStrict [Param "symbolic-ref", Param $ fromRef Git.Ref.headRef] r where parse l | null l = Nothing @@ -51,7 +51,7 @@ changed origbranch newbranch repo where diffs = pipeReadStrict [ Param "log" - , Param (show origbranch ++ ".." ++ show newbranch) + , Param (fromRef origbranch ++ ".." ++ fromRef newbranch) , Params "--oneline -n1" ] repo @@ -74,7 +74,7 @@ fastForward branch (first:rest) repo = where no_ff = return False do_ff to = do - run [Param "update-ref", Param $ show branch, Param $ show to] repo + run [Param "update-ref", Param $ fromRef branch, Param $ fromRef to] repo return True findbest c [] = return $ Just c findbest c (r:rs) @@ -104,14 +104,14 @@ commit allowempty message branch parentrefs repo = do ifM (cancommit tree) ( do sha <- getSha "commit-tree" $ pipeWriteRead - (map Param $ ["commit-tree", show tree] ++ ps) + (map Param $ ["commit-tree", fromRef tree] ++ ps) (Just $ flip hPutStr message) repo update branch sha repo return $ Just sha , return Nothing ) where - ps = concatMap (\r -> ["-p", show r]) parentrefs + ps = concatMap (\r -> ["-p", fromRef r]) parentrefs cancommit tree | allowempty = return True | otherwise = case parentrefs of @@ -130,8 +130,8 @@ forcePush b = "+" ++ b update :: Branch -> Sha -> Repo -> IO () update branch sha = run [ Param "update-ref" - , Param $ show branch - , Param $ show sha + , Param $ fromRef branch + , Param $ fromRef sha ] {- Checks out a branch, creating it if necessary. -} @@ -140,7 +140,7 @@ checkout branch = run [ Param "checkout" , Param "-q" , Param "-B" - , Param $ show $ Git.Ref.base branch + , Param $ fromRef $ Git.Ref.base branch ] {- Removes a branch. -} @@ -149,5 +149,5 @@ delete branch = run [ Param "branch" , Param "-q" , Param "-D" - , Param $ show $ Git.Ref.base branch + , Param $ fromRef $ Git.Ref.base branch ] diff --git a/Git/CatFile.hs b/Git/CatFile.hs index aee6bd19f..c8cb76d59 100644 --- a/Git/CatFile.hs +++ b/Git/CatFile.hs @@ -50,7 +50,7 @@ catFileStop (CatFileHandle p _) = CoProcess.stop p {- Reads a file from a specified branch. -} catFile :: CatFileHandle -> Branch -> FilePath -> IO L.ByteString catFile h branch file = catObject h $ Ref $ - show branch ++ ":" ++ toInternalGitPath file + fromRef branch ++ ":" ++ toInternalGitPath file {- Uses a running git cat-file read the content of an object. - Objects that do not exist will have "" returned. -} @@ -60,7 +60,7 @@ catObject h object = maybe L.empty fst3 <$> catObjectDetails h object catObjectDetails :: CatFileHandle -> Ref -> IO (Maybe (L.ByteString, Sha, ObjectType)) catObjectDetails (CatFileHandle hdl _) object = CoProcess.query hdl send receive where - query = show object + query = fromRef object send to = hPutStrLn to query receive from = do header <- hGetLine from @@ -72,8 +72,8 @@ catObjectDetails (CatFileHandle hdl _) object = CoProcess.query hdl send receive _ -> dne | otherwise -> dne _ - | header == show object ++ " missing" -> dne - | otherwise -> error $ "unknown response from git cat-file " ++ show (header, object) + | header == fromRef object ++ " missing" -> dne + | otherwise -> error $ "unknown response from git cat-file " ++ show (header, query) readcontent objtype bytes from sha = do content <- S.hGet from bytes eatchar '\n' from diff --git a/Git/DiffTree.hs b/Git/DiffTree.hs index c82cf78cd..9e4fef9d6 100644 --- a/Git/DiffTree.hs +++ b/Git/DiffTree.hs @@ -36,12 +36,12 @@ data DiffTreeItem = DiffTreeItem {- Diffs two tree Refs. -} diffTree :: Ref -> Ref -> Repo -> IO ([DiffTreeItem], IO Bool) diffTree src dst = getdiff (Param "diff-tree") - [Param (show src), Param (show dst)] + [Param (fromRef src), Param (fromRef dst)] {- Diffs two tree Refs, recursing into sub-trees -} diffTreeRecursive :: Ref -> Ref -> Repo -> IO ([DiffTreeItem], IO Bool) diffTreeRecursive src dst = getdiff (Param "diff-tree") - [Param "-r", Param (show src), Param (show dst)] + [Param "-r", Param (fromRef src), Param (fromRef dst)] {- Diffs between a tree and the index. Does nothing if there is not yet a - commit in the repository. -} @@ -61,7 +61,7 @@ diffIndex' :: Ref -> [CommandParam] -> Repo -> IO ([DiffTreeItem], IO Bool) diffIndex' ref params repo = ifM (Git.Ref.headExists repo) ( getdiff (Param "diff-index") - ( params ++ [Param $ show ref] ) + ( params ++ [Param $ fromRef ref] ) repo , return ([], return True) ) diff --git a/Git/Fsck.hs b/Git/Fsck.hs index 23d3a3558..e90683bc0 100644 --- a/Git/Fsck.hs +++ b/Git/Fsck.hs @@ -74,7 +74,7 @@ isMissing s r = either (const True) (const False) <$> tryIO dump where dump = runQuiet [ Param "show" - , Param (show s) + , Param (fromRef s) ] r findShas :: Bool -> String -> [Sha] diff --git a/Git/LsTree.hs b/Git/LsTree.hs index 956f9f5b4..6d3ca4813 100644 --- a/Git/LsTree.hs +++ b/Git/LsTree.hs @@ -38,13 +38,13 @@ lsTree t repo = map parseLsTree <$> pipeNullSplitZombie (lsTreeParams t) repo lsTreeParams :: Ref -> [CommandParam] -lsTreeParams t = [ Params "ls-tree --full-tree -z -r --", File $ show t ] +lsTreeParams t = [ Params "ls-tree --full-tree -z -r --", File $ fromRef t ] {- Lists specified files in a tree. -} lsTreeFiles :: Ref -> [FilePath] -> Repo -> IO [TreeItem] lsTreeFiles t fs repo = map parseLsTree <$> pipeNullSplitStrict ps repo where - ps = [Params "ls-tree --full-tree -z --", File $ show t] ++ map File fs + ps = [Params "ls-tree --full-tree -z --", File $ fromRef t] ++ map File fs {- Parses a line of ls-tree output. - (The --long format is not currently supported.) -} diff --git a/Git/Merge.hs b/Git/Merge.hs index f5791274f..948e09e01 100644 --- a/Git/Merge.hs +++ b/Git/Merge.hs @@ -15,7 +15,7 @@ import Git.BuildVersion {- Avoids recent git's interactive merge. -} mergeNonInteractive :: Ref -> Repo -> IO Bool mergeNonInteractive branch - | older "1.7.7.6" = merge [Param $ show branch] - | otherwise = merge [Param "--no-edit", Param $ show branch] + | older "1.7.7.6" = merge [Param $ fromRef branch] + | otherwise = merge [Param "--no-edit", Param $ fromRef branch] where merge ps = runBool $ Param "merge" : ps diff --git a/Git/Objects.hs b/Git/Objects.hs index bb492f558..516aa6d3e 100644 --- a/Git/Objects.hs +++ b/Git/Objects.hs @@ -32,4 +32,4 @@ listLooseObjectShas r = catchDefaultIO [] $ looseObjectFile :: Repo -> Sha -> FilePath looseObjectFile r sha = objectsDir r </> prefix </> rest where - (prefix, rest) = splitAt 2 (show sha) + (prefix, rest) = splitAt 2 (fromRef sha) diff --git a/Git/Ref.hs b/Git/Ref.hs index 88717ce47..3d0c68fb0 100644 --- a/Git/Ref.hs +++ b/Git/Ref.hs @@ -20,12 +20,12 @@ headRef = Ref "HEAD" {- Converts a fully qualified git ref into a user-visible string. -} describe :: Ref -> String -describe = show . base +describe = fromRef . base {- Often git refs are fully qualified (eg: refs/heads/master). - Converts such a fully qualified ref into a base ref (eg: master). -} base :: Ref -> Ref -base = Ref . remove "refs/heads/" . remove "refs/remotes/" . show +base = Ref . remove "refs/heads/" . remove "refs/remotes/" . fromRef where remove prefix s | prefix `isPrefixOf` s = drop (length prefix) s @@ -35,13 +35,13 @@ base = Ref . remove "refs/heads/" . remove "refs/remotes/" . show - it under the directory. -} under :: String -> Ref -> Ref under dir r = Ref $ dir ++ "/" ++ - (reverse $ takeWhile (/= '/') $ reverse $ show r) + (reverse $ takeWhile (/= '/') $ reverse $ fromRef r) {- Given a directory such as "refs/remotes/origin", and a ref such as - refs/heads/master, yields a version of that ref under the directory, - such as refs/remotes/origin/master. -} underBase :: String -> Ref -> Ref -underBase dir r = Ref $ dir ++ "/" ++ show (base r) +underBase dir r = Ref $ dir ++ "/" ++ fromRef (base r) {- A Ref that can be used to refer to a file in the repository, as staged - in the index. @@ -64,12 +64,12 @@ fileFromRef (Ref r) f = let (Ref fr) = fileRef f in Ref (r ++ fr) {- Checks if a ref exists. -} exists :: Ref -> Repo -> IO Bool exists ref = runBool - [Param "show-ref", Param "--verify", Param "-q", Param $ show ref] + [Param "show-ref", Param "--verify", Param "-q", Param $ fromRef ref] {- The file used to record a ref. (Git also stores some refs in a - packed-refs file.) -} file :: Ref -> Repo -> FilePath -file ref repo = localGitDir repo </> show ref +file ref repo = localGitDir repo </> fromRef ref {- Checks if HEAD exists. It generally will, except for in a repository - that was just created. -} @@ -84,17 +84,17 @@ sha branch repo = process <$> showref repo where showref = pipeReadStrict [Param "show-ref", Param "--hash", -- get the hash - Param $ show branch] + Param $ fromRef branch] process [] = Nothing process s = Just $ Ref $ firstLine s {- List of (shas, branches) matching a given ref or refs. -} matching :: [Ref] -> Repo -> IO [(Sha, Branch)] -matching refs repo = matching' (map show refs) repo +matching refs repo = matching' (map fromRef refs) repo {- Includes HEAD in the output, if asked for it. -} matchingWithHEAD :: [Ref] -> Repo -> IO [(Sha, Branch)] -matchingWithHEAD refs repo = matching' ("--head" : map show refs) repo +matchingWithHEAD refs repo = matching' ("--head" : map fromRef refs) repo {- List of (shas, branches) matching a given ref or refs. -} matching' :: [String] -> Repo -> IO [(Sha, Branch)] @@ -114,7 +114,7 @@ matchingUniq refs repo = nubBy uniqref <$> matching refs repo {- Gets the sha of the tree a ref uses. -} tree :: Ref -> Repo -> IO (Maybe Sha) tree ref = extractSha <$$> pipeReadStrict - [ Param "rev-parse", Param (show ref ++ ":") ] + [ Param "rev-parse", Param (fromRef ref ++ ":") ] {- Checks if a String is a legal git ref name. - diff --git a/Git/RefLog.hs b/Git/RefLog.hs index 3f41e8eaa..98c9d66ff 100644 --- a/Git/RefLog.hs +++ b/Git/RefLog.hs @@ -18,5 +18,5 @@ get b = mapMaybe extractSha . lines <$$> pipeReadStrict [ Param "log" , Param "-g" , Param "--format=%H" - , Param (show b) + , Param (fromRef b) ] diff --git a/Git/Repair.hs b/Git/Repair.hs index 2c0983609..96da5ffe7 100644 --- a/Git/Repair.hs +++ b/Git/Repair.hs @@ -168,7 +168,7 @@ resetLocalBranches :: MissingObjects -> GoodCommits -> Repo -> IO ([Branch], [Br resetLocalBranches missing goodcommits r = go [] [] goodcommits =<< filter islocalbranch <$> getAllRefs r where - islocalbranch b = "refs/heads/" `isPrefixOf` show b + islocalbranch b = "refs/heads/" `isPrefixOf` fromRef b go changed deleted gcs [] = return (changed, deleted, gcs) go changed deleted gcs (b:bs) = do (mc, gcs') <- findUncorruptedCommit missing gcs b r @@ -185,12 +185,12 @@ resetLocalBranches missing goodcommits r = nukeBranchRef b r void $ runBool [ Param "branch" - , Param (show $ Ref.base b) - , Param (show c) + , Param (fromRef $ Ref.base b) + , Param (fromRef c) ] r isTrackingBranch :: Ref -> Bool -isTrackingBranch b = "refs/remotes/" `isPrefixOf` show b +isTrackingBranch b = "refs/remotes/" `isPrefixOf` fromRef b {- To deal with missing objects that cannot be recovered, removes - any branches (filtered by a predicate) that reference them @@ -231,10 +231,10 @@ explodePackedRefsFile r = do nukeFile f where makeref (sha, ref) = do - let dest = localGitDir r </> show ref + let dest = localGitDir r </> fromRef ref createDirectoryIfMissing True (parentDir dest) unlessM (doesFileExist dest) $ - writeFile dest (show sha) + writeFile dest (fromRef sha) packedRefsFile :: Repo -> FilePath packedRefsFile r = localGitDir r </> "packed-refs" @@ -249,7 +249,7 @@ parsePacked l = case words l of {- git-branch -d cannot be used to remove a branch that is directly - pointing to a corrupt commit. -} nukeBranchRef :: Branch -> Repo -> IO () -nukeBranchRef b r = nukeFile $ localGitDir r </> show b +nukeBranchRef b r = nukeFile $ localGitDir r </> fromRef b {- Finds the most recent commit to a branch that does not need any - of the missing objects. If the input branch is good as-is, returns it. @@ -268,7 +268,7 @@ findUncorruptedCommit missing goodcommits branch r = do [ Param "log" , Param "-z" , Param "--format=%H" - , Param (show branch) + , Param (fromRef branch) ] r let branchshas = catMaybes $ map extractSha ls reflogshas <- RefLog.get branch r @@ -297,7 +297,7 @@ verifyCommit missing goodcommits commit r [ Param "log" , Param "-z" , Param "--format=%H %T" - , Param (show commit) + , Param (fromRef commit) ] r let committrees = map parse ls if any isNothing committrees || null committrees @@ -501,9 +501,9 @@ runRepair' removablebranch fsckresult forced referencerepo g = do , "remote tracking branches that referred to missing objects." ] (resetbranches, deletedbranches, _) <- resetLocalBranches stillmissing goodcommits g - displayList (map show resetbranches) + displayList (map fromRef resetbranches) "Reset these local branches to old versions before the missing objects were committed:" - displayList (map show deletedbranches) + displayList (map fromRef deletedbranches) "Deleted these local branches, which could not be recovered due to missing objects:" deindexedfiles <- rewriteIndex g displayList deindexedfiles @@ -519,7 +519,7 @@ runRepair' removablebranch fsckresult forced referencerepo g = do Just curr -> when (any (== curr) modifiedbranches) $ do putStrLn $ unwords [ "You currently have" - , show curr + , fromRef curr , "checked out. You may have staged changes in the index that can be committed to recover the lost state of this branch!" ] putStrLn "Successfully recovered repository!" diff --git a/Git/Types.hs b/Git/Types.hs index d805d8574..802922532 100644 --- a/Git/Types.hs +++ b/Git/Types.hs @@ -47,10 +47,10 @@ type RemoteName = String {- A git ref. Can be a sha1, or a branch or tag name. -} newtype Ref = Ref String - deriving (Eq, Ord) + deriving (Eq, Ord, Read, Show) -instance Show Ref where - show (Ref v) = v +fromRef :: Ref -> String +fromRef (Ref s) = s {- Aliases for Ref. -} type Branch = Ref diff --git a/Git/UpdateIndex.hs b/Git/UpdateIndex.hs index 73beaba3a..6d1ff2548 100644 --- a/Git/UpdateIndex.hs +++ b/Git/UpdateIndex.hs @@ -79,7 +79,7 @@ lsTree (Ref x) repo streamer = do - a given file with a given sha. -} updateIndexLine :: Sha -> BlobType -> TopFilePath -> String updateIndexLine sha filetype file = - show filetype ++ " blob " ++ show sha ++ "\t" ++ indexPath file + show filetype ++ " blob " ++ fromRef sha ++ "\t" ++ indexPath file stageFile :: Sha -> BlobType -> FilePath -> Repo -> IO Streamer stageFile sha filetype file repo = do @@ -90,7 +90,7 @@ stageFile sha filetype file repo = do unstageFile :: FilePath -> Repo -> IO Streamer unstageFile file repo = do p <- toTopFilePath file repo - return $ pureStreamer $ "0 " ++ show nullSha ++ "\t" ++ indexPath p + return $ pureStreamer $ "0 " ++ fromRef nullSha ++ "\t" ++ indexPath p {- A streamer that adds a symlink to the index. -} stageSymlink :: FilePath -> Sha -> Repo -> IO Streamer |