aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/library/lux/control/parser
diff options
context:
space:
mode:
Diffstat (limited to '')
-rw-r--r--stdlib/source/library/lux/control/parser.lux33
-rw-r--r--stdlib/source/library/lux/control/parser/analysis.lux8
-rw-r--r--stdlib/source/library/lux/control/parser/binary.lux18
-rw-r--r--stdlib/source/library/lux/control/parser/cli.lux9
-rw-r--r--stdlib/source/library/lux/control/parser/code.lux13
-rw-r--r--stdlib/source/library/lux/control/parser/environment.lux6
-rw-r--r--stdlib/source/library/lux/control/parser/json.lux2
-rw-r--r--stdlib/source/library/lux/control/parser/text.lux6
-rw-r--r--stdlib/source/library/lux/control/parser/type.lux14
9 files changed, 15 insertions, 94 deletions
diff --git a/stdlib/source/library/lux/control/parser.lux b/stdlib/source/library/lux/control/parser.lux
index f4e304045..6d3246295 100644
--- a/stdlib/source/library/lux/control/parser.lux
+++ b/stdlib/source/library/lux/control/parser.lux
@@ -17,7 +17,6 @@
["n" nat]]]]])
(type: .public (Parser s a)
- {#.doc "A generic parser."}
(-> s (Try [s a])))
(implementation: .public functor
@@ -70,7 +69,6 @@
(ma input')))))
(def: .public (assertion message test)
- {#.doc "Fails with the given message if the test is #0."}
(All [s] (-> Text Bit (Parser s Any)))
(function (_ input)
(if test
@@ -78,7 +76,6 @@
(#try.Failure message))))
(def: .public (maybe parser)
- {#.doc "Optionality combinator."}
(All [s a]
(-> (Parser s a) (Parser s (Maybe a))))
(function (_ input)
@@ -90,15 +87,11 @@
(#try.Success [input' (#.Some x)]))))
(def: .public (result parser input)
- {#.doc (example "Executes the parser on the input."
- "Does not verify that all of the input has been consumed by the parser."
- "Returns both the parser's output, and a value that represents the remaining input.")}
(All [s a]
(-> (Parser s a) s (Try [s a])))
(parser input))
(def: .public (and first second)
- {#.doc "Sequencing combinator."}
(All [s a b]
(-> (Parser s a) (Parser s b) (Parser s [a b])))
(do {! ..monad}
@@ -106,7 +99,6 @@
(\ ! map (|>> [head]) second)))
(def: .public (or left right)
- {#.doc "Heterogeneous alternative combinator."}
(All [s a b]
(-> (Parser s a) (Parser s b) (Parser s (Or a b))))
(function (_ tokens)
@@ -123,7 +115,6 @@
(#try.Failure error)))))
(def: .public (either this that)
- {#.doc "Homogeneous alternative combinator."}
(All [s a]
(-> (Parser s a) (Parser s a) (Parser s a)))
(function (_ tokens)
@@ -135,7 +126,6 @@
output)))
(def: .public (some parser)
- {#.doc "0-or-more combinator."}
(All [s a]
(-> (Parser s a) (Parser s (List a))))
(function (_ input)
@@ -149,7 +139,6 @@
input'))))
(def: .public (many parser)
- {#.doc "1-or-more combinator."}
(All [s a]
(-> (Parser s a) (Parser s (List a))))
(|> (..some parser)
@@ -157,25 +146,22 @@
(\ ..monad map (|>> #.Item))))
(def: .public (exactly amount parser)
- {#.doc "Parse exactly N times."}
(All [s a] (-> Nat (Parser s a) (Parser s (List a))))
(case amount
0 (\ ..monad in (list))
_ (do {! ..monad}
[x parser]
(|> parser
- (exactly (dec amount))
+ (exactly (-- amount))
(\ ! map (|>> (#.Item x)))))))
(def: .public (at_least amount parser)
- {#.doc "Parse at least N times."}
(All [s a] (-> Nat (Parser s a) (Parser s (List a))))
(do {! ..monad}
[minimum (..exactly amount parser)]
(\ ! map (list\compose minimum) (..some parser))))
(def: .public (at_most amount parser)
- {#.doc "Parse at most N times."}
(All [s a] (-> Nat (Parser s a) (Parser s (List a))))
(case amount
0 (\ ..monad in (list))
@@ -186,7 +172,7 @@
(#try.Success [input' x])
(..result (\ ..monad map (|>> (#.Item x))
- (at_most (dec amount) parser))
+ (at_most (-- amount) parser))
input')))))
(def: .public (between minimum additional parser)
@@ -199,7 +185,6 @@
(..at_most additional parser)))))
(def: .public (separated_by separator parser)
- {#.doc "Parses instances of 'parser' that are separated by instances of 'separator'."}
(All [s a b] (-> (Parser s b) (Parser s a) (Parser s (List a))))
(do {! ..monad}
[?x (..maybe parser)]
@@ -214,7 +199,6 @@
(\ ! map (|>> (list\map product.right) (#.Item x)))))))
(def: .public (not parser)
- {#.doc (example "Only succeeds when the underlying parser fails.")}
(All [s a] (-> (Parser s a) (Parser s Any)))
(function (_ input)
(case (parser input)
@@ -225,13 +209,11 @@
(#try.Failure "Expected to fail; yet succeeded."))))
(def: .public (failure message)
- {#.doc (example "Always fail with this 'message'.")}
(All [s a] (-> Text (Parser s a)))
(function (_ input)
(#try.Failure message)))
(def: .public (lifted operation)
- {#.doc (example "Lift a potentially failed computation into a parser.")}
(All [s a] (-> (Try a) (Parser s a)))
(function (_ input)
(case operation
@@ -242,7 +224,6 @@
(#try.Failure error))))
(def: .public (else value parser)
- {#.doc "If the given parser fails, returns the default value."}
(All [s a] (-> a (Parser s a) (Parser s a)))
(function (_ input)
(case (parser input)
@@ -253,26 +234,22 @@
(#try.Success [input' output]))))
(def: .public remaining
- {#.doc (example "Yield the remaining input (without consuming it).")}
(All [s] (Parser s s))
(function (_ inputs)
(#try.Success [inputs inputs])))
(def: .public (rec parser)
- {#.doc "Combinator for recursive parsers."}
(All [s a] (-> (-> (Parser s a) (Parser s a)) (Parser s a)))
(function (_ inputs)
(..result (parser (rec parser)) inputs)))
(def: .public (after param subject)
- {#.doc (example "Run the parser after another one (whose output is ignored).")}
(All [s _ a] (-> (Parser s _) (Parser s a) (Parser s a)))
(do ..monad
[_ param]
subject))
(def: .public (before param subject)
- {#.doc (example "Run the parser before another one (whose output is ignored).")}
(All [s _ a] (-> (Parser s _) (Parser s a) (Parser s a)))
(do ..monad
[output subject
@@ -280,7 +257,6 @@
(in output)))
(def: .public (only test parser)
- {#.doc (example "Only succeed when the parser's output passes a test.")}
(All [s a] (-> (-> a Bit) (Parser s a) (Parser s a)))
(do ..monad
[output parser
@@ -288,7 +264,6 @@
(in output)))
(def: .public (parses? parser)
- {#.doc (example "Ignore a parser's output and just verify that it succeeds.")}
(All [s a] (-> (Parser s a) (Parser s Bit)))
(function (_ input)
(case (parser input)
@@ -299,7 +274,6 @@
(#try.Success [input' true]))))
(def: .public (parses parser)
- {#.doc (example "Ignore a parser's output and just execute it.")}
(All [s a] (-> (Parser s a) (Parser s Any)))
(function (_ input)
(case (parser input)
@@ -310,8 +284,6 @@
(#try.Success [input' []]))))
(def: .public (speculative parser)
- {#.doc (example "Executes a parser, without actually consuming the input."
- "That way, the same input can be consumed again by another parser.")}
(All [s a] (-> (Parser s a) (Parser s a)))
(function (_ input)
(case (parser input)
@@ -322,7 +294,6 @@
output)))
(def: .public (codec codec parser)
- {#.doc (example "Decode the output of a parser using a codec.")}
(All [s a z] (-> (Codec a z) (Parser s a) (Parser s z)))
(function (_ input)
(case (parser input)
diff --git a/stdlib/source/library/lux/control/parser/analysis.lux b/stdlib/source/library/lux/control/parser/analysis.lux
index fb32f4608..42bffc310 100644
--- a/stdlib/source/library/lux/control/parser/analysis.lux
+++ b/stdlib/source/library/lux/control/parser/analysis.lux
@@ -48,11 +48,9 @@
["Input" (exception.listing /.%analysis input)]))
(type: .public Parser
- {#.doc (example "A parser for Lux code analysis nodes.")}
(//.Parser (List Analysis)))
(def: .public (result parser input)
- {#.doc (example "Executes a parser and makes sure no inputs go unconsumed.")}
(All [a] (-> (Parser a) (List Analysis) (Try a)))
(case (parser input)
(#try.Failure error)
@@ -65,7 +63,6 @@
(exception.except ..unconsumed_input unconsumed)))
(def: .public any
- {#.doc (example "Matches any value, without discrimination.")}
(Parser Analysis)
(function (_ input)
(case input
@@ -76,7 +73,6 @@
(#try.Success [tail head]))))
(def: .public end!
- {#.doc "Ensures there are no more inputs."}
(Parser Any)
(function (_ tokens)
(case tokens
@@ -85,7 +81,6 @@
(remaining_inputs tokens))))))
(def: .public end?
- {#.doc "Checks whether there are no more inputs."}
(Parser Bit)
(function (_ tokens)
(#try.Success [tokens (case tokens
@@ -94,7 +89,6 @@
(template [<query> <assertion> <tag> <type> <eq>]
[(`` (as_is (def: .public <query>
- {#.doc (example (~~ (template.text ["Queries for a " <query> " value."])))}
(Parser <type>)
(function (_ input)
(case input
@@ -105,7 +99,6 @@
(exception.except ..cannot_parse input))))
(def: .public (<assertion> expected)
- {#.doc (example (~~ (template.text ["Assert a specific " <query> " value."])))}
(-> <type> (Parser Any))
(function (_ input)
(case input
@@ -129,7 +122,6 @@
)
(def: .public (tuple parser)
- {#.doc (example "Parses only within the context of a tuple's contents.")}
(All [a] (-> (Parser a) (Parser a)))
(function (_ input)
(case input
diff --git a/stdlib/source/library/lux/control/parser/binary.lux b/stdlib/source/library/lux/control/parser/binary.lux
index d2d195888..ec251b304 100644
--- a/stdlib/source/library/lux/control/parser/binary.lux
+++ b/stdlib/source/library/lux/control/parser/binary.lux
@@ -27,11 +27,9 @@
["." // ("#\." monad)])
(type: .public Offset
- {#.doc (example "An offset for reading within binary data.")}
Nat)
(type: .public Parser
- {#.doc (example "A parser for raw binary data.")}
(//.Parser [Offset Binary]))
(exception: .public (binary_was_not_fully_read {binary_length Nat} {bytes_read Nat})
@@ -40,7 +38,6 @@
["Bytes read" (%.nat bytes_read)]))
(def: .public (result parser input)
- {#.doc (example "Runs a parser and checks that all the binary data was read by it.")}
(All [a] (-> (Parser a) Binary (Try a)))
(case (parser [0 input])
(#try.Failure msg)
@@ -53,25 +50,21 @@
(exception.except ..binary_was_not_fully_read [length end])))))
(def: .public end?
- {#.doc (example "Checks whether there is no more data to read.")}
(Parser Bit)
(function (_ (^@ input [offset data]))
(#try.Success [input (n.= offset (/.size data))])))
(def: .public offset
- {#.doc (example "The current offset (i.e. how much data has been read).")}
(Parser Offset)
(function (_ (^@ input [offset data]))
(#try.Success [input offset])))
(def: .public remaining
- {#.doc (example "How much of the data remains to be read.")}
(Parser Nat)
(function (_ (^@ input [offset data]))
(#try.Success [input (n.- offset (/.size data))])))
(type: .public Size
- {#.doc (example "The size of a chunk of data within a binary array.")}
Nat)
(def: .public size/8 Size 1)
@@ -129,14 +122,12 @@
[1 #.Right right]]))
(def: .public (rec body)
- {#.doc (example "Tie the knot for a recursive parser.")}
(All [a] (-> (-> (Parser a) (Parser a)) (Parser a)))
(function (_ input)
(let [parser (body (rec body))]
(parser input))))
(def: .public any
- {#.doc (example "Does no parsing, and just returns a dummy value.")}
(Parser Any)
(//\in []))
@@ -156,7 +147,6 @@
_ (//.lifted (exception.except ..not_a_bit [value])))))
(def: .public (segment size)
- {#.doc (example "Parses a chunk of data of a given size.")}
(-> Nat (Parser Binary))
(function (_ [offset binary])
(case size
@@ -167,7 +157,6 @@
(template [<size> <name> <bits>]
[(`` (def: .public <name>
- {#.doc (example (~~ (template.text ["Parses a block of data prefixed with a size that is " <size> " bytes long."])))}
(Parser Binary)
(do //.monad
[size (//\map .nat <bits>)]
@@ -181,7 +170,6 @@
(template [<size> <name> <binary>]
[(`` (def: .public <name>
- {#.doc (example (~~ (template.text ["Parses a block of (UTF-8 encoded) text prefixed with a size that is " <size> " bytes long."])))}
(Parser Text)
(do //.monad
[utf8 <binary>]
@@ -197,7 +185,6 @@
(template [<size> <name> <bits>]
[(def: .public (<name> valueP)
- {#.doc (example (~~ (template.text ["Parses a row of values prefixed with a size that is " <size> " bytes long."])))}
(All [v] (-> (Parser v) (Parser (Row v))))
(do //.monad
[amount (: (Parser Nat)
@@ -212,8 +199,8 @@
(if (n.< amount index)
(do //.monad
[value valueP]
- (recur (.inc index)
- (row.add value output)))
+ (recur (.++ index)
+ (row.suffix value output)))
(//\in output)))))]
[08 row/8 ..bits/8]
@@ -227,7 +214,6 @@
(..or ..any))
(def: .public (list value)
- {#.doc (example "Parses an arbitrarily long list of values.")}
(All [a] (-> (Parser a) (Parser (List a))))
(..rec
(|>> (//.and value)
diff --git a/stdlib/source/library/lux/control/parser/cli.lux b/stdlib/source/library/lux/control/parser/cli.lux
index 3dd50a349..d9b4928ab 100644
--- a/stdlib/source/library/lux/control/parser/cli.lux
+++ b/stdlib/source/library/lux/control/parser/cli.lux
@@ -11,11 +11,9 @@
["." //])
(type: .public (Parser a)
- {#.doc "A command-line interface parser."}
(//.Parser (List Text) a))
(def: .public (result parser inputs)
- {#.doc (example "Executes the parser and verifies that all inputs are processed.")}
(All [a] (-> (Parser a) (List Text) (Try a)))
(case (//.result parser inputs)
(#try.Success [remaining output])
@@ -30,7 +28,6 @@
(#try.Failure try)))
(def: .public any
- {#.doc "Just returns the next input without applying any logic."}
(Parser Text)
(function (_ inputs)
(case inputs
@@ -41,7 +38,6 @@
(#try.Failure "Cannot parse empty arguments."))))
(def: .public (parse parser)
- {#.doc "Parses the next input with a parsing function."}
(All [a] (-> (-> Text (Try a)) (Parser a)))
(function (_ inputs)
(do try.monad
@@ -50,7 +46,6 @@
(in [remaining output]))))
(def: .public (this reference)
- {#.doc "Checks that a token is in the inputs."}
(-> Text (Parser Any))
(function (_ inputs)
(do try.monad
@@ -60,7 +55,6 @@
(#try.Failure (format "Missing token: '" reference "'"))))))
(def: .public (somewhere cli)
- {#.doc "Given a parser, tries to parse it somewhere in the inputs (i.e. not necessarily parsing the immediate inputs)."}
(All [a] (-> (Parser a) (Parser a)))
(function (_ inputs)
(loop [immediate inputs]
@@ -80,7 +74,6 @@
output])))))))
(def: .public end
- {#.doc "Ensures there are no more inputs."}
(Parser Any)
(function (_ inputs)
(case inputs
@@ -88,14 +81,12 @@
_ (#try.Failure (format "Unknown parameters: " (text.interposed " " inputs))))))
(def: .public (named name value)
- {#.doc (example "Parses a named parameter and yields its value.")}
(All [a] (-> Text (Parser a) (Parser a)))
(|> value
(//.after (..this name))
..somewhere))
(def: .public (parameter [short long] value)
- {#.doc (example "Parses a parameter that can have either a short or a long name.")}
(All [a] (-> [Text Text] (Parser a) (Parser a)))
(|> value
(//.after (//.either (..this short) (..this long)))
diff --git a/stdlib/source/library/lux/control/parser/code.lux b/stdlib/source/library/lux/control/parser/code.lux
index 93a2f65d9..1a3bbc5a7 100644
--- a/stdlib/source/library/lux/control/parser/code.lux
+++ b/stdlib/source/library/lux/control/parser/code.lux
@@ -28,7 +28,6 @@
(#.Item [[x y] pairs']) (list& x y (un_paired pairs'))))
(type: .public Parser
- {#.doc "A Lux code parser."}
(//.Parser (List Code)))
(def: remaining_inputs
@@ -38,7 +37,6 @@
($_ text\compose text.new_line "Remaining input: ")))
(def: .public any
- {#.doc "Yields the next input without applying any logic."}
(Parser Code)
(function (_ tokens)
(case tokens
@@ -51,7 +49,6 @@
(template [<query> <check> <type> <tag> <eq> <desc>]
[(with_expansions [<failure> (as_is (#try.Failure ($_ text\compose "Cannot parse " <desc> (remaining_inputs tokens))))]
(def: .public <query>
- {#.doc (code.text ($_ text\compose "Parses the next " <desc> " input."))}
(Parser <type>)
(function (_ tokens)
(case tokens
@@ -62,7 +59,6 @@
<failure>)))
(def: .public (<check> expected)
- {#.doc (code.text ($_ text\compose "Checks for a specific " <desc> " input."))}
(-> <type> (Parser Any))
(function (_ tokens)
(case tokens
@@ -85,7 +81,6 @@
)
(def: .public (this! code)
- {#.doc "Ensures the given Code is the next input."}
(-> Code (Parser Any))
(function (_ tokens)
(case tokens
@@ -101,7 +96,6 @@
(template [<query> <check> <tag> <eq> <desc>]
[(with_expansions [<failure> (as_is (#try.Failure ($_ text\compose "Cannot parse " <desc> (remaining_inputs tokens))))]
(def: .public <query>
- {#.doc (code.text ($_ text\compose "Parse a local " <desc> " (a " <desc> " that has no module prefix)."))}
(Parser Text)
(function (_ tokens)
(case tokens
@@ -112,7 +106,6 @@
<failure>)))
(def: .public (<check> expected)
- {#.doc (code.text ($_ text\compose "Checks for a specific local " <desc> " (a " <desc> " that has no module prefix)."))}
(-> Text (Parser Any))
(function (_ tokens)
(case tokens
@@ -130,7 +123,6 @@
(template [<name> <tag> <desc>]
[(def: .public (<name> p)
- {#.doc (code.text ($_ text\compose "Parses the contents of a " <desc> "."))}
(All [a]
(-> (Parser a) (Parser a)))
(function (_ tokens)
@@ -148,7 +140,6 @@
)
(def: .public (record p)
- {#.doc "Parses the contents of a record."}
(All [a]
(-> (Parser a) (Parser a)))
(function (_ tokens)
@@ -162,7 +153,6 @@
(#try.Failure ($_ text\compose "Cannot parse record" (remaining_inputs tokens))))))
(def: .public end!
- {#.doc "Verifies there are no more inputs."}
(Parser Any)
(function (_ tokens)
(case tokens
@@ -170,7 +160,6 @@
_ (#try.Failure ($_ text\compose "Expected list of tokens to be empty!" (remaining_inputs tokens))))))
(def: .public end?
- {#.doc "Checks whether there are no more inputs."}
(Parser Bit)
(function (_ tokens)
(#try.Success [tokens (case tokens
@@ -178,7 +167,6 @@
_ false)])))
(def: .public (result parser inputs)
- {#.doc (example "Executes a parser against a stream of code, and verifies all the inputs are consumed.")}
(All [a] (-> (Parser a) (List Code) (Try a)))
(case (parser inputs)
(#try.Failure error)
@@ -196,7 +184,6 @@
(text\compose "Unconsumed inputs: "))))))
(def: .public (local inputs parser)
- {#.doc "Runs parser against the given list of inputs."}
(All [a] (-> (List Code) (Parser a) (Parser a)))
(function (_ real)
(do try.monad
diff --git a/stdlib/source/library/lux/control/parser/environment.lux b/stdlib/source/library/lux/control/parser/environment.lux
index e12febdf3..f084a838d 100644
--- a/stdlib/source/library/lux/control/parser/environment.lux
+++ b/stdlib/source/library/lux/control/parser/environment.lux
@@ -13,11 +13,9 @@
["." //])
(type: .public Property
- {#.doc (example "A property in the environment.")}
Text)
(type: .public Environment
- {#.doc (example "An abstraction for environment variables of a program.")}
(Dictionary Property Text))
(exception: .public (unknown_property {property Property})
@@ -25,11 +23,9 @@
["Property" (%.text property)]))
(type: .public (Parser a)
- {#.doc (example "A parser of environment variables of a program.")}
(//.Parser Environment a))
(def: .public empty
- {#.doc (example "An empty environment.")}
Environment
(dictionary.empty text.hash))
@@ -44,7 +40,5 @@
(exception.except ..unknown_property [name]))))
(def: .public (result parser environment)
- {#.doc (example "Executes a parser against the given environment variables."
- "Does not check whether all environment variables were parsed, since they're usually an open set.")}
(All [a] (-> (Parser a) Environment (Try a)))
(\ try.monad map product.right (parser environment)))
diff --git a/stdlib/source/library/lux/control/parser/json.lux b/stdlib/source/library/lux/control/parser/json.lux
index 51c3cc2bf..65569ff9e 100644
--- a/stdlib/source/library/lux/control/parser/json.lux
+++ b/stdlib/source/library/lux/control/parser/json.lux
@@ -159,7 +159,7 @@
dictionary.entries
(list\map (function (_ [key value])
(list (#/.String key) value)))
- list.joined
+ list.together
(//.result parser))
(#try.Failure error)
(//.failure error)
diff --git a/stdlib/source/library/lux/control/parser/text.lux b/stdlib/source/library/lux/control/parser/text.lux
index fb2c59128..46ed6e987 100644
--- a/stdlib/source/library/lux/control/parser/text.lux
+++ b/stdlib/source/library/lux/control/parser/text.lux
@@ -302,7 +302,7 @@
[(def: .public (<name> parser)
{#.doc (code.text ($_ /\compose "Yields " <doc_modifier> " characters as a single continuous text (as a slice)."))}
(-> (Parser Text) (Parser Text))
- (|> parser <base> (\ //.monad map /.joined)))]
+ (|> parser <base> (\ //.monad map /.together)))]
[some //.some "some"]
[many //.many "many"]
@@ -324,7 +324,7 @@
(-> Nat (Parser Text) (Parser Text))
(|> parser
(<base> amount)
- (\ //.monad map /.joined)))]
+ (\ //.monad map /.together)))]
[exactly //.exactly "exactly"]
[at_most //.at_most "at most"]
@@ -347,7 +347,7 @@
(-> Nat Nat (Parser Text) (Parser Text))
(|> parser
(//.between minimum additional)
- (\ //.monad map /.joined)))
+ (\ //.monad map /.together)))
(def: .public (between! minimum additional parser)
(-> Nat Nat (Parser Slice) (Parser Slice))
diff --git a/stdlib/source/library/lux/control/parser/type.lux b/stdlib/source/library/lux/control/parser/type.lux
index 8016080b5..e6ea2b3dd 100644
--- a/stdlib/source/library/lux/control/parser/type.lux
+++ b/stdlib/source/library/lux/control/parser/type.lux
@@ -197,19 +197,19 @@
all_varsL (: (List Code) (list))]
(if (n.< num_args current_arg)
(if (n.= 0 current_arg)
- (let [varL (label (inc funcI))]
- (recur (inc current_arg)
+ (let [varL (label (++ funcI))]
+ (recur (++ current_arg)
(|> env'
(dictionary.has funcI [headT funcL])
- (dictionary.has (inc funcI) [(#.Parameter (inc funcI)) varL]))
+ (dictionary.has (++ funcI) [(#.Parameter (++ funcI)) varL]))
(#.Item varL all_varsL)))
(let [partialI (|> current_arg (n.* 2) (n.+ funcI))
- partial_varI (inc partialI)
+ partial_varI (++ partialI)
partial_varL (label partial_varI)
partialC (` ((~ funcL) (~+ (|> (list.indices num_args)
- (list\map (|>> (n.* 2) inc (n.+ funcI) label))
+ (list\map (|>> (n.* 2) ++ (n.+ funcI) label))
list.reversed))))]
- (recur (inc current_arg)
+ (recur (++ current_arg)
(|> env'
(dictionary.has partialI [.Nothing partialC])
(dictionary.has partial_varI [(#.Parameter partial_varI) partial_varL]))
@@ -265,7 +265,7 @@
(let [env_level (n./ 2 (dictionary.size env))
parameter_level (n./ 2 idx)
parameter_idx (n.% 2 idx)]
- (|> env_level dec (n.- parameter_level) (n.* 2) (n.+ parameter_idx))))
+ (|> env_level -- (n.- parameter_level) (n.* 2) (n.+ parameter_idx))))
(def: .public parameter
(Parser Code)