1
1
mirror of https://github.com/anoma/juvix.git synced 2024-09-21 05:28:17 +03:00
juvix/app/Commands/Format.hs
Paul Cadman 7840f9fa79
Always print source of formatted file unless --check is specified (#2205)
This PR was already merged in https://github.com/anoma/juvix/pull/2173,
but main was subsequently forced pushed as part of the 0.4.0 release and
these changes were erased by mistake.

This PR changes the behaviour of the formatter when run on files that
are already formatted. Previously the source of a file that was already
formatted was not output by the formatter.

After this PR, the formatter always outputs the contents of a formatted
file (when used on a single file, and if the --check option is not
specified).

If the `format: false` pragma is set then the source is echoed verbatim,
without highlighting (because it's not possible to get the highlighting
without the formatting).

This probably helps implementing the formatter in the vscode extension,
see https://github.com/anoma/vscode-juvix/issues/98
2023-06-19 15:14:59 +01:00

100 lines
3.6 KiB
Haskell

module Commands.Format where
import Commands.Base
import Commands.Format.Options
import Data.Text qualified as Text
import Juvix.Formatter
import Juvix.Prelude.Pretty
data FormatNoEditRenderMode
= ReformattedFile (NonEmpty AnsiText)
| InputPath (Path Abs File)
| Silent
data FormatRenderMode
= EditInPlace FormattedFileInfo
| NoEdit FormatNoEditRenderMode
data FormatTarget
= TargetFile
| TargetDir
| TargetStdin
deriving stock (Eq)
runCommand :: forall r. Members '[Embed IO, App, Resource, Files] r => FormatOptions -> Sem r ()
runCommand opts = do
globalOpts <- askGlobalOptions
let isStdin = globalOpts ^. globalStdin
f <- mapM filePathToAbs (opts ^. formatInput)
let target = case f of
Just Left {} -> TargetFile
Just Right {} -> TargetDir
Nothing -> TargetStdin
runOutputSem (renderFormattedOutput target opts) $ runScopeFileApp $ do
res <- case f of
Just (Left p) -> format p
Just (Right p) -> formatProject p
Nothing ->
if
| isStdin -> formatStdin
| otherwise -> do
printFailureExit $
Text.unlines
[ "juvix format error: either 'JUVIX_FILE_OR_PROJECT' or '--stdin' option must be specified",
"Use the --help option to display more usage information."
]
return FormatResultFail
let exitFail :: IO a
exitFail = exitWith (ExitFailure 1)
case res of
FormatResultFail -> embed exitFail
FormatResultNotFormatted ->
{- use exit code 1 for
* unformatted files when using --check
* when running the formatter on a Juvix project
-}
when (opts ^. formatCheck || target == TargetDir) (embed exitFail)
FormatResultOK -> pure ()
renderModeFromOptions :: FormatTarget -> FormatOptions -> FormattedFileInfo -> FormatRenderMode
renderModeFromOptions target opts formattedInfo
| opts ^. formatInPlace = whenContentsModified (EditInPlace formattedInfo)
| opts ^. formatCheck = NoEdit Silent
| otherwise = case target of
TargetFile -> NoEdit (ReformattedFile (formattedInfo ^. formattedFileInfoContentsAnsi))
TargetDir -> whenContentsModified (NoEdit (InputPath (formattedInfo ^. formattedFileInfoPath)))
TargetStdin -> NoEdit (ReformattedFile (formattedInfo ^. formattedFileInfoContentsAnsi))
where
whenContentsModified :: FormatRenderMode -> FormatRenderMode
whenContentsModified res
| formattedInfo ^. formattedFileInfoContentsModified = res
| otherwise = NoEdit Silent
renderFormattedOutput :: forall r. Members '[Embed IO, App, Resource, Files] r => FormatTarget -> FormatOptions -> FormattedFileInfo -> Sem r ()
renderFormattedOutput target opts fInfo = do
let renderMode = renderModeFromOptions target opts fInfo
outputResult renderMode
where
outputResult :: FormatRenderMode -> Sem r ()
outputResult = \case
EditInPlace i@FormattedFileInfo {..} ->
runTempFileIO $
restoreFileOnError _formattedFileInfoPath $
writeFile' _formattedFileInfoPath (i ^. formattedFileInfoContentsText)
NoEdit m -> case m of
ReformattedFile ts -> forM_ ts renderStdOut
InputPath p -> say (pack (toFilePath p))
Silent -> return ()
runScopeFileApp :: Member App r => Sem (ScopeEff ': r) a -> Sem r a
runScopeFileApp = interpret $ \case
ScopeFile p -> do
let appFile =
AppPath
{ _pathPath = mkPrepath (toFilePath p),
_pathIsInput = False
}
runPipeline appFile upToScoping
ScopeStdin -> runPipelineNoFile upToScoping