1
1
{-# LANGUAGE DeriveDataTypeable #-}
2
+ {-# LANGUAGE LambdaCase #-}
2
3
{-# LANGUAGE MultiWayIf #-}
3
4
{-# LANGUAGE NamedFieldPuns #-}
4
5
{-# LANGUAGE TemplateHaskell #-}
@@ -14,7 +15,7 @@ import Data.FileEmbed
14
15
import Data.List (isSuffixOf )
15
16
import Data.Maybe (fromMaybe )
16
17
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 )
18
19
import Data.Version (showVersion )
19
20
import GHC.IO.Encoding (utf8 )
20
21
import qualified Nixfmt
@@ -31,13 +32,15 @@ import System.Console.CmdArgs (
31
32
(&=) ,
32
33
)
33
34
import System.Directory (doesDirectoryExist , listDirectory )
35
+ import System.Environment (getEnv )
34
36
import System.Exit (ExitCode (.. ), exitFailure , exitSuccess )
35
37
import System.FilePath ((</>) )
36
- import System.IO (hPutStrLn , hSetEncoding , stderr )
38
+ import System.IO (Handle , hGetContents , hPutStrLn , hSetEncoding , stderr )
37
39
import System.IO.Atomic (withOutputFile )
38
40
import System.IO.Utf8 (readFileUtf8 , withUtf8StdHandles )
39
41
import System.Posix.Process (exitImmediately )
40
42
import System.Posix.Signals (Handler (.. ), installHandler , keyboardSignal )
43
+ import System.Process (CreateProcess (std_err , std_out ), StdStream (CreatePipe ), createProcess , proc , waitForProcess )
41
44
42
45
type Result = Either String ()
43
46
@@ -47,6 +50,7 @@ data Nixfmt = Nixfmt
47
50
{ files :: [FilePath ],
48
51
width :: Width ,
49
52
check :: Bool ,
53
+ mergetool :: Bool ,
50
54
quiet :: Bool ,
51
55
strict :: Bool ,
52
56
verify :: Bool ,
@@ -70,6 +74,7 @@ options =
70
74
defaultWidth
71
75
&= help (addDefaultHint defaultWidth " Maximum width in characters" ),
72
76
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" ,
73
78
quiet = False &= help " Do not report errors" ,
74
79
strict = False &= help " Enable a stricter formatting mode that isn't influenced as much by how the input is formatted" ,
75
80
verify =
@@ -156,6 +161,14 @@ fileTarget path = Target (readFileUtf8 path) path atomicWriteFile
156
161
-- Don't do anything if the file is already formatted
157
162
atomicWriteFile False _ = mempty
158
163
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
+
159
172
checkFileTarget :: FilePath -> Target
160
173
checkFileTarget path = Target (readFileUtf8 path) path (const $ const $ pure () )
161
174
@@ -183,8 +196,41 @@ toWriteError :: Nixfmt -> String -> IO ()
183
196
toWriteError Nixfmt {quiet = False } = hPutStrLn stderr
184
197
toWriteError Nixfmt {quiet = True } = const $ return ()
185
198
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
+
186
232
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
188
234
189
235
writeErrorBundle :: (String -> IO () ) -> Result -> IO Result
190
236
writeErrorBundle doWrite result = do
0 commit comments