mirror of
https://github.com/anoma/juvix.git
synced 2024-12-25 00:21:41 +03:00
a9995b8e1c
This PR adds an parser, pretty printer, evaluator, repl and quasi-quoter for Nock terms. ## Parser / Pretty Printer The parser and pretty printer handle both standard Nock terms and 'pretty' Nock terms (where op codes and paths can be named). Standard and pretty Nock forms can be mixed in the same term. For example instead of `[0 2]` you can write `[@ L]`. Seea6028b0d92/src/Juvix/Compiler/Nockma/Language.hs (L79)
for the correspondence between pretty Nock and Nock operators. In pretty Nock, paths are represented as strings of `L` (for head) and `R` (for tail) instead of the number encoding in standard nock. The character `S` is used to refer to the whole subject, i.e it is sugar for `1` in standard Nock. Seea6028b0d92/src/Juvix/Compiler/Nockma/Language.hs (L177)
for the correspondence between pretty Nock path and standard Nock position. ## Quasi-quoter A quasi-quoter is added so Nock terms can be included in the source, e.g `[nock| [@ LL] |]`. ## REPL Launch the repl with `juvix dev nockma repl`. A Nock `[subject formula]` cell is input as `subject / formula` , e.g: ``` nockma> [1 0] / [@ L] 1 ``` The subject can be set using `:set-stack`. ``` nockma> :set-stack [1 0] nockma> [@ L] 1 ``` The subject can be viewed using `:get-stack`. ``` nockma> :set-stack [1 0] nockma> :get-stack [1 0] ``` You can assign a Nock term to a variable and use it in another expression: ``` nockma> r := [@ L] nockma> [1 0] / r 1 ``` A list of assignments can be read from a file: ``` $ cat stack.nock r := [@ L] $ juvix dev nockma repl nockma> :load stack.nock nockma> [1 0] / r 1 ``` * Closes https://github.com/anoma/juvix/issues/2557 --------- Co-authored-by: Jan Mas Rovira <janmasrovira@gmail.com> Co-authored-by: Lukasz Czajka <lukasz@heliax.dev>
57 lines
1.7 KiB
Haskell
57 lines
1.7 KiB
Haskell
module Nockma.Parse.Positive where
|
|
|
|
import Base
|
|
import Data.ByteString qualified as BS
|
|
import Juvix.Compiler.Nockma.Language hiding (Path)
|
|
import Juvix.Compiler.Nockma.Pretty (ppPrint)
|
|
import Juvix.Compiler.Nockma.Translation.FromSource (parseText)
|
|
import Juvix.Parser.Error
|
|
import Juvix.Prelude.Pretty
|
|
import Text.Megaparsec
|
|
|
|
data PosTest = PosTest
|
|
{ _name :: String,
|
|
_relDir :: Path Rel Dir,
|
|
_file :: Path Rel File
|
|
}
|
|
|
|
makeLenses ''PosTest
|
|
|
|
root :: Path Abs Dir
|
|
root = relToProject $(mkRelDir "tests/nockma/positive")
|
|
|
|
testDescr :: PosTest -> TestDescr
|
|
testDescr PosTest {..} =
|
|
let tRoot = root <//> _relDir
|
|
file' = tRoot <//> _file
|
|
in TestDescr
|
|
{ _testName = _name,
|
|
_testRoot = tRoot,
|
|
_testAssertion = Steps $ \step -> do
|
|
step "Parsing"
|
|
txt <- decodeUtf8 <$> BS.readFile (toFilePath file')
|
|
nockmaTerm <- assertParse txt
|
|
|
|
step "Pretty printing"
|
|
let ppTerm = ppPrint nockmaTerm
|
|
|
|
step "parse . pretty . parse == parse"
|
|
prettyNockmaTerm <- assertParse ppTerm
|
|
assertEqual "expected equal" nockmaTerm prettyNockmaTerm
|
|
}
|
|
|
|
assertParse :: Text -> IO (Term Natural)
|
|
assertParse txt = case parseText txt of
|
|
Left (MegaparsecError b) -> assertFailure ("Nockma parsing failed " <> unpack (prettyText (errorBundlePretty b)))
|
|
Right t -> return t
|
|
|
|
allTests :: TestTree
|
|
allTests = testGroup "Nockma parse positive" (map (mkTest . testDescr) tests)
|
|
|
|
tests :: [PosTest]
|
|
tests =
|
|
[ PosTest "Identity" $(mkRelDir ".") $(mkRelFile "Identity.nock"),
|
|
PosTest "Identity Pretty" $(mkRelDir ".") $(mkRelFile "IdentityPretty.pnock"),
|
|
PosTest "Stdlib" $(mkRelDir ".") $(mkRelFile "Stdlib.nock")
|
|
]
|