use Common in a few more modules

This commit is contained in:
Joey Hess 2011-12-20 14:37:53 -04:00
parent 6897460d35
commit ee3b5b2a42
8 changed files with 30 additions and 31 deletions

View file

@ -29,7 +29,7 @@ import Common
import qualified Git
import qualified Git.Config
import Git.CatFile
import Git.Queue
import qualified Git.Queue
import Types.Backend
import qualified Types.Remote
import Types.Crypto
@ -57,7 +57,7 @@ data AnnexState = AnnexState
{ repo :: Git.Repo
, backends :: [Backend Annex]
, remotes :: [Types.Remote.Remote Annex]
, repoqueue :: Queue
, repoqueue :: Git.Queue.Queue
, output :: OutputType
, force :: Bool
, fast :: Bool
@ -80,7 +80,7 @@ newState gitrepo = AnnexState
{ repo = gitrepo
, backends = []
, remotes = []
, repoqueue = Git.Queue.empty
, repoqueue = Git.Queue.new
, output = NormalOutput
, force = False
, fast = False

View file

@ -7,11 +7,9 @@
module Annex.Ssh where
import Control.Monad.State (liftIO)
import Common
import qualified Git
import qualified Git.Url
import Utility.SafeCommand
import Types
import Config
import Annex.UUID

View file

@ -19,10 +19,10 @@ import System.IO
import qualified Data.ByteString.Char8 as S
import qualified Data.ByteString.Lazy.Char8 as L
import Common
import Git
import Git.Sha
import Git.Command
import Utility.SafeCommand
type CatFileHandle = (PipeHandle, Handle, Handle)
@ -53,21 +53,21 @@ catObject (_, from, to) object = do
[sha, objtype, size]
| length sha == shaSize &&
validobjtype objtype -> handle size
| otherwise -> empty
| otherwise -> dne
_
| header == show object ++ " missing" -> empty
| header == show object ++ " missing" -> dne
| otherwise -> error $ "unknown response from git cat-file " ++ header
where
handle size = case reads size of
[(bytes, "")] -> readcontent bytes
_ -> empty
_ -> dne
readcontent bytes = do
content <- S.hGet from bytes
c <- hGetChar from
when (c /= '\n') $
error "missing newline from git cat-file"
return $ L.fromChunks [content]
empty = return L.empty
dne = return L.empty
validobjtype t
| t == "blob" = True
| t == "commit" = True

View file

@ -13,22 +13,21 @@ import Data.Char
import Data.Word (Word8)
import Text.Printf
import Common
decode :: String -> FilePath
decode [] = []
decode f@(c:s)
-- encoded strings will be inside double quotes
| c == '"' = unescape ("", middle)
| c == '"' && end s == ['"'] = unescape ("", beginning s)
| otherwise = f
where
e = '\\'
middle = init s
unescape (b, []) = b
-- look for escapes starting with '\'
unescape (b, v) = b ++ beginning ++ unescape (handle rest)
unescape (b, v) = b ++ fst pair ++ unescape (handle $ snd pair)
where
pair = span (/= e) v
beginning = fst pair
rest = snd pair
isescape x = x == e
-- \NNN is an octal encoded character
handle (x:n1:n2:n3:rest)
@ -38,7 +37,7 @@ decode f@(c:s)
isOctDigit n2 &&
isOctDigit n3
fromoctal = [chr $ readoctal [n1, n2, n3]]
readoctal o = read $ "0o" ++ o :: Int
readoctal o = Prelude.read $ "0o" ++ o :: Int
-- \C is used for a few special characters
handle (x:nc:rest)
| isescape x = ([echar nc], rest)

View file

@ -9,6 +9,8 @@ module Git.Index where
import System.Posix.Env (setEnv, unsetEnv, getEnv)
import Common
{- Forces git to use the specified index file.
-
- Returns an action that will reset back to the default

View file

@ -15,9 +15,9 @@ module Git.LsFiles (
typeChangedStaged,
) where
import Common
import Git
import Git.Command
import Utility.SafeCommand
{- Scans for files that are checked into git at the specified locations. -}
inRepo :: [FilePath] -> Repo -> IO [FilePath]
@ -43,10 +43,10 @@ stagedNotDeleted :: [FilePath] -> Repo -> IO [FilePath]
stagedNotDeleted = staged' [Param "--diff-filter=ACMRT"]
staged' :: [CommandParam] -> [FilePath] -> Repo -> IO [FilePath]
staged' middle l = pipeNullSplit $ start ++ middle ++ end
staged' ps l = pipeNullSplit $ prefix ++ ps ++ suffix
where
start = [Params "diff --cached --name-only -z"]
end = Param "--" : map File l
prefix = [Params "diff --cached --name-only -z"]
suffix = Param "--" : map File l
{- Returns a list of files that have unstaged changes. -}
changedUnstaged :: [FilePath] -> Repo -> IO [FilePath]
@ -65,7 +65,7 @@ typeChanged :: [FilePath] -> Repo -> IO [FilePath]
typeChanged = typeChanged' []
typeChanged' :: [CommandParam] -> [FilePath] -> Repo -> IO [FilePath]
typeChanged' middle l = pipeNullSplit $ start ++ middle ++ end
typeChanged' ps l = pipeNullSplit $ prefix ++ ps ++ suffix
where
start = [Params "diff --name-only --diff-filter=T -z"]
end = Param "--" : map File l
prefix = [Params "diff --name-only --diff-filter=T -z"]
suffix = Param "--" : map File l

View file

@ -16,10 +16,10 @@ import Control.Applicative
import System.Posix.Types
import qualified Data.ByteString.Lazy.Char8 as L
import Common
import Git
import Git.Command
import qualified Git.Filename
import Utility.SafeCommand
data TreeItem = TreeItem
{ mode :: FileMode
@ -37,7 +37,7 @@ lsTree t repo = map parseLsTree <$>
- (The --long format is not currently supported.) -}
parseLsTree :: L.ByteString -> TreeItem
parseLsTree l = TreeItem
{ mode = fst $ head $ readOct $ L.unpack m
{ mode = fst $ Prelude.head $ readOct $ L.unpack m
, typeobj = L.unpack t
, sha = L.unpack s
, file = Git.Filename.decode $ L.unpack f

View file

@ -7,7 +7,7 @@
module Git.Queue (
Queue,
empty,
new,
add,
size,
full,
@ -18,9 +18,9 @@ import qualified Data.Map as M
import System.IO
import System.Cmd.Utils
import Data.String.Utils
import Control.Monad (forM_)
import Utility.SafeCommand
import Common
import Git
import Git.Command
@ -50,8 +50,8 @@ maxSize :: Int
maxSize = 10240
{- Constructor for empty queue. -}
empty :: Queue
empty = Queue 0 M.empty
new :: Queue
new = Queue 0 M.empty
{- Adds an action to a queue. -}
add :: Queue -> String -> [CommandParam] -> [FilePath] -> Queue
@ -76,7 +76,7 @@ full (Queue n _) = n > maxSize
flush :: Queue -> Repo -> IO Queue
flush (Queue _ m) repo = do
forM_ (M.toList m) $ uncurry $ runAction repo
return empty
return new
{- Runs an Action on a list of files in a git repository.
-