aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/lux/macro
diff options
context:
space:
mode:
Diffstat (limited to '')
-rw-r--r--stdlib/source/lux/macro.lux54
-rw-r--r--stdlib/source/lux/macro/code.lux58
-rw-r--r--stdlib/source/lux/macro/poly.lux18
-rw-r--r--stdlib/source/lux/macro/poly/equivalence.lux16
-rw-r--r--stdlib/source/lux/macro/poly/functor.lux16
-rw-r--r--stdlib/source/lux/macro/poly/json.lux22
-rw-r--r--stdlib/source/lux/macro/syntax.lux32
-rw-r--r--stdlib/source/lux/macro/syntax/common/reader.lux10
-rw-r--r--stdlib/source/lux/macro/syntax/common/writer.lux6
9 files changed, 116 insertions, 116 deletions
diff --git a/stdlib/source/lux/macro.lux b/stdlib/source/lux/macro.lux
index f6dc72204..1909aeca6 100644
--- a/stdlib/source/lux/macro.lux
+++ b/stdlib/source/lux/macro.lux
@@ -173,15 +173,15 @@
_
#.None))]
- [get-bit-ann #.Bit Bit]
- [get-int-ann #.Int Int]
- [get-frac-ann #.Frac Frac]
- [get-text-ann #.Text Text]
- [get-symbol-ann #.Symbol Name]
- [get-tag-ann #.Tag Name]
- [get-form-ann #.Form (List Code)]
- [get-tuple-ann #.Tuple (List Code)]
- [get-record-ann #.Record (List [Code Code])]
+ [get-bit-ann #.Bit Bit]
+ [get-int-ann #.Int Int]
+ [get-frac-ann #.Frac Frac]
+ [get-text-ann #.Text Text]
+ [get-identifier-ann #.Identifier Name]
+ [get-tag-ann #.Tag Name]
+ [get-form-ann #.Form (List Code)]
+ [get-tuple-ann #.Tuple (List Code)]
+ [get-record-ann #.Record (List [Code Code])]
)
(def: #export (get-doc anns)
@@ -210,7 +210,7 @@
(def: #export (aliased? annotations)
(-> Code Bit)
- (case (get-symbol-ann (name-for #.alias) annotations)
+ (case (get-identifier-ann (name-for #.alias) annotations)
(#.Some _)
#1
@@ -255,7 +255,7 @@
(if (and (macro? def-anns)
(or (export? def-anns) (text/= module this-module)))
(#.Some (:coerce Macro def-value))
- (case (get-symbol-ann (name-for #.alias) def-anns)
+ (case (get-identifier-ann (name-for #.alias) def-anns)
(#.Some [r-module r-name])
(find-macro' modules this-module r-module r-name)
@@ -291,7 +291,7 @@
Otherwise, returns the code as-is."}
(-> Code (Meta (List Code)))
(case syntax
- [_ (#.Form (#.Cons [[_ (#.Symbol name)] args]))]
+ [_ (#.Form (#.Cons [[_ (#.Identifier name)] args]))]
(do Monad<Meta>
[?macro (find-macro name)]
(case ?macro
@@ -310,7 +310,7 @@
Otherwise, returns the code as-is."}
(-> Code (Meta (List Code)))
(case syntax
- [_ (#.Form (#.Cons [[_ (#.Symbol name)] args]))]
+ [_ (#.Form (#.Cons [[_ (#.Identifier name)] args]))]
(do Monad<Meta>
[?macro (find-macro name)]
(case ?macro
@@ -330,7 +330,7 @@
{#.doc "Expands all macro-calls everywhere recursively, until only primitive/base code remains."}
(-> Code (Meta (List Code)))
(case syntax
- [_ (#.Form (#.Cons [[_ (#.Symbol name)] args]))]
+ [_ (#.Form (#.Cons [[_ (#.Identifier name)] args]))]
(do Monad<Meta>
[?macro (find-macro name)]
(case ?macro
@@ -342,7 +342,7 @@
#.None
(do Monad<Meta>
- [parts' (monad.map Monad<Meta> expand-all (list& (code.symbol name) args))]
+ [parts' (monad.map Monad<Meta> expand-all (list& (code.identifier name) args))]
(wrap (list (code.form (list/join parts')))))))
[_ (#.Form (#.Cons [harg targs]))]
@@ -370,19 +370,19 @@
(get@ #.seed)
(:: number.Codec<Text,Nat> encode)
($_ text/compose "__gensym__" prefix)
- [""] code.symbol)])))
+ [""] code.identifier)])))
-(def: (get-local-symbol ast)
+(def: (get-local-identifier ast)
(-> Code (Meta Text))
(case ast
- [_ (#.Symbol [_ name])]
+ [_ (#.Identifier [_ name])]
(:: Monad<Meta> wrap name)
_
- (fail (text/compose "Code is not a local symbol: " (code.to-text ast)))))
+ (fail (text/compose "Code is not a local identifier: " (code.to-text ast)))))
(macro: #export (with-gensyms tokens)
- {#.doc (doc "Creates new symbols and offers them to the body expression."
+ {#.doc (doc "Creates new identifiers and offers them to the body expression."
(syntax: #export (synchronized lock body)
(with-gensyms [g!lock g!body g!_]
(wrap (list (` (let [(~ g!lock) (~ lock)
@@ -392,14 +392,14 @@
(~ g!body)))))
)))}
(case tokens
- (^ (list [_ (#.Tuple symbols)] body))
+ (^ (list [_ (#.Tuple identifiers)] body))
(do Monad<Meta>
- [symbol-names (monad.map @ get-local-symbol symbols)
- #let [symbol-defs (list/join (list/map (: (-> Text (List Code))
- (function (_ name) (list (code.symbol ["" name]) (` (gensym (~ (code.text name)))))))
- symbol-names))]]
+ [identifier-names (monad.map @ get-local-identifier identifiers)
+ #let [identifier-defs (list/join (list/map (: (-> Text (List Code))
+ (function (_ name) (list (code.identifier ["" name]) (` (gensym (~ (code.text name)))))))
+ identifier-names))]]
(wrap (list (` ((~! do) (~! Monad<Meta>)
- [(~+ symbol-defs)]
+ [(~+ identifier-defs)]
(~ body))))))
_
@@ -671,7 +671,7 @@
(-> Name (Meta Name))
(do Monad<Meta>
[[_ def-anns _] (find-def def-name)]
- (case (get-symbol-ann (name-for #.alias) def-anns)
+ (case (get-identifier-ann (name-for #.alias) def-anns)
(#.Some real-def-name)
(wrap real-def-name)
diff --git a/stdlib/source/lux/macro/code.lux b/stdlib/source/lux/macro/code.lux
index b48406f13..f6896343c 100644
--- a/stdlib/source/lux/macro/code.lux
+++ b/stdlib/source/lux/macro/code.lux
@@ -17,8 +17,8 @@
## (#.Int Int)
## (#.Frac Frac)
## (#.Text Text)
-## (#.Symbol Text Text)
-## (#.Tag Text Text)
+## (#.Identifier Name)
+## (#.Tag Name)
## (#.Form (List (w (Code' w))))
## (#.Tuple (List (w (Code' w))))
## (#.Record (List [(w (Code' w)) (w (Code' w))])))
@@ -35,17 +35,17 @@
(-> <type> Code)
[_cursor (<tag> x)])]
- [bit Bit #.Bit]
- [nat Nat #.Nat]
- [int Int #.Int]
- [rev Rev #.Rev]
- [frac Frac #.Frac]
- [text Text #.Text]
- [symbol Name #.Symbol]
- [tag Name #.Tag]
- [form (List Code) #.Form]
- [tuple (List Code) #.Tuple]
- [record (List [Code Code]) #.Record]
+ [bit Bit #.Bit]
+ [nat Nat #.Nat]
+ [int Int #.Int]
+ [rev Rev #.Rev]
+ [frac Frac #.Frac]
+ [text Text #.Text]
+ [identifier Name #.Identifier]
+ [tag Name #.Tag]
+ [form (List Code) #.Form]
+ [tuple (List Code) #.Tuple]
+ [record (List [Code Code]) #.Record]
)
(do-template [<name> <tag> <doc>]
@@ -54,8 +54,8 @@
(-> Text Code)
[_cursor (<tag> ["" name])])]
- [local-symbol #.Symbol "Produces a local symbol (a symbol with no module prefix)."]
- [local-tag #.Tag "Produces a local tag (a tag with no module prefix)."])
+ [local-identifier #.Identifier "Produces a local identifier (an identifier with no module prefix)."]
+ [local-tag #.Tag "Produces a local tag (a tag with no module prefix)."])
## [Structures]
(structure: #export _ (Equivalence Code)
@@ -64,14 +64,14 @@
(^template [<tag> <eq>]
[[_ (<tag> x')] [_ (<tag> y')]]
(:: <eq> = x' y'))
- ([#.Bit Equivalence<Bit>]
- [#.Nat Equivalence<Nat>]
- [#.Int Equivalence<Int>]
- [#.Rev Equivalence<Rev>]
- [#.Frac Equivalence<Frac>]
- [#.Text Equivalence<Text>]
- [#.Symbol Equivalence<Name>]
- [#.Tag Equivalence<Name>])
+ ([#.Bit Equivalence<Bit>]
+ [#.Nat Equivalence<Nat>]
+ [#.Int Equivalence<Int>]
+ [#.Rev Equivalence<Rev>]
+ [#.Frac Equivalence<Frac>]
+ [#.Text Equivalence<Text>]
+ [#.Identifier Equivalence<Name>]
+ [#.Tag Equivalence<Name>])
(^template [<tag>]
[[_ (<tag> xs')] [_ (<tag> ys')]]
@@ -93,12 +93,12 @@
(^template [<tag> <struct>]
[_ (<tag> value)]
(:: <struct> encode value))
- ([#.Bit Codec<Text,Bit>]
- [#.Nat Codec<Text,Nat>]
- [#.Int Codec<Text,Int>]
- [#.Rev Codec<Text,Rev>]
- [#.Frac Codec<Text,Frac>]
- [#.Symbol Codec<Text,Name>])
+ ([#.Bit Codec<Text,Bit>]
+ [#.Nat Codec<Text,Nat>]
+ [#.Int Codec<Text,Int>]
+ [#.Rev Codec<Text,Rev>]
+ [#.Frac Codec<Text,Frac>]
+ [#.Identifier Codec<Text,Name>])
[_ (#.Text value)]
(text.encode value)
diff --git a/stdlib/source/lux/macro/poly.lux b/stdlib/source/lux/macro/poly.lux
index 1dffc77ea..7cfa74fce 100644
--- a/stdlib/source/lux/macro/poly.lux
+++ b/stdlib/source/lux/macro/poly.lux
@@ -131,7 +131,7 @@
(def: (label idx)
(-> Nat Code)
- (code.local-symbol (text/compose "label\u0000" (nat/encode idx))))
+ (code.local-identifier (text/compose "label\u0000" (nat/encode idx))))
(def: #export (with-extension type poly)
(All [a] (-> Type (Poly a) (Poly [Code a])))
@@ -353,11 +353,11 @@
## [Syntax]
(syntax: #export (poly: {export csr.export}
- {name s.local-symbol}
+ {name s.local-identifier}
body)
(with-gensyms [g!_ g!type g!output]
- (let [g!name (code.symbol ["" name])]
- (wrap (.list (` (syntax: (~+ (csw.export export)) ((~ g!name) {(~ g!type) s.symbol})
+ (let [g!name (code.identifier ["" name])]
+ (wrap (.list (` (syntax: (~+ (csw.export export)) ((~ g!name) {(~ g!type) s.identifier})
(do macro.Monad<Meta>
[(~ g!type) (macro.find-type-def (~ g!type))]
(case (|> (~ body)
@@ -383,8 +383,8 @@
#.None))
(syntax: #export (derived: {export csr.export}
- {?name (p.maybe s.local-symbol)}
- {[poly-func poly-args] (s.form (p.seq s.symbol (p.many s.symbol)))}
+ {?name (p.maybe s.local-identifier)}
+ {[poly-func poly-args] (s.form (p.seq s.identifier (p.many s.identifier)))}
{?custom-impl (p.maybe s.any)})
(do @
[poly-args (monad.map @ macro.normalize poly-args)
@@ -404,9 +404,9 @@
custom-impl
#.None
- (` ((~ (code.symbol poly-func)) (~+ (list/map code.symbol poly-args)))))]]
+ (` ((~ (code.identifier poly-func)) (~+ (list/map code.identifier poly-args)))))]]
(wrap (.list (` (def: (~+ (csw.export export))
- (~ (code.symbol ["" name]))
+ (~ (code.identifier ["" name]))
{#.struct? #1}
(~ impl)))))))
@@ -448,7 +448,7 @@
[#.Product & type.flatten-tuple])
(#.Named name sub-type)
- (code.symbol name)
+ (code.identifier name)
(^template [<tag>]
(<tag> scope body)
diff --git a/stdlib/source/lux/macro/poly/equivalence.lux b/stdlib/source/lux/macro/poly/equivalence.lux
index 8c2f8dd21..80606aeb2 100644
--- a/stdlib/source/lux/macro/poly/equivalence.lux
+++ b/stdlib/source/lux/macro/poly/equivalence.lux
@@ -35,7 +35,7 @@
## [Derivers]
(poly: #export Equivalence<?>
(`` (do @
- [#let [g!_ (code.local-symbol "_____________")]
+ [#let [g!_ (code.local-identifier "_____________")]
*env* poly.env
inputT poly.peek
#let [@Equivalence (: (-> Type Code)
@@ -99,9 +99,9 @@
## Variants
(do @
[members (poly.variant (p.many Equivalence<?>))
- #let [g!_ (code.local-symbol "_____________")
- g!left (code.local-symbol "_____________left")
- g!right (code.local-symbol "_____________right")]]
+ #let [g!_ (code.local-identifier "_____________")
+ g!left (code.local-identifier "_____________left")
+ g!right (code.local-identifier "_____________right")]]
(wrap (` (: (~ (@Equivalence inputT))
(function ((~ g!_) (~ g!left) (~ g!right))
(case [(~ g!left) (~ g!right)]
@@ -115,10 +115,10 @@
## Tuples
(do @
[g!eqs (poly.tuple (p.many Equivalence<?>))
- #let [g!_ (code.local-symbol "_____________")
+ #let [g!_ (code.local-identifier "_____________")
indices (|> (list.size g!eqs) dec (list.n/range +0))
- g!lefts (list/map (|>> nat/encode (text/compose "left") code.local-symbol) indices)
- g!rights (list/map (|>> nat/encode (text/compose "right") code.local-symbol) indices)]]
+ g!lefts (list/map (|>> nat/encode (text/compose "left") code.local-identifier) indices)
+ g!rights (list/map (|>> nat/encode (text/compose "right") code.local-identifier) indices)]]
(wrap (` (: (~ (@Equivalence inputT))
(function ((~ g!_) [(~+ g!lefts)] [(~+ g!rights)])
(and (~+ (|> (list.zip3 g!eqs g!lefts g!rights)
@@ -127,7 +127,7 @@
## Type recursion
(do @
[[g!self bodyC] (poly.recursive Equivalence<?>)
- #let [g!_ (code.local-symbol "_____________")]]
+ #let [g!_ (code.local-identifier "_____________")]]
(wrap (` (: (~ (@Equivalence inputT))
(eq.rec (.function ((~ g!_) (~ g!self))
(~ bodyC)))))))
diff --git a/stdlib/source/lux/macro/poly/functor.lux b/stdlib/source/lux/macro/poly/functor.lux
index 3b9e851a4..d28e98337 100644
--- a/stdlib/source/lux/macro/poly/functor.lux
+++ b/stdlib/source/lux/macro/poly/functor.lux
@@ -19,9 +19,9 @@
(poly: #export Functor<?>
(do @
- [#let [type-funcC (code.local-symbol "____________type-funcC")
- funcC (code.local-symbol "____________funcC")
- inputC (code.local-symbol "____________inputC")]
+ [#let [type-funcC (code.local-identifier "____________type-funcC")
+ funcC (code.local-identifier "____________funcC")
+ inputC (code.local-identifier "____________inputC")]
*env* poly.env
inputT poly.peek
[polyC varsC non-functorT] (poly.local (list inputT)
@@ -31,7 +31,7 @@
(function (_ unwrappedT)
(if (n/= +1 num-vars)
(` ((~! functor.Functor) (~ (poly.to-code *env* unwrappedT))))
- (let [paramsC (|> num-vars dec list.indices (list/map (|>> %n code.local-symbol)))]
+ (let [paramsC (|> num-vars dec list.indices (list/map (|>> %n code.local-identifier)))]
(` (All [(~+ paramsC)]
((~! functor.Functor) ((~ (poly.to-code *env* unwrappedT)) (~+ paramsC)))))))))
Arg<?> (: (-> Code (poly.Poly Code))
@@ -57,7 +57,7 @@
(poly.tuple (loop [idx +0
pairsCC (: (List [Code Code])
(list))]
- (p.either (let [slotC (|> idx %n (format "____________slot") code.local-symbol)]
+ (p.either (let [slotC (|> idx %n (format "____________slot") code.local-identifier)]
(do @
[_ (wrap [])
memberC (Arg<?> slotC)]
@@ -70,13 +70,13 @@
## Functions
(do @
[_ (wrap [])
- #let [g! (code.local-symbol "____________")
- outL (code.local-symbol "____________outL")]
+ #let [g! (code.local-identifier "____________")
+ outL (code.local-identifier "____________outL")]
[inT+ outC] (poly.function (p.many poly.any)
(Arg<?> outL))
#let [inC+ (|> (list.size inT+) dec
(list.n/range +0)
- (list/map (|>> %n (format "____________inC") code.local-symbol)))]]
+ (list/map (|>> %n (format "____________inC") code.local-identifier)))]]
(wrap (` (function ((~ g!) (~+ inC+))
(let [(~ outL) ((~ valueC) (~+ inC+))]
(~ outC))))))
diff --git a/stdlib/source/lux/macro/poly/json.lux b/stdlib/source/lux/macro/poly/json.lux
index 7cd02657f..4217ce704 100644
--- a/stdlib/source/lux/macro/poly/json.lux
+++ b/stdlib/source/lux/macro/poly/json.lux
@@ -86,12 +86,12 @@
(with-expansions
[<basic> (do-template [<matcher> <encoder>]
[(do @
- [#let [g!_ (code.local-symbol "_______")]
+ [#let [g!_ (code.local-identifier "_______")]
_ <matcher>]
(wrap (` (: (~ (@JSON//encode inputT))
<encoder>))))]
- [(poly.exactly Any) (function ((~ g!_) (~ (code.symbol ["" "0"]))) #//.Null)]
+ [(poly.exactly Any) (function ((~ g!_) (~ (code.identifier ["" "0"]))) #//.Null)]
[(poly.sub Bit) (|>> #//.Boolean)]
[(poly.sub Nat) (:: (~! ..Codec<JSON,Nat>) (~' encode))]
[(poly.sub Int) (:: (~! ..Codec<JSON,Int>) (~' encode))]
@@ -123,9 +123,9 @@
(wrap (` (: (~ (@JSON//encode inputT))
(:: (~! Codec<JSON,Qty>) (~' encode))))))
(do @
- [#let [g!_ (code.local-symbol "_______")
- g!key (code.local-symbol "_______key")
- g!val (code.local-symbol "_______val")]
+ [#let [g!_ (code.local-identifier "_______")
+ g!key (code.local-identifier "_______key")
+ g!val (code.local-identifier "_______val")]
[_ _ =val=] (poly.apply ($_ p.seq
(poly.exactly d.Dictionary)
(poly.exactly .Text)
@@ -149,8 +149,8 @@
(wrap (` (: (~ (@JSON//encode inputT))
(|>> ((~! list/map) (~ =sub=)) row.from-list #//.Array)))))
(do @
- [#let [g!_ (code.local-symbol "_______")
- g!input (code.local-symbol "_______input")]
+ [#let [g!_ (code.local-identifier "_______")
+ g!input (code.local-identifier "_______input")]
members (poly.variant (p.many Codec<JSON,?>//encode))]
(wrap (` (: (~ (@JSON//encode inputT))
(function ((~ g!_) (~ g!input))
@@ -162,10 +162,10 @@
(list.enumerate members))))))))))
(do @
[g!encoders (poly.tuple (p.many Codec<JSON,?>//encode))
- #let [g!_ (code.local-symbol "_______")
+ #let [g!_ (code.local-identifier "_______")
g!members (|> (list.size g!encoders) dec
(list.n/range +0)
- (list/map (|>> nat/encode code.local-symbol)))]]
+ (list/map (|>> nat/encode code.local-identifier)))]]
(wrap (` (: (~ (@JSON//encode inputT))
(function ((~ g!_) [(~+ g!members)])
(//.json [(~+ (list/map (function (_ [g!member g!encode])
@@ -174,7 +174,7 @@
## Type recursion
(do @
[[selfC non-recC] (poly.recursive Codec<JSON,?>//encode)
- #let [g! (code.local-symbol "____________")]]
+ #let [g! (code.local-identifier "____________")]]
(wrap (` (: (~ (@JSON//encode inputT))
((~! ..rec-encode) (.function ((~ g!) (~ selfC))
(~ non-recC)))))))
@@ -271,7 +271,7 @@
## Type recursion
(do @
[[selfC bodyC] (poly.recursive Codec<JSON,?>//decode)
- #let [g! (code.local-symbol "____________")]]
+ #let [g! (code.local-identifier "____________")]]
(wrap (` (: (~ (@JSON//decode inputT))
(p.rec (.function ((~ g!) (~ selfC))
(~ bodyC)))))))
diff --git a/stdlib/source/lux/macro/syntax.lux b/stdlib/source/lux/macro/syntax.lux
index 1334296da..db5e086b6 100644
--- a/stdlib/source/lux/macro/syntax.lux
+++ b/stdlib/source/lux/macro/syntax.lux
@@ -55,14 +55,14 @@
_
(#error.Error ($_ text/compose "Cannot parse " <desc> (remaining-inputs tokens))))))]
- [ bit Bit #.Bit bit.Equivalence<Bit> "bit"]
- [ nat Nat #.Nat number.Equivalence<Nat> "nat"]
- [ int Int #.Int number.Equivalence<Int> "int"]
- [ rev Rev #.Rev number.Equivalence<Rev> "rev"]
- [ frac Frac #.Frac number.Equivalence<Frac> "frac"]
- [ text Text #.Text text.Equivalence<Text> "text"]
- [symbol Name #.Symbol name.Equivalence<Name> "symbol"]
- [ tag Name #.Tag name.Equivalence<Name> "tag"]
+ [ bit Bit #.Bit bit.Equivalence<Bit> "bit"]
+ [ nat Nat #.Nat number.Equivalence<Nat> "nat"]
+ [ int Int #.Int number.Equivalence<Int> "int"]
+ [ rev Rev #.Rev number.Equivalence<Rev> "rev"]
+ [ frac Frac #.Frac number.Equivalence<Frac> "frac"]
+ [ text Text #.Text text.Equivalence<Text> "text"]
+ [identifier Name #.Identifier name.Equivalence<Name> "identifier"]
+ [ tag Name #.Tag name.Equivalence<Name> "tag"]
)
(def: #export (this? ast)
@@ -106,7 +106,7 @@
_
(#error.Error ($_ text/compose "Cannot parse local " <desc> (remaining-inputs tokens))))))]
- [local-symbol #.Symbol "symbol"]
+ [local-identifier #.Identifier "identifier"]
[ local-tag #.Tag "tag"]
)
@@ -221,11 +221,11 @@
[#0 tokens]))
?parts (: (Maybe [Text (List Code) Code Code])
(case tokens
- (^ (list [_ (#.Form (list& [_ (#.Symbol ["" name])] args))]
+ (^ (list [_ (#.Form (list& [_ (#.Identifier ["" name])] args))]
body))
(#.Some name args (` {}) body)
- (^ (list [_ (#.Form (list& [_ (#.Symbol ["" name])] args))]
+ (^ (list [_ (#.Form (list& [_ (#.Identifier ["" name])] args))]
meta-data
body))
(#.Some name args meta-data body)
@@ -243,19 +243,19 @@
(^ [_ (#.Record (list [var parser]))])
(wrap [var parser])
- [_ (#.Symbol var-name)]
- (wrap [(code.symbol var-name) (` any)])
+ [_ (#.Identifier var-name)]
+ (wrap [(code.identifier var-name) (` any)])
_
- (//.fail "Syntax pattern expects records or symbols."))))
+ (//.fail "Syntax pattern expects records or identifiers."))))
args)
- #let [g!state (code.symbol ["" "*compiler*"])
+ #let [g!state (code.identifier ["" "*compiler*"])
error-msg (code.text (text/compose "Wrong syntax for " name))
export-ast (: (List Code)
(if exported?
(list (' #export))
(list)))]]
- (wrap (list (` (macro: (~+ export-ast) ((~ (code.symbol ["" name])) (~ g!tokens) (~ g!state))
+ (wrap (list (` (macro: (~+ export-ast) ((~ (code.identifier ["" name])) (~ g!tokens) (~ g!state))
(~ meta)
({(#error.Success (~ g!body))
((~ g!body) (~ g!state))
diff --git a/stdlib/source/lux/macro/syntax/common/reader.lux b/stdlib/source/lux/macro/syntax/common/reader.lux
index 2ec2ee95d..fb4238317 100644
--- a/stdlib/source/lux/macro/syntax/common/reader.lux
+++ b/stdlib/source/lux/macro/syntax/common/reader.lux
@@ -26,10 +26,10 @@
quux
(foo bar baz))}
(Syntax //.Declaration)
- (p.either (p.seq s.local-symbol
+ (p.either (p.seq s.local-identifier
(parser/wrap (list)))
- (s.form (p.seq s.local-symbol
- (p.many s.local-symbol)))))
+ (s.form (p.seq s.local-identifier
+ (p.many s.local-identifier)))))
## Annotations
(def: #export annotations
@@ -114,7 +114,7 @@
(s.local me-definition-raw
(s.form (do @
[_ (s.this (' "lux def"))
- definition-name s.local-symbol
+ definition-name s.local-identifier
[?definition-type definition-value] check^
definition-anns s.any
definition-anns (s.local (list definition-anns)
@@ -147,4 +147,4 @@
(def: #export type-variables
{#.doc "Reader for the common type var/param used by many macros."}
(Syntax (List Text))
- (s.tuple (p.some s.local-symbol)))
+ (s.tuple (p.some s.local-identifier)))
diff --git a/stdlib/source/lux/macro/syntax/common/writer.lux b/stdlib/source/lux/macro/syntax/common/writer.lux
index 114a41505..9133cdfa0 100644
--- a/stdlib/source/lux/macro/syntax/common/writer.lux
+++ b/stdlib/source/lux/macro/syntax/common/writer.lux
@@ -17,8 +17,8 @@
(def: #export (declaration declaration)
(-> //.Declaration Code)
- (` ((~ (code.local-symbol (get@ #//.declaration-name declaration)))
- (~+ (list/map code.local-symbol
+ (` ((~ (code.local-identifier (get@ #//.declaration-name declaration)))
+ (~+ (list/map code.local-identifier
(get@ #//.declaration-args declaration))))))
(def: #export (annotations anns)
@@ -27,4 +27,4 @@
(def: #export (type-variables vars)
(-> (List Text) (List Code))
- (list/map code.local-symbol vars))
+ (list/map code.local-identifier vars))