2022-05-18 18:10:10 +03:00
|
|
|
module App where
|
|
|
|
|
2022-09-14 17:16:15 +03:00
|
|
|
import CommonOptions
|
2022-08-12 10:48:06 +03:00
|
|
|
import Data.ByteString qualified as ByteString
|
2022-05-18 18:10:10 +03:00
|
|
|
import GlobalOptions
|
2023-12-30 22:15:35 +03:00
|
|
|
import Juvix.Compiler.Internal.Translation (InternalTypedResult)
|
2023-08-30 17:38:59 +03:00
|
|
|
import Juvix.Compiler.Internal.Translation.FromInternal.Analysis.Termination.Checker
|
2023-12-30 22:15:35 +03:00
|
|
|
import Juvix.Compiler.Pipeline.Loader.PathResolver
|
|
|
|
import Juvix.Compiler.Pipeline.Root
|
2023-10-23 14:38:52 +03:00
|
|
|
import Juvix.Compiler.Pipeline.Run
|
2022-08-03 14:20:40 +03:00
|
|
|
import Juvix.Data.Error qualified as Error
|
2023-10-30 16:05:52 +03:00
|
|
|
import Juvix.Extra.Paths.Base hiding (rootBuildDir)
|
2023-04-27 18:33:08 +03:00
|
|
|
import Juvix.Prelude.Pretty hiding
|
|
|
|
( Doc,
|
|
|
|
)
|
2022-05-18 18:10:10 +03:00
|
|
|
import System.Console.ANSI qualified as Ansi
|
|
|
|
|
|
|
|
data App m a where
|
2022-09-06 16:26:48 +03:00
|
|
|
ExitMsg :: ExitCode -> Text -> App m a
|
2024-01-16 19:22:10 +03:00
|
|
|
ExitFailMsg :: Text -> App m a
|
2022-07-08 14:59:45 +03:00
|
|
|
ExitJuvixError :: JuvixError -> App m a
|
2022-08-30 12:24:15 +03:00
|
|
|
PrintJuvixError :: JuvixError -> App m ()
|
2023-10-30 16:05:52 +03:00
|
|
|
AskRoot :: App m Root
|
2023-12-06 20:24:59 +03:00
|
|
|
AskArgs :: App m RunAppIOArgs
|
2022-12-20 15:05:40 +03:00
|
|
|
AskInvokeDir :: App m (Path Abs Dir)
|
|
|
|
AskPkgDir :: App m (Path Abs Dir)
|
2023-01-06 19:54:13 +03:00
|
|
|
AskBuildDir :: App m (Path Abs Dir)
|
2022-09-14 17:16:15 +03:00
|
|
|
AskPackage :: App m Package
|
2023-04-13 12:27:39 +03:00
|
|
|
AskPackageGlobal :: App m Bool
|
2022-09-14 17:16:15 +03:00
|
|
|
AskGlobalOptions :: App m GlobalOptions
|
2023-04-19 17:56:48 +03:00
|
|
|
FromAppPathFile :: AppPath File -> App m (Path Abs File)
|
2023-05-24 16:42:20 +03:00
|
|
|
GetMainFile :: Maybe (AppPath File) -> App m (Path Abs File)
|
2023-04-19 17:56:48 +03:00
|
|
|
FromAppPathDir :: AppPath Dir -> App m (Path Abs Dir)
|
2022-05-18 18:10:10 +03:00
|
|
|
RenderStdOut :: (HasAnsiBackend a, HasTextBackend a) => a -> App m ()
|
2022-06-09 17:36:07 +03:00
|
|
|
Say :: Text -> App m ()
|
2022-12-20 15:05:40 +03:00
|
|
|
SayRaw :: ByteString -> App m ()
|
2022-05-18 18:10:10 +03:00
|
|
|
|
2023-01-06 19:54:13 +03:00
|
|
|
data RunAppIOArgs = RunAppIOArgs
|
|
|
|
{ _runAppIOArgsGlobalOptions :: GlobalOptions,
|
2023-10-30 16:05:52 +03:00
|
|
|
_runAppIOArgsRoot :: Root
|
2023-01-06 19:54:13 +03:00
|
|
|
}
|
|
|
|
|
2023-12-06 20:24:59 +03:00
|
|
|
makeSem ''App
|
|
|
|
makeLenses ''RunAppIOArgs
|
|
|
|
|
2023-01-06 19:54:13 +03:00
|
|
|
runAppIO ::
|
|
|
|
forall r a.
|
2023-12-06 20:24:59 +03:00
|
|
|
(Members '[Embed IO, TaggedLock] r) =>
|
2023-01-06 19:54:13 +03:00
|
|
|
RunAppIOArgs ->
|
|
|
|
Sem (App ': r) a ->
|
|
|
|
Sem r a
|
2023-12-06 20:24:59 +03:00
|
|
|
runAppIO args = evalSingletonCache (readPackageRootIO root) . reAppIO args
|
|
|
|
where
|
|
|
|
root = args ^. runAppIOArgsRoot
|
|
|
|
|
|
|
|
reAppIO ::
|
|
|
|
forall r a.
|
|
|
|
(Members '[Embed IO, TaggedLock] r) =>
|
|
|
|
RunAppIOArgs ->
|
|
|
|
Sem (App ': r) a ->
|
|
|
|
Sem (SCache Package ': r) a
|
|
|
|
reAppIO args@RunAppIOArgs {..} =
|
|
|
|
reinterpret $ \case
|
2023-11-30 19:22:18 +03:00
|
|
|
AskPackageGlobal -> return (_runAppIOArgsRoot ^. rootPackageType `elem` [GlobalStdlib, GlobalPackageDescription, GlobalPackageBase])
|
2023-04-19 17:56:48 +03:00
|
|
|
FromAppPathFile p -> embed (prepathToAbsFile invDir (p ^. pathPath))
|
2023-05-24 16:42:20 +03:00
|
|
|
GetMainFile m -> getMainFile' m
|
2023-12-06 20:24:59 +03:00
|
|
|
FromAppPathDir p -> liftIO (prepathToAbsDir invDir (p ^. pathPath))
|
2023-01-06 19:54:13 +03:00
|
|
|
RenderStdOut t
|
|
|
|
| _runAppIOArgsGlobalOptions ^. globalOnlyErrors -> return ()
|
|
|
|
| otherwise -> embed $ do
|
|
|
|
sup <- Ansi.hSupportsANSIColor stdout
|
|
|
|
renderIO (not (_runAppIOArgsGlobalOptions ^. globalNoColors) && sup) t
|
|
|
|
AskGlobalOptions -> return _runAppIOArgsGlobalOptions
|
2023-12-06 20:24:59 +03:00
|
|
|
AskPackage -> getPkg
|
|
|
|
AskArgs -> return args
|
2023-10-30 16:05:52 +03:00
|
|
|
AskRoot -> return _runAppIOArgsRoot
|
2023-04-19 17:56:48 +03:00
|
|
|
AskInvokeDir -> return invDir
|
2023-10-30 16:05:52 +03:00
|
|
|
AskPkgDir -> return (_runAppIOArgsRoot ^. rootRootDir)
|
2023-11-07 21:11:02 +03:00
|
|
|
AskBuildDir -> return (resolveAbsBuildDir (_runAppIOArgsRoot ^. rootRootDir) (_runAppIOArgsRoot ^. rootBuildDir))
|
2023-01-06 19:54:13 +03:00
|
|
|
Say t
|
|
|
|
| g ^. globalOnlyErrors -> return ()
|
2024-01-16 19:22:10 +03:00
|
|
|
| otherwise -> putStrLn t
|
2023-01-06 19:54:13 +03:00
|
|
|
PrintJuvixError e -> do
|
|
|
|
printErr e
|
|
|
|
ExitJuvixError e -> do
|
|
|
|
printErr e
|
|
|
|
embed exitFailure
|
2024-01-16 19:22:10 +03:00
|
|
|
ExitMsg exitCode t -> exitMsg' (exitWith exitCode) t
|
|
|
|
ExitFailMsg t -> exitMsg' exitFailure t
|
2023-01-06 19:54:13 +03:00
|
|
|
SayRaw b -> embed (ByteString.putStr b)
|
2022-08-30 12:24:15 +03:00
|
|
|
where
|
2023-12-06 20:24:59 +03:00
|
|
|
getPkg :: (Members '[SCache Package] r') => Sem r' Package
|
|
|
|
getPkg = cacheSingletonGet
|
|
|
|
|
2024-01-16 19:22:10 +03:00
|
|
|
exitMsg' :: (Members '[Embed IO] r') => IO x -> Text -> Sem r' x
|
|
|
|
exitMsg' onExit t = liftIO (putStrLn t >> hFlush stdout >> onExit)
|
2023-12-06 20:24:59 +03:00
|
|
|
|
|
|
|
getMainFile' :: (Members '[SCache Package, Embed IO] r') => Maybe (AppPath File) -> Sem r' (Path Abs File)
|
2023-05-24 16:42:20 +03:00
|
|
|
getMainFile' = \case
|
|
|
|
Just p -> embed (prepathToAbsFile invDir (p ^. pathPath))
|
2023-12-06 20:24:59 +03:00
|
|
|
Nothing -> do
|
|
|
|
pkg <- getPkg
|
|
|
|
case pkg ^. packageMain of
|
|
|
|
Just p -> embed (prepathToAbsFile invDir p)
|
|
|
|
Nothing -> missingMainErr
|
|
|
|
|
|
|
|
missingMainErr :: (Members '[Embed IO] r') => Sem r' x
|
2023-05-24 16:42:20 +03:00
|
|
|
missingMainErr =
|
|
|
|
exitMsg'
|
2024-01-16 19:22:10 +03:00
|
|
|
exitFailure
|
2023-05-24 16:42:20 +03:00
|
|
|
( "A path to the main file must be given in the CLI or specified in the `main` field of the "
|
|
|
|
<> pack (toFilePath juvixYamlFile)
|
|
|
|
<> " file"
|
|
|
|
)
|
2023-10-30 16:05:52 +03:00
|
|
|
invDir = _runAppIOArgsRoot ^. rootInvokeDir
|
2023-01-06 19:54:13 +03:00
|
|
|
g :: GlobalOptions
|
|
|
|
g = _runAppIOArgsGlobalOptions
|
2022-08-30 12:24:15 +03:00
|
|
|
printErr e =
|
2023-01-06 19:54:13 +03:00
|
|
|
embed $ hPutStrLn stderr $ run $ runReader (project' @GenericOptions g) $ Error.render (not (_runAppIOArgsGlobalOptions ^. globalNoColors)) (g ^. globalOnlyErrors) e
|
2022-05-18 18:10:10 +03:00
|
|
|
|
2023-12-06 20:24:59 +03:00
|
|
|
getEntryPoint' :: (Members '[Embed IO, TaggedLock] r) => RunAppIOArgs -> AppPath File -> Sem r EntryPoint
|
2023-01-06 19:54:13 +03:00
|
|
|
getEntryPoint' RunAppIOArgs {..} inputFile = do
|
|
|
|
let opts = _runAppIOArgsGlobalOptions
|
2023-10-30 16:05:52 +03:00
|
|
|
root = _runAppIOArgsRoot
|
2022-09-14 17:16:15 +03:00
|
|
|
estdin <-
|
|
|
|
if
|
2023-12-06 20:24:59 +03:00
|
|
|
| opts ^. globalStdin -> Just <$> liftIO getContents
|
2022-09-14 17:16:15 +03:00
|
|
|
| otherwise -> return Nothing
|
2023-10-30 16:05:52 +03:00
|
|
|
set entryPointStdin estdin <$> entryPointFromGlobalOptionsPre root (inputFile ^. pathPath) opts
|
2022-09-14 17:16:15 +03:00
|
|
|
|
2023-12-30 22:15:35 +03:00
|
|
|
runPipelineEither :: (Members '[Embed IO, TaggedLock, App] r) => AppPath File -> Sem (PipelineEff r) a -> Sem r (Either JuvixError (ResolverState, PipelineResult a))
|
2024-01-16 19:22:10 +03:00
|
|
|
runPipelineEither input_ p = do
|
2023-12-06 20:24:59 +03:00
|
|
|
args <- askArgs
|
2024-01-16 19:22:10 +03:00
|
|
|
entry <- getEntryPoint' args input_
|
2023-12-30 22:15:35 +03:00
|
|
|
runIOEither entry p
|
|
|
|
|
|
|
|
runPipelineSetupEither :: (Members '[Embed IO, TaggedLock, App] r) => Sem (PipelineEff' r) a -> Sem r (Either JuvixError (ResolverState, a))
|
|
|
|
runPipelineSetupEither p = do
|
|
|
|
args <- askArgs
|
|
|
|
entry <- getEntryPointStdin' args
|
|
|
|
runIOEitherPipeline entry p
|
2023-12-06 20:24:59 +03:00
|
|
|
|
|
|
|
getEntryPointStdin' :: (Members '[Embed IO, TaggedLock] r) => RunAppIOArgs -> Sem r EntryPoint
|
2023-04-27 18:33:08 +03:00
|
|
|
getEntryPointStdin' RunAppIOArgs {..} = do
|
|
|
|
let opts = _runAppIOArgsGlobalOptions
|
2023-10-30 16:05:52 +03:00
|
|
|
root = _runAppIOArgsRoot
|
2023-04-27 18:33:08 +03:00
|
|
|
estdin <-
|
|
|
|
if
|
2023-12-06 20:24:59 +03:00
|
|
|
| opts ^. globalStdin -> Just <$> liftIO getContents
|
2023-04-27 18:33:08 +03:00
|
|
|
| otherwise -> return Nothing
|
2023-10-30 16:05:52 +03:00
|
|
|
set entryPointStdin estdin <$> entryPointFromGlobalOptionsNoFile root opts
|
2023-04-27 18:33:08 +03:00
|
|
|
|
Update CI to install Smoke, Github actions, and Makefile fixes (#1735)
This PR adds some maintenance at different levels to the CI config, the
Make file, and formatting.
- Most of the actions used by the CI related to haskell, ormolu, hlint
and pre-commit have been updated because Github requires NodeJS 16. This
change removes all the old warnings related to nodeJs.
In the case of ormolu, the new version makes us format some files that
were not formatted before, similarly with hlint.
- The CI has been updated to use the latest version of the Smoke testing
framework, which introduced installation of the dependencies for Linux
(libicu66) and macOS (icu4c) in the CI. In the case of macOS, the CI
uses a binary for smoke. For Linux, we use stack to build smoke from the
source. The source here is in a fork of [the official Smoke
repo](https://github.com/SamirTalwar/smoke). Such includes some
features/changes that are not yet in the official repo.
- The Makefile runs the ormolu and hlint targets using as a path for the
binaries the environment variables ORMOLU and HLINT. Thus, export those
variables in your environment before running `make check,` `make format`
or `make hlint`. Otherwise, the Makefile will use the binaries provided
by `stack`.
Co-authored-by: Paul Cadman <git@paulcadman.dev>
2023-01-24 13:50:23 +03:00
|
|
|
someBaseToAbs' :: (Members '[App] r) => SomeBase a -> Sem r (Path Abs a)
|
2022-12-20 15:05:40 +03:00
|
|
|
someBaseToAbs' f = do
|
|
|
|
r <- askInvokeDir
|
|
|
|
return (someBaseToAbs r f)
|
|
|
|
|
2023-08-25 19:37:23 +03:00
|
|
|
filePathToAbs :: (Members '[Embed IO, App] r) => Prepath FileOrDir -> Sem r (Either (Path Abs File) (Path Abs Dir))
|
2023-03-29 16:51:04 +03:00
|
|
|
filePathToAbs fp = do
|
|
|
|
invokeDir <- askInvokeDir
|
2023-04-19 17:56:48 +03:00
|
|
|
embed (fromPreFileOrDir invokeDir fp)
|
2023-03-29 16:51:04 +03:00
|
|
|
|
Update CI to install Smoke, Github actions, and Makefile fixes (#1735)
This PR adds some maintenance at different levels to the CI config, the
Make file, and formatting.
- Most of the actions used by the CI related to haskell, ormolu, hlint
and pre-commit have been updated because Github requires NodeJS 16. This
change removes all the old warnings related to nodeJs.
In the case of ormolu, the new version makes us format some files that
were not formatted before, similarly with hlint.
- The CI has been updated to use the latest version of the Smoke testing
framework, which introduced installation of the dependencies for Linux
(libicu66) and macOS (icu4c) in the CI. In the case of macOS, the CI
uses a binary for smoke. For Linux, we use stack to build smoke from the
source. The source here is in a fork of [the official Smoke
repo](https://github.com/SamirTalwar/smoke). Such includes some
features/changes that are not yet in the official repo.
- The Makefile runs the ormolu and hlint targets using as a path for the
binaries the environment variables ORMOLU and HLINT. Thus, export those
variables in your environment before running `make check,` `make format`
or `make hlint`. Otherwise, the Makefile will use the binaries provided
by `stack`.
Co-authored-by: Paul Cadman <git@paulcadman.dev>
2023-01-24 13:50:23 +03:00
|
|
|
askGenericOptions :: (Members '[App] r) => Sem r GenericOptions
|
2022-09-14 17:16:15 +03:00
|
|
|
askGenericOptions = project <$> askGlobalOptions
|
|
|
|
|
2023-12-06 20:24:59 +03:00
|
|
|
getEntryPoint :: (Members '[Embed IO, App, TaggedLock] r) => AppPath File -> Sem r EntryPoint
|
2022-09-14 17:16:15 +03:00
|
|
|
getEntryPoint inputFile = do
|
2023-01-06 19:54:13 +03:00
|
|
|
_runAppIOArgsGlobalOptions <- askGlobalOptions
|
2023-10-30 16:05:52 +03:00
|
|
|
_runAppIOArgsRoot <- askRoot
|
2023-12-06 20:24:59 +03:00
|
|
|
getEntryPoint' (RunAppIOArgs {..}) inputFile
|
2022-09-14 17:16:15 +03:00
|
|
|
|
2023-12-30 22:15:35 +03:00
|
|
|
getEntryPointStdin :: (Members '[Embed IO, App, TaggedLock] r) => Sem r EntryPoint
|
|
|
|
getEntryPointStdin = do
|
|
|
|
_runAppIOArgsGlobalOptions <- askGlobalOptions
|
|
|
|
_runAppIOArgsRoot <- askRoot
|
|
|
|
getEntryPointStdin' (RunAppIOArgs {..})
|
|
|
|
|
|
|
|
runPipelineTermination :: (Members '[Embed IO, App, TaggedLock] r) => AppPath File -> Sem (Termination ': PipelineEff r) a -> Sem r (PipelineResult a)
|
2024-01-16 19:22:10 +03:00
|
|
|
runPipelineTermination input_ p = do
|
|
|
|
r <- runPipelineEither input_ (evalTermination iniTerminationState p)
|
2023-08-30 17:38:59 +03:00
|
|
|
case r of
|
|
|
|
Left err -> exitJuvixError err
|
|
|
|
Right res -> return (snd res)
|
|
|
|
|
2023-12-06 20:24:59 +03:00
|
|
|
runPipeline :: (Members '[App, Embed IO, TaggedLock] r) => AppPath File -> Sem (PipelineEff r) a -> Sem r a
|
2024-01-16 19:22:10 +03:00
|
|
|
runPipeline input_ p = do
|
|
|
|
r <- runPipelineEither input_ p
|
2022-05-18 18:10:10 +03:00
|
|
|
case r of
|
2022-07-08 14:59:45 +03:00
|
|
|
Left err -> exitJuvixError err
|
2023-12-30 22:15:35 +03:00
|
|
|
Right res -> return (snd res ^. pipelineResult)
|
|
|
|
|
|
|
|
runPipelineHtml :: (Members '[App, Embed IO, TaggedLock] r) => Bool -> AppPath File -> Sem r (InternalTypedResult, [InternalTypedResult])
|
2024-01-17 13:15:38 +03:00
|
|
|
runPipelineHtml bNonRecursive input_
|
|
|
|
| bNonRecursive = do
|
|
|
|
r <- runPipeline input_ upToInternalTyped
|
|
|
|
return (r, [])
|
|
|
|
| otherwise = do
|
|
|
|
args <- askArgs
|
|
|
|
entry <- getEntryPoint' args input_
|
|
|
|
r <- runPipelineHtmlEither entry
|
|
|
|
case r of
|
|
|
|
Left err -> exitJuvixError err
|
|
|
|
Right res -> return res
|
2023-12-30 22:15:35 +03:00
|
|
|
|
|
|
|
runPipelineEntry :: (Members '[App, Embed IO, TaggedLock] r) => EntryPoint -> Sem (PipelineEff r) a -> Sem r a
|
|
|
|
runPipelineEntry entry p = do
|
|
|
|
r <- runIOEither entry p
|
|
|
|
case r of
|
|
|
|
Left err -> exitJuvixError err
|
|
|
|
Right res -> return (snd res ^. pipelineResult)
|
2022-05-18 18:10:10 +03:00
|
|
|
|
2023-12-30 22:15:35 +03:00
|
|
|
runPipelineSetup :: (Members '[App, Embed IO, TaggedLock] r) => Sem (PipelineEff' r) a -> Sem r a
|
|
|
|
runPipelineSetup p = do
|
|
|
|
r <- runPipelineSetupEither p
|
2023-04-27 18:33:08 +03:00
|
|
|
case r of
|
|
|
|
Left err -> exitJuvixError err
|
|
|
|
Right res -> return (snd res)
|
|
|
|
|
Update CI to install Smoke, Github actions, and Makefile fixes (#1735)
This PR adds some maintenance at different levels to the CI config, the
Make file, and formatting.
- Most of the actions used by the CI related to haskell, ormolu, hlint
and pre-commit have been updated because Github requires NodeJS 16. This
change removes all the old warnings related to nodeJs.
In the case of ormolu, the new version makes us format some files that
were not formatted before, similarly with hlint.
- The CI has been updated to use the latest version of the Smoke testing
framework, which introduced installation of the dependencies for Linux
(libicu66) and macOS (icu4c) in the CI. In the case of macOS, the CI
uses a binary for smoke. For Linux, we use stack to build smoke from the
source. The source here is in a fork of [the official Smoke
repo](https://github.com/SamirTalwar/smoke). Such includes some
features/changes that are not yet in the official repo.
- The Makefile runs the ormolu and hlint targets using as a path for the
binaries the environment variables ORMOLU and HLINT. Thus, export those
variables in your environment before running `make check,` `make format`
or `make hlint`. Otherwise, the Makefile will use the binaries provided
by `stack`.
Co-authored-by: Paul Cadman <git@paulcadman.dev>
2023-01-24 13:50:23 +03:00
|
|
|
newline :: (Member App r) => Sem r ()
|
2022-05-18 18:10:10 +03:00
|
|
|
newline = say ""
|
2022-06-09 17:36:07 +03:00
|
|
|
|
Update CI to install Smoke, Github actions, and Makefile fixes (#1735)
This PR adds some maintenance at different levels to the CI config, the
Make file, and formatting.
- Most of the actions used by the CI related to haskell, ormolu, hlint
and pre-commit have been updated because Github requires NodeJS 16. This
change removes all the old warnings related to nodeJs.
In the case of ormolu, the new version makes us format some files that
were not formatted before, similarly with hlint.
- The CI has been updated to use the latest version of the Smoke testing
framework, which introduced installation of the dependencies for Linux
(libicu66) and macOS (icu4c) in the CI. In the case of macOS, the CI
uses a binary for smoke. For Linux, we use stack to build smoke from the
source. The source here is in a fork of [the official Smoke
repo](https://github.com/SamirTalwar/smoke). Such includes some
features/changes that are not yet in the official repo.
- The Makefile runs the ormolu and hlint targets using as a path for the
binaries the environment variables ORMOLU and HLINT. Thus, export those
variables in your environment before running `make check,` `make format`
or `make hlint`. Otherwise, the Makefile will use the binaries provided
by `stack`.
Co-authored-by: Paul Cadman <git@paulcadman.dev>
2023-01-24 13:50:23 +03:00
|
|
|
printSuccessExit :: (Member App r) => Text -> Sem r a
|
2022-06-09 17:36:07 +03:00
|
|
|
printSuccessExit = exitMsg ExitSuccess
|
|
|
|
|
Update CI to install Smoke, Github actions, and Makefile fixes (#1735)
This PR adds some maintenance at different levels to the CI config, the
Make file, and formatting.
- Most of the actions used by the CI related to haskell, ormolu, hlint
and pre-commit have been updated because Github requires NodeJS 16. This
change removes all the old warnings related to nodeJs.
In the case of ormolu, the new version makes us format some files that
were not formatted before, similarly with hlint.
- The CI has been updated to use the latest version of the Smoke testing
framework, which introduced installation of the dependencies for Linux
(libicu66) and macOS (icu4c) in the CI. In the case of macOS, the CI
uses a binary for smoke. For Linux, we use stack to build smoke from the
source. The source here is in a fork of [the official Smoke
repo](https://github.com/SamirTalwar/smoke). Such includes some
features/changes that are not yet in the official repo.
- The Makefile runs the ormolu and hlint targets using as a path for the
binaries the environment variables ORMOLU and HLINT. Thus, export those
variables in your environment before running `make check,` `make format`
or `make hlint`. Otherwise, the Makefile will use the binaries provided
by `stack`.
Co-authored-by: Paul Cadman <git@paulcadman.dev>
2023-01-24 13:50:23 +03:00
|
|
|
printFailureExit :: (Member App r) => Text -> Sem r a
|
2022-06-09 17:36:07 +03:00
|
|
|
printFailureExit = exitMsg (ExitFailure 1)
|
2022-09-06 16:26:48 +03:00
|
|
|
|
|
|
|
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
|
Update CI to install Smoke, Github actions, and Makefile fixes (#1735)
This PR adds some maintenance at different levels to the CI config, the
Make file, and formatting.
- Most of the actions used by the CI related to haskell, ormolu, hlint
and pre-commit have been updated because Github requires NodeJS 16. This
change removes all the old warnings related to nodeJs.
In the case of ormolu, the new version makes us format some files that
were not formatted before, similarly with hlint.
- The CI has been updated to use the latest version of the Smoke testing
framework, which introduced installation of the dependencies for Linux
(libicu66) and macOS (icu4c) in the CI. In the case of macOS, the CI
uses a binary for smoke. For Linux, we use stack to build smoke from the
source. The source here is in a fork of [the official Smoke
repo](https://github.com/SamirTalwar/smoke). Such includes some
features/changes that are not yet in the official repo.
- The Makefile runs the ormolu and hlint targets using as a path for the
binaries the environment variables ORMOLU and HLINT. Thus, export those
variables in your environment before running `make check,` `make format`
or `make hlint`. Otherwise, the Makefile will use the binaries provided
by `stack`.
Co-authored-by: Paul Cadman <git@paulcadman.dev>
2023-01-24 13:50:23 +03:00
|
|
|
appError :: (Members '[App] r) => e -> Sem r a
|