use openTempFile from file-io
And follow-on changes. Note that relatedTemplate was changed to operate on a RawFilePath, and so when it counts the length, it is now the number of bytes, not the number of code points. This will just make it truncate shorter strings in some cases, the truncation is still unicode aware. When not building with the OsPath flag, toOsPath . fromRawFilePath and fromRawFilePath . fromOsPath do extra conversions back and forth between String and ByteString. That overhead could be avoided, but that's the non-optimised build mode, so didn't bother. Sponsored-by: unqueued
This commit is contained in:
parent
1faa3af9cd
commit
793ddecd4b
46 changed files with 235 additions and 178 deletions
|
@ -6,6 +6,7 @@
|
|||
-}
|
||||
|
||||
{-# LANGUAGE CPP #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
|
||||
module Git.HashObject where
|
||||
|
||||
|
@ -82,10 +83,10 @@ instance HashableBlob Builder where
|
|||
{- Injects a blob into git. Unfortunately, the current git-hash-object
|
||||
- interface does not allow batch hashing without using temp files. -}
|
||||
hashBlob :: HashableBlob b => HashObjectHandle -> b -> IO Sha
|
||||
hashBlob h b = withTmpFile "hash" $ \tmp tmph -> do
|
||||
hashBlob h b = withTmpFile (toOsPath "hash") $ \tmp tmph -> do
|
||||
hashableBlobToHandle tmph b
|
||||
hClose tmph
|
||||
hashFile h (toRawFilePath tmp)
|
||||
hashFile h (fromOsPath tmp)
|
||||
|
||||
{- Injects some content into git, returning its Sha.
|
||||
-
|
||||
|
|
32
Git/Hook.hs
32
Git/Hook.hs
|
@ -6,6 +6,7 @@
|
|||
-}
|
||||
|
||||
{-# LANGUAGE CPP #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
|
||||
module Git.Hook where
|
||||
|
||||
|
@ -14,15 +15,16 @@ import Git
|
|||
import Utility.Tmp
|
||||
import Utility.Shell
|
||||
import Utility.FileMode
|
||||
import qualified Utility.FileIO as F
|
||||
#ifndef mingw32_HOST_OS
|
||||
import qualified Utility.RawFilePath as R
|
||||
import System.PosixCompat.Files (fileMode)
|
||||
#endif
|
||||
|
||||
import qualified Data.ByteString as B
|
||||
import qualified System.FilePath.ByteString as P
|
||||
|
||||
data Hook = Hook
|
||||
{ hookName :: FilePath
|
||||
{ hookName :: RawFilePath
|
||||
, hookScript :: String
|
||||
, hookOldScripts :: [String]
|
||||
}
|
||||
|
@ -31,8 +33,8 @@ data Hook = Hook
|
|||
instance Eq Hook where
|
||||
a == b = hookName a == hookName b
|
||||
|
||||
hookFile :: Hook -> Repo -> FilePath
|
||||
hookFile h r = fromRawFilePath (localGitDir r) </> "hooks" </> hookName h
|
||||
hookFile :: Hook -> Repo -> RawFilePath
|
||||
hookFile h r = localGitDir r P.</> "hooks" P.</> hookName h
|
||||
|
||||
{- Writes a hook. Returns False if the hook already exists with a different
|
||||
- content. Upgrades old scripts.
|
||||
|
@ -48,7 +50,7 @@ hookFile h r = fromRawFilePath (localGitDir r) </> "hooks" </> hookName h
|
|||
- is run with a bundled bash, so should start with #!/bin/sh
|
||||
-}
|
||||
hookWrite :: Hook -> Repo -> IO Bool
|
||||
hookWrite h r = ifM (doesFileExist f)
|
||||
hookWrite h r = ifM (doesFileExist (fromRawFilePath f))
|
||||
( expectedContent h r >>= \case
|
||||
UnexpectedContent -> return False
|
||||
ExpectedContent -> return True
|
||||
|
@ -58,15 +60,13 @@ hookWrite h r = ifM (doesFileExist f)
|
|||
where
|
||||
f = hookFile h r
|
||||
go = do
|
||||
-- On Windows, using B.writeFile here avoids
|
||||
-- the newline translation done by writeFile.
|
||||
-- On Windows, using a ByteString as the file content
|
||||
-- avoids the newline translation done by writeFile.
|
||||
-- Hook scripts on Windows could use CRLF endings, but
|
||||
-- they typically use unix newlines, which does work there
|
||||
-- and makes the repository more portable.
|
||||
viaTmp B.writeFile f (encodeBS (hookScript h))
|
||||
void $ tryIO $ modifyFileMode
|
||||
(toRawFilePath f)
|
||||
(addModes executeModes)
|
||||
viaTmp F.writeFile' (toOsPath f) (encodeBS (hookScript h))
|
||||
void $ tryIO $ modifyFileMode f (addModes executeModes)
|
||||
return True
|
||||
|
||||
{- Removes a hook. Returns False if the hook contained something else, and
|
||||
|
@ -81,7 +81,7 @@ hookUnWrite h r = ifM (doesFileExist f)
|
|||
, return True
|
||||
)
|
||||
where
|
||||
f = hookFile h r
|
||||
f = fromRawFilePath $ hookFile h r
|
||||
|
||||
data ExpectedContent = UnexpectedContent | ExpectedContent | OldExpectedContent
|
||||
|
||||
|
@ -91,7 +91,7 @@ expectedContent h r = do
|
|||
-- and so a hook file that has CRLF will be treated the same as one
|
||||
-- that has LF. That is intentional, since users may have a reason
|
||||
-- to prefer one or the other.
|
||||
content <- readFile $ hookFile h r
|
||||
content <- readFile $ fromRawFilePath $ hookFile h r
|
||||
return $ if content == hookScript h
|
||||
then ExpectedContent
|
||||
else if any (content ==) (hookOldScripts h)
|
||||
|
@ -103,13 +103,13 @@ hookExists h r = do
|
|||
let f = hookFile h r
|
||||
catchBoolIO $
|
||||
#ifndef mingw32_HOST_OS
|
||||
isExecutable . fileMode <$> R.getFileStatus (toRawFilePath f)
|
||||
isExecutable . fileMode <$> R.getFileStatus f
|
||||
#else
|
||||
doesFileExist f
|
||||
doesFileExist (fromRawFilePath f)
|
||||
#endif
|
||||
|
||||
runHook :: (FilePath -> [CommandParam] -> IO a) -> Hook -> [CommandParam] -> Repo -> IO a
|
||||
runHook runner h ps r = do
|
||||
let f = hookFile h r
|
||||
let f = fromRawFilePath $ hookFile h r
|
||||
(c, cps) <- findShellCommand f
|
||||
runner c (cps ++ ps)
|
||||
|
|
|
@ -78,7 +78,7 @@ explodePacks :: Repo -> IO Bool
|
|||
explodePacks r = go =<< listPackFiles r
|
||||
where
|
||||
go [] = return False
|
||||
go packs = withTmpDir "packs" $ \tmpdir -> do
|
||||
go packs = withTmpDir (toOsPath "packs") $ \tmpdir -> do
|
||||
r' <- addGitEnv r "GIT_OBJECT_DIRECTORY" tmpdir
|
||||
putStrLn "Unpacking all pack files."
|
||||
forM_ packs $ \packfile -> do
|
||||
|
@ -112,7 +112,7 @@ explodePacks r = go =<< listPackFiles r
|
|||
retrieveMissingObjects :: FsckResults -> Maybe FilePath -> Repo -> IO FsckResults
|
||||
retrieveMissingObjects missing referencerepo r
|
||||
| not (foundBroken missing) = return missing
|
||||
| otherwise = withTmpDir "tmprepo" $ \tmpdir -> do
|
||||
| otherwise = withTmpDir (toOsPath "tmprepo") $ \tmpdir -> do
|
||||
unlessM (boolSystem "git" [Param "init", File tmpdir]) $
|
||||
giveup $ "failed to create temp repository in " ++ tmpdir
|
||||
tmpr <- Config.read =<< Construct.fromPath (toRawFilePath tmpdir)
|
||||
|
|
Loading…
Add table
Add a link
Reference in a new issue