Skip to content

Commit 6a2c935

Browse files
committed
Implement --mergetool mode
Inspired by oxij's #277, but implemented in Haskell, therefore faster (less process spawning) and trivially integrated into the build and distribution.
1 parent e825e95 commit 6a2c935

File tree

2 files changed

+50
-3
lines changed

2 files changed

+50
-3
lines changed

main/Main.hs

Lines changed: 49 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,5 @@
11
{-# LANGUAGE DeriveDataTypeable #-}
2+
{-# LANGUAGE LambdaCase #-}
23
{-# LANGUAGE MultiWayIf #-}
34
{-# LANGUAGE NamedFieldPuns #-}
45
{-# LANGUAGE TemplateHaskell #-}
@@ -14,7 +15,7 @@ import Data.FileEmbed
1415
import Data.List (isSuffixOf)
1516
import Data.Maybe (fromMaybe)
1617
import Data.Text (Text)
17-
import qualified Data.Text.IO as TextIO (getContents, hPutStr, putStr)
18+
import qualified Data.Text.IO as TextIO (getContents, hGetContents, hPutStr, putStr)
1819
import Data.Version (showVersion)
1920
import GHC.IO.Encoding (utf8)
2021
import qualified Nixfmt
@@ -31,13 +32,15 @@ import System.Console.CmdArgs (
3132
(&=),
3233
)
3334
import System.Directory (doesDirectoryExist, listDirectory)
35+
import System.Environment (getEnv)
3436
import System.Exit (ExitCode (..), exitFailure, exitSuccess)
3537
import System.FilePath ((</>))
36-
import System.IO (hPutStrLn, hSetEncoding, stderr)
38+
import System.IO (Handle, hGetContents, hPutStrLn, hSetEncoding, stderr)
3739
import System.IO.Atomic (withOutputFile)
3840
import System.IO.Utf8 (readFileUtf8, withUtf8StdHandles)
3941
import System.Posix.Process (exitImmediately)
4042
import System.Posix.Signals (Handler (..), installHandler, keyboardSignal)
43+
import System.Process (CreateProcess (std_err, std_out), StdStream (CreatePipe), createProcess, proc, waitForProcess)
4144

4245
type Result = Either String ()
4346

@@ -47,6 +50,7 @@ data Nixfmt = Nixfmt
4750
{ files :: [FilePath],
4851
width :: Width,
4952
check :: Bool,
53+
mergetool :: Bool,
5054
quiet :: Bool,
5155
strict :: Bool,
5256
verify :: Bool,
@@ -70,6 +74,7 @@ options =
7074
defaultWidth
7175
&= help (addDefaultHint defaultWidth "Maximum width in characters"),
7276
check = False &= help "Check whether files are formatted without modifying them",
77+
mergetool = False &= help "Whether to run in git mergetool mode, see TODO for more info",
7378
quiet = False &= help "Do not report errors",
7479
strict = False &= help "Enable a stricter formatting mode that isn't influenced as much by how the input is formatted",
7580
verify =
@@ -156,6 +161,14 @@ fileTarget path = Target (readFileUtf8 path) path atomicWriteFile
156161
-- Don't do anything if the file is already formatted
157162
atomicWriteFile False _ = mempty
158163

164+
-- | Writes to a (potentially non-existent) file path, but reads from a potentially separate handle
165+
copyTarget :: Handle -> FilePath -> Target
166+
copyTarget from to = Target (TextIO.hGetContents from) to atomicWriteFile
167+
where
168+
atomicWriteFile _ t = withOutputFile to $ \h -> do
169+
hSetEncoding h utf8
170+
TextIO.hPutStr h t
171+
159172
checkFileTarget :: FilePath -> Target
160173
checkFileTarget path = Target (readFileUtf8 path) path (const $ const $ pure ())
161174

@@ -183,8 +196,41 @@ toWriteError :: Nixfmt -> String -> IO ()
183196
toWriteError Nixfmt{quiet = False} = hPutStrLn stderr
184197
toWriteError Nixfmt{quiet = True} = const $ return ()
185198

199+
mergeToolJob :: Nixfmt -> IO Result
200+
mergeToolJob Nixfmt{mergetool = False} = return $ Right ()
201+
mergeToolJob opts = do
202+
let formatter = toFormatter opts
203+
oneByOne [] = return $ Right ()
204+
oneByOne (y : ys) =
205+
y >>= \case
206+
Left err -> return $ Left err
207+
Right () -> oneByOne ys
208+
209+
base <- getEnv "BASE"
210+
local <- getEnv "LOCAL"
211+
remote <- getEnv "REMOTE"
212+
merged <- getEnv "MERGED"
213+
214+
if not (".nix" `isSuffixOf` merged)
215+
then return $ Left ("Skipping non-Nix file " ++ merged)
216+
else do
217+
inputResult <- oneByOne $ map (formatTarget formatter . fileTarget) [base, local, remote]
218+
case inputResult of
219+
Left err -> return $ Left (err <> "pre-formatting with `nixfmt` failed\n")
220+
Right () -> do
221+
(_, Just out, Just err, process) <-
222+
createProcess
223+
(proc "git" ["merge-file", "--stdout", base, local, remote])
224+
{ std_out = CreatePipe,
225+
std_err = CreatePipe
226+
}
227+
228+
waitForProcess process >>= \case
229+
ExitFailure _ -> Left . (<> "`git merge-file` failed\n") <$> hGetContents err
230+
ExitSuccess -> formatTarget formatter (copyTarget out merged)
231+
186232
toJobs :: Nixfmt -> IO [IO Result]
187-
toJobs opts = map (toOperation opts $ toFormatter opts) <$> toTargets opts
233+
toJobs opts = (mergeToolJob opts :) . map (toOperation opts $ toFormatter opts) <$> toTargets opts
188234

189235
writeErrorBundle :: (String -> IO ()) -> Result -> IO Result
190236
writeErrorBundle doWrite result = do

nixfmt.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -38,6 +38,7 @@ executable nixfmt
3838
, unix >= 2.7.2 && < 2.9
3939
, text >= 1.2.3 && < 2.2
4040
, transformers
41+
, process
4142

4243
-- for System.IO.Atomic
4344
, directory >= 1.3.3 && < 1.4

0 commit comments

Comments
 (0)