1
1
{-# LANGUAGE DeriveDataTypeable #-}
2
+ {-# LANGUAGE LambdaCase #-}
2
3
{-# LANGUAGE MultiWayIf #-}
3
4
{-# LANGUAGE NamedFieldPuns #-}
4
5
{-# LANGUAGE TemplateHaskell #-}
5
6
6
7
module Main where
7
8
8
- import Control.Monad (unless )
9
+ import Control.Monad (forM , unless )
9
10
import Control.Monad.Trans.Class (lift )
11
+ import Control.Monad.Trans.Except (ExceptT (ExceptT ), runExceptT , throwE )
10
12
import Control.Monad.Trans.State.Strict (StateT , evalStateT , get , put )
13
+ import Data.Bifunctor (first )
11
14
import Data.ByteString.Char8 (unpack )
12
15
import Data.Either (lefts )
13
16
import Data.FileEmbed
14
- import Data.List (isSuffixOf )
17
+ import Data.List (intersperse , isSuffixOf )
15
18
import Data.Maybe (fromMaybe )
16
19
import Data.Text (Text )
17
- import qualified Data.Text.IO as TextIO (getContents , hPutStr , putStr )
20
+ import qualified Data.Text.IO as TextIO (getContents , hGetContents , hPutStr , putStr )
18
21
import Data.Version (showVersion )
19
22
import GHC.IO.Encoding (utf8 )
20
23
import qualified Nixfmt
@@ -33,11 +36,12 @@ import System.Console.CmdArgs (
33
36
import System.Directory (doesDirectoryExist , listDirectory )
34
37
import System.Exit (ExitCode (.. ), exitFailure , exitSuccess )
35
38
import System.FilePath ((</>) )
36
- import System.IO (hPutStrLn , hSetEncoding , stderr )
39
+ import System.IO (Handle , hGetContents , hPutStrLn , hSetEncoding , stderr )
37
40
import System.IO.Atomic (withOutputFile )
38
41
import System.IO.Utf8 (readFileUtf8 , withUtf8StdHandles )
39
42
import System.Posix.Process (exitImmediately )
40
43
import System.Posix.Signals (Handler (.. ), installHandler , keyboardSignal )
44
+ import System.Process (CreateProcess (std_out ), StdStream (CreatePipe ), createProcess , proc , waitForProcess )
41
45
42
46
type Result = Either String ()
43
47
@@ -47,6 +51,7 @@ data Nixfmt = Nixfmt
47
51
{ files :: [FilePath ],
48
52
width :: Width ,
49
53
check :: Bool ,
54
+ mergetool :: Bool ,
50
55
quiet :: Bool ,
51
56
strict :: Bool ,
52
57
verify :: Bool ,
@@ -70,6 +75,7 @@ options =
70
75
defaultWidth
71
76
&= help (addDefaultHint defaultWidth " Maximum width in characters" ),
72
77
check = False &= help " Check whether files are formatted without modifying them" ,
78
+ mergetool = False &= help " Whether to run in git mergetool mode, see https://github.com/NixOS/nixfmt?tab=readme-ov-file#git-mergetool for more info" ,
73
79
quiet = False &= help " Do not report errors" ,
74
80
strict = False &= help " Enable a stricter formatting mode that isn't influenced as much by how the input is formatted" ,
75
81
verify =
@@ -156,6 +162,14 @@ fileTarget path = Target (readFileUtf8 path) path atomicWriteFile
156
162
-- Don't do anything if the file is already formatted
157
163
atomicWriteFile False _ = mempty
158
164
165
+ -- | Writes to a (potentially non-existent) file path, but reads from a potentially separate handle
166
+ copyTarget :: Handle -> FilePath -> Target
167
+ copyTarget from to = Target (TextIO. hGetContents from) to atomicWriteFile
168
+ where
169
+ atomicWriteFile _ t = withOutputFile to $ \ h -> do
170
+ hSetEncoding h utf8
171
+ TextIO. hPutStr h t
172
+
159
173
checkFileTarget :: FilePath -> Target
160
174
checkFileTarget path = Target (readFileUtf8 path) path (const $ const $ pure () )
161
175
@@ -183,8 +197,54 @@ toWriteError :: Nixfmt -> String -> IO ()
183
197
toWriteError Nixfmt {quiet = False } = hPutStrLn stderr
184
198
toWriteError Nixfmt {quiet = True } = const $ return ()
185
199
200
+ -- | `git mergetool` mode, which rejects all non-\`.nix\` files, while for \`.nix\` files it simply
201
+ -- - Calls `nixfmt` on its first three inputs (the BASE, LOCAL and REMOTE versions to merge)
202
+ -- - Runs `git merge-file` on the same inputs
203
+ -- - Runs `nixfmt` on the result and stores it in the path given in the fourth argument (the MERGED file)
204
+ mergeToolJob :: Nixfmt -> IO Result
205
+ mergeToolJob opts@ Nixfmt {files = [base, local, remote, merged]} = runExceptT $ do
206
+ let formatter = toFormatter opts
207
+ joinResults :: [Result ] -> Result
208
+ joinResults xs = case lefts xs of
209
+ [] -> Right ()
210
+ ls -> Left (mconcat (intersperse " \n " ls))
211
+ inputs =
212
+ [ (" base" , base),
213
+ (" local" , local),
214
+ (" remote" , remote)
215
+ ]
216
+
217
+ unless (" .nix" `isSuffixOf` merged) $
218
+ throwE (" Skipping non-Nix file " ++ merged)
219
+
220
+ ExceptT $
221
+ joinResults
222
+ <$> forM
223
+ inputs
224
+ ( \ (name, path) -> do
225
+ first (<> " pre-formatting the " <> name <> " version failed" )
226
+ <$> formatTarget formatter (fileTarget path)
227
+ )
228
+
229
+ (_, Just out, _, process) <- do
230
+ lift $
231
+ createProcess
232
+ (proc " git" [" merge-file" , " --stdout" , base, local, remote])
233
+ { std_out = CreatePipe
234
+ }
235
+
236
+ lift (waitForProcess process) >>= \ case
237
+ ExitFailure code -> do
238
+ output <- lift $ hGetContents out
239
+ throwE $ output <> " `git merge-file` failed with exit code " <> show code <> " \n "
240
+ ExitSuccess -> return ()
241
+
242
+ ExceptT $ formatTarget formatter (copyTarget out merged)
243
+ mergeToolJob _ = return $ Left " --mergetool mode expects exactly 4 file arguments ($BASE, $LOCAL, $REMOTE, $MERGED)"
244
+
186
245
toJobs :: Nixfmt -> IO [IO Result ]
187
- toJobs opts = map (toOperation opts $ toFormatter opts) <$> toTargets opts
246
+ toJobs opts@ Nixfmt {mergetool = False } = map (toOperation opts $ toFormatter opts) <$> toTargets opts
247
+ toJobs opts@ Nixfmt {mergetool = True } = return [mergeToolJob opts]
188
248
189
249
writeErrorBundle :: (String -> IO () ) -> Result -> IO Result
190
250
writeErrorBundle doWrite result = do
0 commit comments