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.lux44
1 files changed, 16 insertions, 28 deletions
diff --git a/stdlib/source/lux/macro/syntax.lux b/stdlib/source/lux/macro/syntax.lux
index b18e0763f..e31b8c876 100644
--- a/stdlib/source/lux/macro/syntax.lux
+++ b/stdlib/source/lux/macro/syntax.lux
@@ -194,13 +194,8 @@
(wrap [real value]))))
## [Syntax]
-(def: #hidden text/join-with text.join-with)
-
-(def: #hidden _run_ p.run)
-(def: #hidden _Monad<Parser>_ p.Monad<Parser>)
-
(macro: #export (syntax: tokens)
- {#.doc (doc "A more advanced way to define macros than macro:."
+ {#.doc (doc "A more advanced way to define macros than \"macro:\"."
"The inputs to the macro can be parsed in complex ways through the use of syntax parsers."
"The macro body is also (implicitly) run in the Monad<Meta>, to save some typing."
"Also, the compiler state can be accessed through the *compiler* binding."
@@ -216,16 +211,13 @@
(with-brackets (spaced (list/map constructor-arg$ constructor-args)))
(with-brackets (spaced (list/map (method-def$ id) methods))))))]
(wrap (list (` ((~ (code.text def-code)))))))))}
- (let [[exported? tokens] (: [(Maybe (Either Unit Unit)) (List Code)]
+ (let [[exported? tokens] (: [Bool (List Code)]
(case tokens
- (^ (list& [_ (#.Tag ["" "hidden"])] tokens'))
- [(#.Some #.Left) tokens']
-
(^ (list& [_ (#.Tag ["" "export"])] tokens'))
- [(#.Some #.Right) tokens']
+ [true tokens']
_
- [#.None tokens]))
+ [false tokens]))
?parts (: (Maybe [Text (List Code) Code Code])
(case tokens
(^ (list [_ (#.Form (list& [_ (#.Symbol ["" name])] args))]
@@ -241,7 +233,7 @@
#.None))]
(case ?parts
(#.Some [name args meta body])
- (with-gensyms [g!tokens g!body g!msg]
+ (with-gensyms [g!text/join-with g!tokens g!body g!error]
(do macro.Monad<Meta>
[vars+parsers (monad.map @
(: (-> Code (Meta [Code Code]))
@@ -258,29 +250,25 @@
args)
#let [g!state (code.symbol ["" "*compiler*"])
error-msg (code.text (text/compose "Wrong syntax for " name))
- export-ast (: (List Code) (case exported?
- (#.Some #.Left)
- (list (' #hidden))
-
- (#.Some #.Right)
- (list (' #export))
-
- _
- (list)))]]
- (wrap (list (` (macro: (~@ export-ast) ((~ (code.symbol ["" name])) (~ g!tokens) (~ g!state))
+ export-ast (: (List Code)
+ (if exported?
+ (list (' #export))
+ (list)))]]
+ (wrap (list (` (macro: (~+ export-ast) ((~ (code.symbol ["" name])) (~ g!tokens) (~ g!state))
(~ meta)
("lux case" (..run (~ g!tokens)
(: (Syntax (Meta (List Code)))
- (do .._Monad<Parser>_
- [(~@ (join-pairs vars+parsers))]
- ((~' wrap) (do macro.Monad<Meta>
+ (do (~! p.Monad<Parser>)
+ [(~+ (join-pairs vars+parsers))]
+ ((~' wrap) (do (~! macro.Monad<Meta>)
[]
(~ body))))))
{(#E.Success (~ g!body))
((~ g!body) (~ g!state))
- (#E.Error (~ g!msg))
- (#E.Error (text/join-with ": " (list (~ error-msg) (~ g!msg))))})))))))
+ (#E.Error (~ g!error))
+ (let [(~ g!text/join-with) (~! text.join-with)]
+ (#E.Error ((~ g!text/join-with) ": " (list (~ error-msg) (~ g!error)))))})))))))
_
(macro.fail "Wrong syntax for syntax:"))))