summaryrefslogtreecommitdiff
path: root/Git/LsTree.hs
diff options
context:
space:
mode:
Diffstat (limited to 'Git/LsTree.hs')
-rw-r--r--Git/LsTree.hs33
1 files changed, 21 insertions, 12 deletions
diff --git a/Git/LsTree.hs b/Git/LsTree.hs
index 1ed6247..2060fa7 100644
--- a/Git/LsTree.hs
+++ b/Git/LsTree.hs
@@ -1,16 +1,19 @@
{- git ls-tree interface
-
- - Copyright 2011 Joey Hess <id@joeyh.name>
+ - Copyright 2011-2016 Joey Hess <id@joeyh.name>
-
- Licensed under the GNU GPL version 3 or higher.
-}
+{-# LANGUAGE BangPatterns #-}
+
module Git.LsTree (
TreeItem(..),
lsTree,
+ lsTree',
lsTreeParams,
lsTreeFiles,
- parseLsTree
+ parseLsTree,
) where
import Common
@@ -26,15 +29,19 @@ import System.Posix.Types
data TreeItem = TreeItem
{ mode :: FileMode
, typeobj :: String
- , sha :: String
+ , sha :: Ref
, file :: TopFilePath
} deriving Show
{- Lists the complete contents of a tree, recursing into sub-trees,
- with lazy output. -}
-lsTree :: Ref -> Repo -> IO [TreeItem]
-lsTree t repo = map parseLsTree
- <$> pipeNullSplitZombie (lsTreeParams t []) repo
+lsTree :: Ref -> Repo -> IO ([TreeItem], IO Bool)
+lsTree = lsTree' []
+
+lsTree' :: [CommandParam] -> Ref -> Repo -> IO ([TreeItem], IO Bool)
+lsTree' ps t repo = do
+ (l, cleanup) <- pipeNullSplit (lsTreeParams t ps) repo
+ return (map parseLsTree l, cleanup)
lsTreeParams :: Ref -> [CommandParam] -> [CommandParam]
lsTreeParams r ps =
@@ -63,16 +70,18 @@ lsTreeFiles t fs repo = map parseLsTree <$> pipeNullSplitStrict ps repo
- (The --long format is not currently supported.) -}
parseLsTree :: String -> TreeItem
parseLsTree l = TreeItem
- { mode = fst $ Prelude.head $ readOct m
+ { mode = smode
, typeobj = t
- , sha = s
- , file = asTopFilePath $ Git.Filename.decode f
+ , sha = Ref s
+ , file = sfile
}
where
-- l = <mode> SP <type> SP <sha> TAB <file>
-- All fields are fixed, so we can pull them out of
-- specific positions in the line.
(m, past_m) = splitAt 7 l
- (t, past_t) = splitAt 4 past_m
- (s, past_s) = splitAt shaSize $ Prelude.tail past_t
- f = Prelude.tail past_s
+ (!t, past_t) = splitAt 4 past_m
+ (!s, past_s) = splitAt shaSize $ Prelude.tail past_t
+ !f = Prelude.tail past_s
+ !smode = fst $ Prelude.head $ readOct m
+ !sfile = asTopFilePath $ Git.Filename.decode f