2022-08-12 00:05:38 +03:00
|
|
|
module Commands.Init where
|
|
|
|
|
|
|
|
import Data.Text qualified as Text
|
|
|
|
import Data.Versions
|
|
|
|
import Data.Yaml (encodeFile)
|
|
|
|
import Juvix.Compiler.Pipeline.Package
|
|
|
|
import Juvix.Data.Effect.Fail.Extra qualified as Fail
|
|
|
|
import Juvix.Extra.Paths
|
|
|
|
import Juvix.Prelude
|
|
|
|
import Juvix.Prelude.Pretty
|
|
|
|
import Text.Megaparsec (Parsec)
|
|
|
|
import Text.Megaparsec qualified as P
|
|
|
|
import Text.Megaparsec.Char qualified as P
|
|
|
|
|
|
|
|
type Err = Text
|
|
|
|
|
|
|
|
parse :: Parsec Void Text a -> Text -> Either Err a
|
|
|
|
parse p t = mapLeft ppErr (P.runParser p "<stdin>" t)
|
|
|
|
|
|
|
|
ppErr :: P.ParseErrorBundle Text Void -> Text
|
|
|
|
ppErr = pack . errorBundlePretty
|
|
|
|
|
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
|
|
|
init :: forall r. (Members '[Embed IO] r) => Sem r ()
|
2022-08-12 00:05:38 +03:00
|
|
|
init = do
|
|
|
|
checkNotInProject
|
|
|
|
say "✨ Your next Juvix adventure is about to begin! ✨"
|
|
|
|
say "I will help you set it up"
|
|
|
|
pkg <- getPackage
|
2022-12-20 15:05:40 +03:00
|
|
|
say ("creating " <> pack (toFilePath juvixYamlFile))
|
|
|
|
embed (encodeFile (toFilePath juvixYamlFile) (rawPackage pkg))
|
2022-08-12 00:05:38 +03:00
|
|
|
say "you are all set"
|
|
|
|
|
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
|
|
|
checkNotInProject :: forall r. (Members '[Embed IO] r) => Sem r ()
|
2022-08-12 00:05:38 +03:00
|
|
|
checkNotInProject =
|
2022-12-20 15:05:40 +03:00
|
|
|
whenM (doesFileExist juvixYamlFile) err
|
2022-08-12 00:05:38 +03:00
|
|
|
where
|
|
|
|
err :: Sem r ()
|
|
|
|
err = do
|
|
|
|
say "You are already in a Juvix project"
|
|
|
|
embed exitFailure
|
|
|
|
|
2023-02-10 19:53:23 +03:00
|
|
|
getPackage :: forall r. Members '[Embed IO] r => Sem r Package
|
2022-08-12 00:05:38 +03:00
|
|
|
getPackage = do
|
|
|
|
tproj <- getProjName
|
2023-02-10 19:53:23 +03:00
|
|
|
say "Write the version of your project [leave empty for 0.0.0]"
|
2022-12-20 15:05:40 +03:00
|
|
|
tversion :: SemVer <- getVersion
|
2022-08-12 00:05:38 +03:00
|
|
|
return
|
2023-04-13 12:27:39 +03:00
|
|
|
Package
|
2022-12-20 15:05:40 +03:00
|
|
|
{ _packageName = tproj,
|
2023-04-13 12:27:39 +03:00
|
|
|
_packageVersion = tversion,
|
|
|
|
_packageBuildDir = Nothing,
|
|
|
|
_packageDependencies = [defaultStdlibDep]
|
2022-08-12 00:05:38 +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
|
|
|
getProjName :: forall r. (Members '[Embed IO] r) => Sem r Text
|
2022-08-12 00:05:38 +03:00
|
|
|
getProjName = do
|
|
|
|
d <- getDefault
|
|
|
|
let defMsg :: Text
|
|
|
|
defMsg = case d of
|
|
|
|
Nothing -> mempty
|
|
|
|
Just d' -> " [leave empty for '" <> d' <> "']"
|
|
|
|
say
|
2023-02-10 19:53:23 +03:00
|
|
|
( "Write the name of your project"
|
2022-08-12 00:05:38 +03:00
|
|
|
<> defMsg
|
|
|
|
<> " (lower case letters, numbers and dashes are allowed): "
|
|
|
|
)
|
|
|
|
readName d
|
|
|
|
where
|
|
|
|
getDefault :: Sem r (Maybe Text)
|
|
|
|
getDefault = runFail $ do
|
2022-12-20 15:05:40 +03:00
|
|
|
dir <- map toLower . dropTrailingPathSeparator . toFilePath . dirname <$> getCurrentDir
|
2022-08-12 00:05:38 +03:00
|
|
|
Fail.fromRight (parse projectNameParser (pack dir))
|
|
|
|
readName :: Maybe Text -> Sem r Text
|
|
|
|
readName def = go
|
|
|
|
where
|
|
|
|
go :: Sem r Text
|
|
|
|
go = do
|
|
|
|
txt <- embed getLine
|
|
|
|
if
|
|
|
|
| Text.null txt, Just def' <- def -> return def'
|
|
|
|
| otherwise ->
|
|
|
|
case parse projectNameParser txt of
|
|
|
|
Right p
|
|
|
|
| Text.length p <= projextNameMaxLength -> return p
|
|
|
|
| otherwise -> do
|
|
|
|
say ("The project name cannot exceed " <> prettyText projextNameMaxLength <> " characters")
|
|
|
|
retry
|
|
|
|
Left err -> do
|
|
|
|
say err
|
|
|
|
retry
|
|
|
|
where
|
|
|
|
retry :: Sem r Text
|
|
|
|
retry = do
|
|
|
|
tryAgain
|
|
|
|
go
|
|
|
|
|
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
|
|
|
say :: (Members '[Embed IO] r) => Text -> Sem r ()
|
2022-08-12 00:05:38 +03:00
|
|
|
say = embed . putStrLn
|
|
|
|
|
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
|
|
|
tryAgain :: (Members '[Embed IO] r) => Sem r ()
|
2022-08-12 00:05:38 +03:00
|
|
|
tryAgain = say "Please, try again:"
|
|
|
|
|
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
|
|
|
getVersion :: forall r. (Members '[Embed IO] r) => Sem r SemVer
|
2022-08-12 00:05:38 +03:00
|
|
|
getVersion = do
|
|
|
|
txt <- embed getLine
|
|
|
|
if
|
|
|
|
| Text.null txt -> return mempty
|
|
|
|
| otherwise -> case parse semver' txt of
|
|
|
|
Right r -> return r
|
|
|
|
Left err -> do
|
|
|
|
say err
|
|
|
|
say "The version must follow the 'Semantic Versioning 2.0.0' specification"
|
|
|
|
retry
|
|
|
|
where
|
|
|
|
retry :: Sem r SemVer
|
|
|
|
retry = do
|
|
|
|
tryAgain
|
|
|
|
getVersion
|
|
|
|
|
|
|
|
projextNameMaxLength :: Int
|
|
|
|
projextNameMaxLength = 100
|
|
|
|
|
|
|
|
projectNameParser :: Parsec Void Text Text
|
|
|
|
projectNameParser = do
|
|
|
|
h <- P.satisfy validFirstChar
|
|
|
|
t <- P.takeWhileP (Just "project name character") validChar
|
|
|
|
P.hspace
|
|
|
|
P.eof
|
|
|
|
return (Text.cons h t)
|
|
|
|
where
|
|
|
|
validFirstChar :: Char -> Bool
|
|
|
|
validFirstChar c =
|
|
|
|
isAscii c
|
|
|
|
&& (isLower c || isNumber c)
|
|
|
|
validChar :: Char -> Bool
|
|
|
|
validChar c = c == '-' || validFirstChar c
|