1
1
mirror of https://github.com/anoma/juvix.git synced 2024-12-13 11:16:48 +03:00
juvix/test/Format.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

74 lines
2.0 KiB
Haskell

module Format where
import Base
import Juvix.Compiler.Concrete qualified as Concrete
import Juvix.Compiler.Concrete.Print qualified as P
import Juvix.Compiler.Concrete.Translation.FromParsed.Analysis.Scoping qualified as Scoper
import Juvix.Compiler.Concrete.Translation.FromSource qualified as Parser
import Juvix.Compiler.Pipeline.Setup
import Juvix.Prelude.Pretty
data PosTest = PosTest
{ _name :: String,
_dir :: Path Abs Dir,
_file :: Path Abs File
}
makeLenses ''PosTest
root :: Path Abs Dir
root = relToProject $(mkRelDir "tests/positive")
renderCode :: (HasLoc a, P.PrettyPrint a) => P.Comments -> a -> Text
renderCode c = prettyText . P.ppOutDefault c
posTest :: String -> Path Rel Dir -> Path Rel File -> PosTest
posTest _name rdir rfile =
let _dir = root <//> rdir
_file = _dir <//> rfile
in PosTest {..}
testDescr :: PosTest -> TestDescr
testDescr PosTest {..} =
TestDescr
{ _testName = _name,
_testRoot = _dir,
_testAssertion = Steps $ \step -> do
entryPoint <- defaultEntryPointCwdIO _file
let maybeFile = entryPoint ^? entryPointModulePaths . _head
f <- fromMaybeM (assertFailure "Not a module") (return maybeFile)
original :: Text <- readFile (toFilePath f)
step "Parsing"
p :: Parser.ParserResult <- snd <$> runIO' entryPoint upToParsing
step "Scoping"
s :: Scoper.ScoperResult <-
snd
<$> runIO'
entryPoint
( do
void entrySetup
Concrete.fromParsed p
)
let formatted :: Text
formatted = renderCode (s ^. Scoper.comments) (s ^. Scoper.mainModule)
step "Format"
assertEqDiffText "check: pretty . scope . parse = id" original formatted
}
allTests :: TestTree
allTests =
testGroup
"Format positive tests"
(map (mkTest . testDescr) tests)
tests :: [PosTest]
tests =
[ posTest
"Format"
$(mkRelDir ".")
$(mkRelFile "Format.juvix")
]