1
1
mirror of https://github.com/anoma/juvix.git synced 2024-12-11 20:32:07 +03:00
juvix/app/App.hs
Veronika Romashkina 8ab4ccd73b
Make format command's filepath optional (#2028)
# Description

No the filepath in the `juvix forma` command is n=made optional.
However, in that case, the `--stdin` command is required.

### Implementation details

~For now, as a quick solution, I have introduce the "fake" path that is
used for `fomat` command with stdin option.~
I needed to do a couple of big changes:
* `format` command FILE is now optional, howvere, I check that in case
of `Nothing` `--stdin` option should be present, otherwise it will fail
 * `entryPointModulePaths` is now `[]` instead of `NonEmpty`
* `ScopeEff` now has `ScopeStdin` constructor as well, which would take
the input from stdin instead of having path passed around
* `RunPipelineNoFileEither` is added to the `App` with the bunch of
`*Stdin` functions that doesn't require filepath argument to be passed

Fixes #2008

## Type of change

- [x] New feature (non-breaking change which adds functionality)

# Checklist:

- [x] My code follows the style guidelines of this project
- [x] I have made corresponding changes to the documentation
- [x] My changes generate no new warnings
- [x] I have added tests that prove my fix is effective or that my
feature works:
  - [x] smoke tests

---------

Co-authored-by: Paul Cadman <git@paulcadman.dev>
Co-authored-by: janmasrovira <janmasrovira@gmail.com>
2023-04-27 17:33:08 +02:00

162 lines
5.7 KiB
Haskell

module App where
import CommonOptions
import Data.ByteString qualified as ByteString
import GlobalOptions
import Juvix.Compiler.Concrete.Translation.FromParsed.Analysis.PathResolver
import Juvix.Compiler.Pipeline
import Juvix.Data.Error qualified as Error
import Juvix.Prelude.Pretty hiding
( Doc,
)
import System.Console.ANSI qualified as Ansi
data App m a where
ExitMsg :: ExitCode -> Text -> App m a
ExitJuvixError :: JuvixError -> App m a
PrintJuvixError :: JuvixError -> App m ()
AskRoots :: App m Roots
AskInvokeDir :: App m (Path Abs Dir)
AskPkgDir :: App m (Path Abs Dir)
AskBuildDir :: App m (Path Abs Dir)
AskPackage :: App m Package
AskPackageGlobal :: App m Bool
AskGlobalOptions :: App m GlobalOptions
FromAppPathFile :: AppPath File -> App m (Path Abs File)
FromAppPathDir :: AppPath Dir -> App m (Path Abs Dir)
RenderStdOut :: (HasAnsiBackend a, HasTextBackend a) => a -> App m ()
RunPipelineEither :: AppPath File -> Sem PipelineEff a -> App m (Either JuvixError (ResolverState, a))
RunPipelineNoFileEither :: Sem PipelineEff a -> App m (Either JuvixError (ResolverState, a))
RunCorePipelineEither :: AppPath File -> App m (Either JuvixError Artifacts)
Say :: Text -> App m ()
SayRaw :: ByteString -> App m ()
makeSem ''App
data RunAppIOArgs = RunAppIOArgs
{ _runAppIOArgsGlobalOptions :: GlobalOptions,
_runAppIOArgsRoots :: Roots
}
runAppIO ::
forall r a.
(Member (Embed IO) r) =>
RunAppIOArgs ->
Sem (App ': r) a ->
Sem r a
runAppIO args@RunAppIOArgs {..} =
interpret $ \case
AskPackageGlobal -> return (_runAppIOArgsRoots ^. rootsPackageGlobal)
FromAppPathFile p -> embed (prepathToAbsFile invDir (p ^. pathPath))
FromAppPathDir p -> embed (prepathToAbsDir invDir (p ^. pathPath))
RenderStdOut t
| _runAppIOArgsGlobalOptions ^. globalOnlyErrors -> return ()
| otherwise -> embed $ do
sup <- Ansi.hSupportsANSIColor stdout
renderIO (not (_runAppIOArgsGlobalOptions ^. globalNoColors) && sup) t
AskGlobalOptions -> return _runAppIOArgsGlobalOptions
AskPackage -> return (_runAppIOArgsRoots ^. rootsPackage)
AskRoots -> return _runAppIOArgsRoots
AskInvokeDir -> return invDir
AskPkgDir -> return (_runAppIOArgsRoots ^. rootsRootDir)
AskBuildDir -> return (_runAppIOArgsRoots ^. rootsBuildDir)
RunCorePipelineEither input -> do
entry <- embed (getEntryPoint' args input)
embed (corePipelineIOEither entry)
RunPipelineEither input p -> do
entry <- embed (getEntryPoint' args input)
embed (runIOEither entry p)
RunPipelineNoFileEither p -> do
entry <- embed (getEntryPointStdin' args)
embed (runIOEither entry p)
Say t
| g ^. globalOnlyErrors -> return ()
| otherwise -> embed (putStrLn t)
PrintJuvixError e -> do
printErr e
ExitJuvixError e -> do
printErr e
embed exitFailure
ExitMsg exitCode t -> embed (putStrLn t >> hFlush stdout >> exitWith exitCode)
SayRaw b -> embed (ByteString.putStr b)
where
invDir = _runAppIOArgsRoots ^. rootsInvokeDir
g :: GlobalOptions
g = _runAppIOArgsGlobalOptions
printErr e =
embed $ hPutStrLn stderr $ run $ runReader (project' @GenericOptions g) $ Error.render (not (_runAppIOArgsGlobalOptions ^. globalNoColors)) (g ^. globalOnlyErrors) e
getEntryPoint' :: RunAppIOArgs -> AppPath File -> IO EntryPoint
getEntryPoint' RunAppIOArgs {..} inputFile = do
let opts = _runAppIOArgsGlobalOptions
roots = _runAppIOArgsRoots
estdin <-
if
| opts ^. globalStdin -> Just <$> getContents
| otherwise -> return Nothing
set entryPointStdin estdin <$> entryPointFromGlobalOptionsPre roots (inputFile ^. pathPath) opts
getEntryPointStdin' :: RunAppIOArgs -> IO EntryPoint
getEntryPointStdin' RunAppIOArgs {..} = do
let opts = _runAppIOArgsGlobalOptions
roots = _runAppIOArgsRoots
estdin <-
if
| opts ^. globalStdin -> Just <$> getContents
| otherwise -> return Nothing
set entryPointStdin estdin <$> entryPointFromGlobalOptionsNoFile roots opts
someBaseToAbs' :: (Members '[App] r) => SomeBase a -> Sem r (Path Abs a)
someBaseToAbs' f = do
r <- askInvokeDir
return (someBaseToAbs r f)
filePathToAbs :: Members '[Embed IO, App] r => Prepath FileOrDir -> Sem r (Either (Path Abs File) (Path Abs Dir))
filePathToAbs fp = do
invokeDir <- askInvokeDir
embed (fromPreFileOrDir invokeDir fp)
askGenericOptions :: (Members '[App] r) => Sem r GenericOptions
askGenericOptions = project <$> askGlobalOptions
getEntryPoint :: (Members '[Embed IO, App] r) => AppPath File -> Sem r EntryPoint
getEntryPoint inputFile = do
_runAppIOArgsGlobalOptions <- askGlobalOptions
_runAppIOArgsRoots <- askRoots
embed (getEntryPoint' (RunAppIOArgs {..}) inputFile)
runPipeline :: (Member App r) => AppPath File -> Sem PipelineEff a -> Sem r a
runPipeline input p = do
r <- runPipelineEither input p
case r of
Left err -> exitJuvixError err
Right res -> return (snd res)
runPipelineNoFile :: (Member App r) => Sem PipelineEff a -> Sem r a
runPipelineNoFile p = do
r <- runPipelineNoFileEither p
case r of
Left err -> exitJuvixError err
Right res -> return (snd res)
newline :: (Member App r) => Sem r ()
newline = say ""
printSuccessExit :: (Member App r) => Text -> Sem r a
printSuccessExit = exitMsg ExitSuccess
printFailureExit :: (Member App r) => Text -> Sem r a
printFailureExit = exitMsg (ExitFailure 1)
getRight :: (Members '[App] r, AppError e) => Either e a -> Sem r a
getRight = either appError return
instance AppError Text where
appError = printFailureExit
instance AppError JuvixError where
appError = exitJuvixError
class AppError e where
appError :: (Members '[App] r) => e -> Sem r a