2023-03-29 16:51:04 +03:00
|
|
|
module Commands.Format where
|
|
|
|
|
|
|
|
import Commands.Base
|
|
|
|
import Commands.Format.Options
|
2023-04-27 18:33:08 +03:00
|
|
|
import Data.Text qualified as Text
|
2023-03-29 16:51:04 +03:00
|
|
|
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
|
2023-04-27 18:33:08 +03:00
|
|
|
| TargetStdin
|
2023-06-07 14:53:10 +03:00
|
|
|
deriving stock (Eq)
|
2023-03-29 16:51:04 +03:00
|
|
|
|
|
|
|
runCommand :: forall r. Members '[Embed IO, App, Resource, Files] r => FormatOptions -> Sem r ()
|
|
|
|
runCommand opts = do
|
2023-04-27 18:33:08 +03:00
|
|
|
globalOpts <- askGlobalOptions
|
|
|
|
let isStdin = globalOpts ^. globalStdin
|
|
|
|
f <- mapM filePathToAbs (opts ^. formatInput)
|
|
|
|
|
2023-03-29 16:51:04 +03:00
|
|
|
let target = case f of
|
2023-04-27 18:33:08 +03:00
|
|
|
Just Left {} -> TargetFile
|
|
|
|
Just Right {} -> TargetDir
|
|
|
|
Nothing -> TargetStdin
|
2023-03-29 16:51:04 +03:00
|
|
|
runOutputSem (renderFormattedOutput target opts) $ runScopeFileApp $ do
|
|
|
|
res <- case f of
|
2023-04-27 18:33:08 +03:00
|
|
|
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
|
2023-06-07 14:53:10 +03:00
|
|
|
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 ()
|
2023-03-29 16:51:04 +03:00
|
|
|
|
|
|
|
renderModeFromOptions :: FormatTarget -> FormatOptions -> FormattedFileInfo -> FormatRenderMode
|
|
|
|
renderModeFromOptions target opts formattedInfo
|
|
|
|
| opts ^. formatInPlace = EditInPlace formattedInfo
|
|
|
|
| opts ^. formatCheck = NoEdit Silent
|
|
|
|
| otherwise = case target of
|
|
|
|
TargetFile -> NoEdit (ReformattedFile (formattedInfo ^. formattedFileInfoContentsAnsi))
|
|
|
|
TargetDir -> NoEdit (InputPath (formattedInfo ^. formattedFileInfoPath))
|
2023-04-27 18:33:08 +03:00
|
|
|
TargetStdin -> NoEdit (ReformattedFile (formattedInfo ^. formattedFileInfoContentsAnsi))
|
2023-03-29 16:51:04 +03:00
|
|
|
|
|
|
|
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
|
2023-05-31 10:53:08 +03:00
|
|
|
EditInPlace i@FormattedFileInfo {..} ->
|
2023-03-29 16:51:04 +03:00
|
|
|
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
|
2023-04-19 17:56:48 +03:00
|
|
|
let appFile =
|
|
|
|
AppPath
|
|
|
|
{ _pathPath = mkPrepath (toFilePath p),
|
|
|
|
_pathIsInput = False
|
|
|
|
}
|
2023-03-29 16:51:04 +03:00
|
|
|
runPipeline appFile upToScoping
|
2023-05-31 10:53:08 +03:00
|
|
|
ScopeStdin -> runPipelineNoFile upToScoping
|