aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/lux/macro/syntax.lux
diff options
context:
space:
mode:
Diffstat (limited to '')
-rw-r--r--stdlib/source/lux/macro/syntax.lux52
1 files changed, 26 insertions, 26 deletions
diff --git a/stdlib/source/lux/macro/syntax.lux b/stdlib/source/lux/macro/syntax.lux
index 4b8339b8e..3d7b4575f 100644
--- a/stdlib/source/lux/macro/syntax.lux
+++ b/stdlib/source/lux/macro/syntax.lux
@@ -30,7 +30,7 @@
## [Structures]
(struct: #export _ (Functor Syntax)
(def: (map f ma)
- (lambda [tokens]
+ (function [tokens]
(case (ma tokens)
(#;Left msg)
(#;Left msg)
@@ -45,7 +45,7 @@
(#;Right [tokens x]))
(def: (apply ff fa)
- (lambda [tokens]
+ (function [tokens]
(case (ff tokens)
(#;Right [tokens' f])
(case (fa tokens')
@@ -62,7 +62,7 @@
(def: applicative Applicative<Syntax>)
(def: (join mma)
- (lambda [tokens]
+ (function [tokens]
(case (mma tokens)
(#;Left msg)
(#;Left msg)
@@ -80,7 +80,7 @@
(def: #export any
{#;doc "Just returns the next input without applying any logic."}
(Syntax AST)
- (lambda [tokens]
+ (function [tokens]
(case tokens
#;Nil (#;Left "There are no tokens to parse!")
(#;Cons [t tokens']) (#;Right [tokens' t]))))
@@ -89,7 +89,7 @@
[(def: #export <get-name>
{#;doc (#;TextA ($_ Text/append "Parses the next " <desc> " input AST."))}
(Syntax <type>)
- (lambda [tokens]
+ (function [tokens]
(case tokens
(#;Cons [[_ (<tag> x)] tokens'])
(#;Right [tokens' x])
@@ -111,7 +111,7 @@
(def: #export (this? ast)
{#;doc "Asks if the given AST is the next input."}
(-> AST (Syntax Bool))
- (lambda [tokens]
+ (function [tokens]
(case tokens
(#;Cons [token tokens'])
(let [is-it? (AST/= ast token)
@@ -126,7 +126,7 @@
(def: #export (this! ast)
{#;doc "Ensures the given AST is the next input."}
(-> AST (Syntax Unit))
- (lambda [tokens]
+ (function [tokens]
(case tokens
(#;Cons [token tokens'])
(if (AST/= ast token)
@@ -140,7 +140,7 @@
(def: #export (assert message test)
{#;doc "Fails with the given message if the test is false."}
(-> Text Bool (Syntax Unit))
- (lambda [tokens]
+ (function [tokens]
(if test
(#;Right [tokens []])
(#;Left ($_ Text/append message (remaining-inputs tokens))))))
@@ -161,7 +161,7 @@
[(def: #export <name>
{#;doc (#;TextA ($_ Text/append "Parse a local " <desc> " (a " <desc> " that has no module prefix)."))}
(Syntax Text)
- (lambda [tokens]
+ (function [tokens]
(case tokens
(#;Cons [[_ (<tag> ["" x])] tokens'])
(#;Right [tokens' x])
@@ -178,7 +178,7 @@
{#;doc (#;TextA ($_ Text/append "Parse inside the contents of a " <desc> " as if they were the input ASTs."))}
(All [a]
(-> (Syntax a) (Syntax a)))
- (lambda [tokens]
+ (function [tokens]
(case tokens
(#;Cons [[_ (<tag> members)] tokens'])
(case (p members)
@@ -196,7 +196,7 @@
{#;doc (#;TextA ($_ Text/append "Parse inside the contents of a record as if they were the input ASTs."))}
(All [a]
(-> (Syntax a) (Syntax a)))
- (lambda [tokens]
+ (function [tokens]
(case tokens
(#;Cons [[_ (#;RecordS pairs)] tokens'])
(case (p (join-pairs pairs))
@@ -210,7 +210,7 @@
{#;doc "Optionality combinator."}
(All [a]
(-> (Syntax a) (Syntax (Maybe a))))
- (lambda [tokens]
+ (function [tokens]
(case (p tokens)
(#;Left _) (#;Right [tokens #;None])
(#;Right [tokens' x]) (#;Right [tokens' (#;Some x)]))))
@@ -224,7 +224,7 @@
{#;doc "0-or-more combinator."}
(All [a]
(-> (Syntax a) (Syntax (List a))))
- (lambda [tokens]
+ (function [tokens]
(case (p tokens)
(#;Left _) (#;Right [tokens (list)])
(#;Right [tokens' x]) (run tokens'
@@ -255,7 +255,7 @@
{#;doc "Heterogeneous alternative combinator."}
(All [a b]
(-> (Syntax a) (Syntax b) (Syntax (| a b))))
- (lambda [tokens]
+ (function [tokens]
(case (p1 tokens)
(#;Right [tokens' x1]) (#;Right [tokens' (+0 x1)])
(#;Left _) (run tokens
@@ -268,7 +268,7 @@
{#;doc "Homogeneous alternative combinator."}
(All [a]
(-> (Syntax a) (Syntax a) (Syntax a)))
- (lambda [tokens]
+ (function [tokens]
(case (pl tokens)
(#;Left _) (pr tokens)
output output
@@ -277,7 +277,7 @@
(def: #export end!
{#;doc "Ensures there are no more inputs."}
(Syntax Unit)
- (lambda [tokens]
+ (function [tokens]
(case tokens
#;Nil (#;Right [tokens []])
_ (#;Left ($_ Text/append "Expected list of tokens to be empty!" (remaining-inputs tokens))))))
@@ -285,7 +285,7 @@
(def: #export end?
{#;doc "Checks whether there are no more inputs."}
(Syntax Bool)
- (lambda [tokens]
+ (function [tokens]
(case tokens
#;Nil (#;Right [tokens true])
_ (#;Right [tokens false]))))
@@ -312,7 +312,7 @@
{#;doc "Parse at most N times."}
(All [a] (-> Nat (Syntax a) (Syntax (List a))))
(if (n.> +0 n)
- (lambda [input]
+ (function [input]
(case (p input)
(#;Left msg)
(#;Right [input (list)])
@@ -350,7 +350,7 @@
(def: #export (not p)
(All [a] (-> (Syntax a) (Syntax Unit)))
- (lambda [input]
+ (function [input]
(case (p input)
(#;Left msg)
(#;Right [input []])
@@ -360,13 +360,13 @@
(def: #export (fail message)
(All [a] (-> Text (Syntax a)))
- (lambda [input]
+ (function [input]
(#;Left message)))
(def: #export (default value parser)
{#;doc "If the given parser fails, returns the default value."}
(All [a] (-> a (Syntax a) (Syntax a)))
- (lambda [input]
+ (function [input]
(case (parser input)
(#;Left error)
(#;Right [input value])
@@ -377,7 +377,7 @@
(def: #export (on compiler action)
{#;doc "Run a Lux operation as if it was a Syntax parser."}
(All [a] (-> Compiler (Lux a) (Syntax a)))
- (lambda [input]
+ (function [input]
(case (compiler;run compiler action)
(#;Left error)
(#;Left error)
@@ -389,7 +389,7 @@
(def: #export (local local-inputs syntax)
{#;doc "Run a syntax parser with the given list of inputs, instead of the real ones."}
(All [a] (-> (List AST) (Syntax a) (Syntax a)))
- (lambda [real-inputs]
+ (function [real-inputs]
(case (syntax local-inputs)
(#;Left error)
(#;Left error)
@@ -407,7 +407,7 @@
(def: #export (rec syntax)
{#;doc "Combinator for recursive syntax."}
(All [a] (-> (-> (Syntax a) (Syntax a)) (Syntax a)))
- (lambda [inputs]
+ (function [inputs]
(run inputs (syntax (rec syntax)))))
## [Syntax]
@@ -458,7 +458,7 @@
(do Monad<Lux>
[vars+parsers (mapM Monad<Lux>
(: (-> AST (Lux [AST AST]))
- (lambda [arg]
+ (function [arg]
(case arg
(^ [_ (#;TupleS (list var parser))])
(wrap [var parser])
@@ -483,7 +483,7 @@
(list)))]]
(wrap (list (` (macro: (~@ export-ast) ((~ (ast;symbol ["" name])) (~ g!tokens))
(~ meta)
- (lambda [(~ g!state)]
+ (function [(~ g!state)]
(;_lux_case (run (~ g!tokens)
(: (Syntax (Lux (List AST)))
(do Monad<Syntax>