aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/lux.lux
diff options
context:
space:
mode:
authorEduardo Julian2018-07-21 22:58:54 -0400
committerEduardo Julian2018-07-21 22:58:54 -0400
commit2746f1a2d7606e3295e12e9c2e6833663658ffa8 (patch)
treeab578e1caf50a57d65c514b173be57311459786c /stdlib/source/lux.lux
parent7061c56c7b038a633389c35eccb4a2cfef5098d0 (diff)
Re-named "Symbol" to "Identifier".
Diffstat (limited to 'stdlib/source/lux.lux')
-rw-r--r--stdlib/source/lux.lux334
1 files changed, 167 insertions, 167 deletions
diff --git a/stdlib/source/lux.lux b/stdlib/source/lux.lux
index e53709ce2..9bf84ca45 100644
--- a/stdlib/source/lux.lux
+++ b/stdlib/source/lux.lux
@@ -162,9 +162,9 @@
(#Cons [[dummy-cursor (+7 ["lux" "export?"])]
[dummy-cursor (+0 #1)]]
(#Cons [[dummy-cursor (+7 ["lux" "doc"])]
- [dummy-cursor (+5 "An identifier.
+ [dummy-cursor (+5 "A name.
- It is used as part of Lux syntax to represent symbols and tags.")]]
+ It is used as part of Lux syntax to represent identifiers and tags.")]]
#Nil))))])
## (type: (Maybe a)
@@ -311,7 +311,7 @@
## (#Rev Rev)
## (#Frac Frac)
## (#Text Text)
-## (#Symbol Name)
+## (#Identifier Name)
## (#Tag Name)
## (#Form (List (w (Code' w))))
## (#Tuple (List (w (Code' w))))
@@ -333,7 +333,7 @@
Frac
(#Sum ## "lux.Text"
Text
- (#Sum ## "lux.Symbol"
+ (#Sum ## "lux.Identifier"
Name
(#Sum ## "lux.Tag"
Name
@@ -357,7 +357,7 @@
(#Cons [dummy-cursor (+5 "Rev")]
(#Cons [dummy-cursor (+5 "Frac")]
(#Cons [dummy-cursor (+5 "Text")]
- (#Cons [dummy-cursor (+5 "Symbol")]
+ (#Cons [dummy-cursor (+5 "Identifier")]
(#Cons [dummy-cursor (+5 "Tag")]
(#Cons [dummy-cursor (+5 "Form")]
(#Cons [dummy-cursor (+5 "Tuple")]
@@ -425,14 +425,14 @@
([_ text] (_ann (#Text text))))
[dummy-cursor (#Record #Nil)])
-("lux def" symbol$
+("lux def" identifier$
("lux check" (#Function Name Code)
- ([_ name] (_ann (#Symbol name))))
+ ([_ name] (_ann (#Identifier name))))
[dummy-cursor (#Record #Nil)])
-("lux def" local-symbol$
+("lux def" local-identifier$
("lux check" (#Function Text Code)
- ([_ name] (_ann (#Symbol ["" name]))))
+ ([_ name] (_ann (#Identifier ["" name]))))
[dummy-cursor (#Record #Nil)])
("lux def" tag$
@@ -827,27 +827,27 @@
("lux check" Macro
([_ tokens]
({(#Cons [_ (#Tuple (#Cons arg args'))] (#Cons body #Nil))
- (return (#Cons (_ann (#Form (#Cons (_ann (#Tuple (#Cons (_ann (#Symbol "" ""))
+ (return (#Cons (_ann (#Form (#Cons (_ann (#Tuple (#Cons (_ann (#Identifier "" ""))
(#Cons arg #Nil))))
(#Cons ({#Nil
body
_
- (_ann (#Form (#Cons (_ann (#Symbol "lux" "function''"))
+ (_ann (#Form (#Cons (_ann (#Identifier "lux" "function''"))
(#Cons (_ann (#Tuple args'))
(#Cons body #Nil)))))}
args')
#Nil))))
#Nil))
- (#Cons [_ (#Symbol "" self)] (#Cons [_ (#Tuple (#Cons arg args'))] (#Cons body #Nil)))
- (return (#Cons (_ann (#Form (#Cons (_ann (#Tuple (#Cons (_ann (#Symbol "" self))
+ (#Cons [_ (#Identifier "" self)] (#Cons [_ (#Tuple (#Cons arg args'))] (#Cons body #Nil)))
+ (return (#Cons (_ann (#Form (#Cons (_ann (#Tuple (#Cons (_ann (#Identifier "" self))
(#Cons arg #Nil))))
(#Cons ({#Nil
body
_
- (_ann (#Form (#Cons (_ann (#Symbol "lux" "function''"))
+ (_ann (#Form (#Cons (_ann (#Identifier "lux" "function''"))
(#Cons (_ann (#Tuple args'))
(#Cons body #Nil)))))}
args')
@@ -927,12 +927,12 @@
(#Cons [name
(#Cons [(_ann (#Form (#Cons [(_ann (#Text "lux check"))
(#Cons [type
- (#Cons [(_ann (#Form (#Cons [(_ann (#Symbol ["lux" "function''"]))
+ (#Cons [(_ann (#Form (#Cons [(_ann (#Identifier ["lux" "function''"]))
(#Cons [name
(#Cons [(_ann (#Tuple args))
(#Cons [body #Nil])])])])))
#Nil])])])))
- (#Cons (form$ (#Cons (symbol$ ["lux" "record$"])
+ (#Cons (form$ (#Cons (identifier$ ["lux" "record$"])
(#Cons (with-export-meta meta)
#Nil)))
#Nil)])])])))
@@ -945,7 +945,7 @@
(#Cons [type
(#Cons [body
#Nil])])])))
- (#Cons (form$ (#Cons (symbol$ ["lux" "record$"])
+ (#Cons (form$ (#Cons (identifier$ ["lux" "record$"])
(#Cons (with-export-meta meta)
#Nil)))
#Nil)])])])))
@@ -957,12 +957,12 @@
(#Cons [name
(#Cons [(_ann (#Form (#Cons [(_ann (#Text "lux check"))
(#Cons [type
- (#Cons [(_ann (#Form (#Cons [(_ann (#Symbol ["lux" "function''"]))
+ (#Cons [(_ann (#Form (#Cons [(_ann (#Identifier ["lux" "function''"]))
(#Cons [name
(#Cons [(_ann (#Tuple args))
(#Cons [body #Nil])])])])))
#Nil])])])))
- (#Cons (form$ (#Cons (symbol$ ["lux" "record$"])
+ (#Cons (form$ (#Cons (identifier$ ["lux" "record$"])
(#Cons meta
#Nil)))
#Nil)])])])))
@@ -975,7 +975,7 @@
(#Cons [type
(#Cons [body
#Nil])])])))
- (#Cons (form$ (#Cons (symbol$ ["lux" "record$"])
+ (#Cons (form$ (#Cons (identifier$ ["lux" "record$"])
(#Cons meta
#Nil)))
#Nil)])])])))
@@ -990,32 +990,32 @@
default-macro-meta
Macro
({(#Cons [_ (#Form (#Cons name args))] (#Cons body #Nil))
- (return (#Cons (form$ (#Cons (symbol$ ["lux" "def:''"])
+ (return (#Cons (form$ (#Cons (identifier$ ["lux" "def:''"])
(#Cons (form$ (#Cons name args))
(#Cons (with-macro-meta (tag$ ["lux" "Nil"]))
- (#Cons (symbol$ ["lux" "Macro"])
+ (#Cons (identifier$ ["lux" "Macro"])
(#Cons body
#Nil)))
)))
#Nil))
(#Cons [_ (#Tag ["" "export"])] (#Cons [_ (#Form (#Cons name args))] (#Cons body #Nil)))
- (return (#Cons (form$ (#Cons (symbol$ ["lux" "def:''"])
+ (return (#Cons (form$ (#Cons (identifier$ ["lux" "def:''"])
(#Cons (tag$ ["" "export"])
(#Cons (form$ (#Cons name args))
(#Cons (with-macro-meta (tag$ ["lux" "Nil"]))
- (#Cons (symbol$ ["lux" "Macro"])
+ (#Cons (identifier$ ["lux" "Macro"])
(#Cons body
#Nil)))
))))
#Nil))
(#Cons [_ (#Tag ["" "export"])] (#Cons [_ (#Form (#Cons name args))] (#Cons meta-data (#Cons body #Nil))))
- (return (#Cons (form$ (#Cons (symbol$ ["lux" "def:''"])
+ (return (#Cons (form$ (#Cons (identifier$ ["lux" "def:''"])
(#Cons (tag$ ["" "export"])
(#Cons (form$ (#Cons name args))
(#Cons (with-macro-meta meta-data)
- (#Cons (symbol$ ["lux" "Macro"])
+ (#Cons (identifier$ ["lux" "Macro"])
(#Cons body
#Nil)))
))))
@@ -1038,7 +1038,7 @@
(return tokens)
(#Cons x (#Cons y xs))
- (return (#Cons (form$ (#Cons (symbol$ ["lux" "$'"])
+ (return (#Cons (form$ (#Cons (identifier$ ["lux" "$'"])
(#Cons (form$ (#Cons (tag$ ["lux" "Apply"])
(#Cons y (#Cons x #Nil))))
xs)))
@@ -1100,7 +1100,7 @@
(def:'' (replace-syntax reps syntax)
#Nil
(#Function RepEnv (#Function Code Code))
- ({[_ (#Symbol "" name)]
+ ({[_ (#Identifier "" name)]
({(#Some replacement)
replacement
@@ -1183,11 +1183,11 @@
({#Nil
(next #Nil)
- (#Cons [_ (#Symbol "" arg-name)] args')
+ (#Cons [_ (#Identifier "" arg-name)] args')
(parse-quantified-args args' (function'' [names] (next (#Cons arg-name names))))
_
- (fail "Expected symbol.")}
+ (fail "Expected identifier.")}
args))
(def:'' (make-parameter idx)
@@ -1228,7 +1228,7 @@
(| Any
[a (List a)]))")]
#Nil)
- (let'' [self-name tokens] ({(#Cons [_ (#Symbol "" self-name)] tokens)
+ (let'' [self-name tokens] ({(#Cons [_ (#Identifier "" self-name)] tokens)
[self-name tokens]
_
@@ -1275,7 +1275,7 @@
a
(List (Self a))])")]
#Nil)
- (let'' [self-name tokens] ({(#Cons [_ (#Symbol "" self-name)] tokens)
+ (let'' [self-name tokens] ({(#Cons [_ (#Identifier "" self-name)] tokens)
[self-name tokens]
_
@@ -1374,7 +1374,7 @@
(&)")]
#Nil)
({#Nil
- (return (list (symbol$ ["lux" "Any"])))
+ (return (list (identifier$ ["lux" "Any"])))
(#Cons last prevs)
(return (list (list/fold (function'' [left right] (form$ (list (tag$ ["lux" "Product"]) left right)))
@@ -1391,7 +1391,7 @@
(|)")]
#Nil)
({#Nil
- (return (list (symbol$ ["lux" "Nothing"])))
+ (return (list (identifier$ ["lux" "Nothing"])))
(#Cons last prevs)
(return (list (list/fold (function'' [left right] (form$ (list (tag$ ["lux" "Sum"]) left right)))
@@ -1400,7 +1400,7 @@
(list/reverse tokens)))
(macro:' (function' tokens)
- (let'' [name tokens'] ({(#Cons [[_ (#Symbol ["" name])] tokens'])
+ (let'' [name tokens'] ({(#Cons [[_ (#Identifier ["" name])] tokens'])
[name tokens']
_
@@ -1411,10 +1411,10 @@
(fail "function' requires a non-empty arguments tuple.")
(#Cons [harg targs])
- (return (list (form$ (list (tuple$ (list (symbol$ ["" name])
+ (return (list (form$ (list (tuple$ (list (identifier$ ["" name])
harg))
(list/fold (function'' [arg body']
- (form$ (list (tuple$ (list (symbol$ ["" ""])
+ (form$ (list (tuple$ (list (identifier$ ["" ""])
arg))
body')))
body
@@ -1433,11 +1433,11 @@
name
(form$ (list (text$ "lux check")
type
- (form$ (list (symbol$ ["lux" "function'"])
+ (form$ (list (identifier$ ["lux" "function'"])
name
(tuple$ args)
body))))
- (form$ (#Cons (symbol$ ["lux" "record$"])
+ (form$ (#Cons (identifier$ ["lux" "record$"])
(#Cons (with-export-meta meta)
#Nil)))))))
@@ -1447,7 +1447,7 @@
(form$ (list (text$ "lux check")
type
body))
- (form$ (#Cons (symbol$ ["lux" "record$"])
+ (form$ (#Cons (identifier$ ["lux" "record$"])
(#Cons (with-export-meta meta)
#Nil)))))))
@@ -1457,11 +1457,11 @@
name
(form$ (list (text$ "lux check")
type
- (form$ (list (symbol$ ["lux" "function'"])
+ (form$ (list (identifier$ ["lux" "function'"])
name
(tuple$ args)
body))))
- (form$ (#Cons (symbol$ ["lux" "record$"])
+ (form$ (#Cons (identifier$ ["lux" "record$"])
(#Cons meta
#Nil)))))))
@@ -1469,7 +1469,7 @@
(return (list (form$ (list (text$ "lux def")
name
(form$ (list (text$ "lux check") type body))
- (form$ (#Cons (symbol$ ["lux" "record$"])
+ (form$ (#Cons (identifier$ ["lux" "record$"])
(#Cons meta
#Nil)))))))
@@ -1650,17 +1650,17 @@
(macro:' (do tokens)
({(#Cons monad (#Cons [_ (#Tuple bindings)] (#Cons body #Nil)))
- (let' [g!wrap (symbol$ ["" "wrap"])
- g!bind (symbol$ ["" " bind "])
+ (let' [g!wrap (identifier$ ["" "wrap"])
+ g!bind (identifier$ ["" " bind "])
body' (list/fold ("lux check" (-> (& Code Code) Code Code)
(function' [binding body']
(let' [[var value] binding]
({[_ (#Tag "" "let")]
- (form$ (list (symbol$ ["lux" "let'"]) value body'))
+ (form$ (list (identifier$ ["lux" "let'"]) value body'))
_
(form$ (list g!bind
- (form$ (list (tuple$ (list (symbol$ ["" ""]) var)) body'))
+ (form$ (list (tuple$ (list (identifier$ ["" ""]) var)) body'))
value))}
var))))
body
@@ -1805,7 +1805,7 @@
#None}
def-meta)))
-(def:''' (resolve-global-symbol full-name state)
+(def:''' (resolve-global-identifier full-name state)
#Nil
(-> Name ($' Meta Name))
(let' [[module name] full-name
@@ -1815,7 +1815,7 @@
#scope-type-vars scope-type-vars} state]
({(#Some {#module-hash _ #module-aliases _ #definitions definitions #imports _ #tags tags #types types #module-annotations _ #module-state _})
({(#Some [def-type def-meta def-value])
- ({(#Some [_ (#Symbol real-name)])
+ ({(#Some [_ (#Identifier real-name)])
(#Right [state real-name])
_
@@ -1839,7 +1839,7 @@
(#Cons lastI inits)
(do Monad<Meta>
- [lastO ({[_ (#Form (#Cons [[_ (#Symbol ["" "~+"])] (#Cons [spliced #Nil])]))]
+ [lastO ({[_ (#Form (#Cons [[_ (#Identifier ["" "~+"])] (#Cons [spliced #Nil])]))]
(let' [[[_module-name _ _] _] spliced]
(wrap spliced))
@@ -1850,9 +1850,9 @@
lastI)]
(monad/fold Monad<Meta>
(function' [leftI rightO]
- ({[_ (#Form (#Cons [[_ (#Symbol ["" "~+"])] (#Cons [spliced #Nil])]))]
+ ({[_ (#Form (#Cons [[_ (#Identifier ["" "~+"])] (#Cons [spliced #Nil])]))]
(let' [[[_module-name _ _] _] spliced]
- (wrap (form$ (list (symbol$ ["lux" "splice-helper"])
+ (wrap (form$ (list (identifier$ ["lux" "splice-helper"])
spliced
rightO))))
@@ -1908,26 +1908,26 @@
module)]
(return (wrap-meta (form$ (list (tag$ ["lux" "Tag"]) (tuple$ (list (text$ module') (text$ name))))))))
- [#1 [_ (#Symbol [module name])]]
+ [#1 [_ (#Identifier [module name])]]
(do Monad<Meta>
[real-name ({""
(if (text/= "" subst)
(wrap [module name])
- (resolve-global-symbol [subst name]))
+ (resolve-global-identifier [subst name]))
_
(wrap [module name])}
module)
#let [[module name] real-name]]
- (return (wrap-meta (form$ (list (tag$ ["lux" "Symbol"]) (tuple$ (list (text$ module) (text$ name))))))))
+ (return (wrap-meta (form$ (list (tag$ ["lux" "Identifier"]) (tuple$ (list (text$ module) (text$ name))))))))
- [#0 [_ (#Symbol [module name])]]
- (return (wrap-meta (form$ (list (tag$ ["lux" "Symbol"]) (tuple$ (list (text$ module) (text$ name)))))))
+ [#0 [_ (#Identifier [module name])]]
+ (return (wrap-meta (form$ (list (tag$ ["lux" "Identifier"]) (tuple$ (list (text$ module) (text$ name)))))))
- [#1 [_ (#Form (#Cons [[_ (#Symbol ["" "~"])] (#Cons [unquoted #Nil])]))]]
+ [#1 [_ (#Form (#Cons [[_ (#Identifier ["" "~"])] (#Cons [unquoted #Nil])]))]]
(return unquoted)
- [#1 [_ (#Form (#Cons [[_ (#Symbol ["" "~!"])] (#Cons [dependent #Nil])]))]]
+ [#1 [_ (#Form (#Cons [[_ (#Identifier ["" "~!"])] (#Cons [dependent #Nil])]))]]
(do Monad<Meta>
[independent (untemplate replace? subst dependent)]
(wrap (wrap-meta (form$ (list (tag$ ["lux" "Form"])
@@ -1935,7 +1935,7 @@
(untemplate-text subst)
independent)))))))
- [#1 [_ (#Form (#Cons [[_ (#Symbol ["" "~'"])] (#Cons [keep-quoted #Nil])]))]]
+ [#1 [_ (#Form (#Cons [[_ (#Identifier ["" "~'"])] (#Cons [keep-quoted #Nil])]))]]
(untemplate #0 subst keep-quoted)
[_ [meta (#Form elems)]]
@@ -2007,7 +2007,7 @@
[current-module current-module-name
=template (untemplate #1 current-module template)]
(wrap (list (form$ (list (text$ "lux check")
- (symbol$ ["lux" "Code"])
+ (identifier$ ["lux" "Code"])
=template)))))
_
@@ -2023,7 +2023,7 @@
({(#Cons template #Nil)
(do Monad<Meta>
[=template (untemplate #1 "" template)]
- (wrap (list (form$ (list (text$ "lux check") (symbol$ ["lux" "Code"]) =template)))))
+ (wrap (list (form$ (list (text$ "lux check") (identifier$ ["lux" "Code"]) =template)))))
_
(fail "Wrong syntax for `")}
@@ -2036,7 +2036,7 @@
({(#Cons template #Nil)
(do Monad<Meta>
[=template (untemplate #0 "" template)]
- (wrap (list (form$ (list (text$ "lux check") (symbol$ ["lux" "Code"]) =template)))))
+ (wrap (list (form$ (list (text$ "lux check") (identifier$ ["lux" "Code"]) =template)))))
_
(fail "Wrong syntax for '")}
@@ -2108,7 +2108,7 @@
(def:''' (get-name x)
#Nil
(-> Code ($' Maybe Name))
- ({[_ (#Symbol sname)]
+ ({[_ (#Identifier sname)]
(#Some sname)
_
@@ -2128,7 +2128,7 @@
(def:''' (get-short x)
#Nil
(-> Code ($' Maybe Text))
- ({[_ (#Symbol "" sname)]
+ ({[_ (#Identifier "" sname)]
(#Some sname)
_
@@ -2148,7 +2148,7 @@
(def:''' (apply-template env template)
#Nil
(-> RepEnv Code Code)
- ({[_ (#Symbol "" sname)]
+ ({[_ (#Identifier "" sname)]
({(#Some subst)
subst
@@ -2633,7 +2633,7 @@
(get-meta ["lux" "export?"] def-meta))
_
- ({(#Some [_ (#Symbol [r-module r-name])])
+ ({(#Some [_ (#Identifier [r-module r-name])])
(find-macro' modules current-module r-module r-name)
_
@@ -2702,7 +2702,7 @@
(def:''' (macro-expand-once token)
#Nil
(-> Code ($' Meta ($' List Code)))
- ({[_ (#Form (#Cons [_ (#Symbol macro-name)] args))]
+ ({[_ (#Form (#Cons [_ (#Identifier macro-name)] args))]
(do Monad<Meta>
[macro-name' (normalize macro-name)
?macro (find-macro macro-name')]
@@ -2720,7 +2720,7 @@
(def:''' (macro-expand token)
#Nil
(-> Code ($' Meta ($' List Code)))
- ({[_ (#Form (#Cons [_ (#Symbol macro-name)] args))]
+ ({[_ (#Form (#Cons [_ (#Identifier macro-name)] args))]
(do Monad<Meta>
[macro-name' (normalize macro-name)
?macro (find-macro macro-name')]
@@ -2741,7 +2741,7 @@
(def:''' (macro-expand-all syntax)
#Nil
(-> Code ($' Meta ($' List Code)))
- ({[_ (#Form (#Cons [_ (#Symbol macro-name)] args))]
+ ({[_ (#Form (#Cons [_ (#Identifier macro-name)] args))]
(do Monad<Meta>
[macro-name' (normalize macro-name)
?macro (find-macro macro-name')]
@@ -2754,7 +2754,7 @@
#None
(do Monad<Meta>
[args' (monad/map Monad<Meta> macro-expand-all args)]
- (wrap (list (form$ (#Cons (symbol$ macro-name) (list/join args'))))))}
+ (wrap (list (form$ (#Cons (identifier$ macro-name) (list/join args'))))))}
?macro))
[_ (#Form members)]
@@ -2802,7 +2802,7 @@
#Nil))))]
(` ("lux in-module" (~ (text$ module)) (~ (walk-type type'))))
- [_ (#Form (#Cons [_ (#Symbol ["" ":~"])] (#Cons expression #Nil)))]
+ [_ (#Form (#Cons [_ (#Identifier ["" ":~"])] (#Cons expression #Nil)))]
expression
[_ (#Form (#Cons type-fn args))]
@@ -2938,7 +2938,7 @@
#seed (n/+ +1 seed) #expected expected
#cursor cursor #extensions extensions
#scope-type-vars scope-type-vars}
- (symbol$ ["" ($_ text/compose "__gensym__" prefix (nat/encode seed))]))}
+ (identifier$ ["" ($_ text/compose "__gensym__" prefix (nat/encode seed))]))}
state))
(macro:' #export (Rec tokens)
@@ -2947,7 +2947,7 @@
## A name has to be given to the whole type, to use it within its body.
(Rec Self
[Int (List Self)])")])
- ({(#Cons [_ (#Symbol "" name)] (#Cons body #Nil))
+ ({(#Cons [_ (#Identifier "" name)] (#Cons body #Nil))
(let' [body' (replace-syntax (list [name (` (#.Apply (~ (make-parameter +1)) (~ (make-parameter +0))))])
(update-parameters body))]
(return (list (` (#.Apply .Nothing (#.UnivQ #.Nil (~ body')))))))
@@ -2965,7 +2965,7 @@
(log! \"#3\")
\"YOLO\")")])
({(#Cons value actions)
- (let' [dummy (symbol$ ["" ""])]
+ (let' [dummy (identifier$ ["" ""])]
(return (list (list/fold ("lux check" (-> Code Code Code)
(function' [pre post] (` ({(~ dummy) (~ post)}
(~ pre)))))
@@ -3047,7 +3047,7 @@
[_ (#Text value)]
($_ text/compose "\"" value "\"")
- [_ (#Symbol [prefix name])]
+ [_ (#Identifier [prefix name])]
(if (text/= "" prefix)
name
($_ text/compose prefix "." name))
@@ -3082,18 +3082,18 @@
(def:' (expander branches)
(-> (List Code) (Meta (List Code)))
- ({(#Cons [_ (#Form (#Cons [_ (#Symbol macro-name)] macro-args))]
+ ({(#Cons [_ (#Form (#Cons [_ (#Identifier macro-name)] macro-args))]
(#Cons body
branches'))
(do Monad<Meta>
[??? (macro? macro-name)]
(if ???
(do Monad<Meta>
- [init-expansion (macro-expand-once (form$ (list& (symbol$ macro-name) (form$ macro-args) body branches')))]
+ [init-expansion (macro-expand-once (form$ (list& (identifier$ macro-name) (form$ macro-args) body branches')))]
(expander init-expansion))
(do Monad<Meta>
[sub-expansion (expander branches')]
- (wrap (list& (form$ (list& (symbol$ macro-name) macro-args))
+ (wrap (list& (form$ (list& (identifier$ macro-name) macro-args))
body
sub-expansion)))))
@@ -3191,10 +3191,10 @@
_
(fail "Wrong syntax for ^or")))
-(def:' (symbol? code)
+(def:' (identifier? code)
(-> Code Bit)
(case code
- [_ (#Symbol _)]
+ [_ (#Identifier _)]
#1
_
@@ -3214,7 +3214,7 @@
(list/fold (: (-> [Code Code] Code Code)
(function' [lr body']
(let' [[l r] lr]
- (if (symbol? l)
+ (if (identifier? l)
(` ({(~ l) (~ body')} (~ r)))
(` (case (~ r) (~ l) (~ body')))))))
body)
@@ -3236,23 +3236,23 @@
(function (const x y) x))")])
(case (: (Maybe [Text Code (List Code) Code])
(case tokens
- (^ (list [_ (#Form (list& [_ (#Symbol ["" name])] head tail))] body))
+ (^ (list [_ (#Form (list& [_ (#Identifier ["" name])] head tail))] body))
(#Some name head tail body)
_
#None))
(#Some g!name head tail body)
- (let [g!blank (symbol$ ["" ""])
- g!name (symbol$ ["" g!name])
+ (let [g!blank (identifier$ ["" ""])
+ g!name (identifier$ ["" g!name])
body+ (list/fold (: (-> Code Code Code)
(function' [arg body']
- (if (symbol? arg)
+ (if (identifier? arg)
(` ([(~ g!blank) (~ arg)] (~ body')))
(` ([(~ g!blank) (~ g!blank)]
(case (~ g!blank) (~ arg) (~ body')))))))
body
(list/reverse tail))]
- (return (list (if (symbol? head)
+ (return (list (if (identifier? head)
(` ([(~ g!name) (~ head)] (~ body+)))
(` ([(~ g!name) (~ g!blank)] (case (~ g!blank) (~ head) (~ body+))))))))
@@ -3283,7 +3283,7 @@
[_ (#Tag [prefix name])]
(meta-code ["lux" "Tag"] (` [(~ (text$ prefix)) (~ (text$ name))]))
- (^or [_ (#Form _)] [_ (#Symbol _)])
+ (^or [_ (#Form _)] [_ (#Identifier _)])
code
[_ (#Tuple xs)]
@@ -3436,30 +3436,30 @@
(^template [<tag>]
(^ (list [_ (<tag> [prefix name])]))
(return (list (` [(~ (text$ prefix)) (~ (text$ name))]))))
- ([#Symbol] [#Tag])
+ ([#Identifier] [#Tag])
_
(fail \"Wrong syntax for name-for\")))")])
(let [[exported? tokens] (export^ tokens)
name+args+meta+body?? (: (Maybe [Name (List Code) Code Code])
(case tokens
- (^ (list [_ (#Form (list& [_ (#Symbol name)] args))] body))
+ (^ (list [_ (#Form (list& [_ (#Identifier name)] args))] body))
(#Some [name args (` {}) body])
- (^ (list [_ (#Symbol name)] body))
+ (^ (list [_ (#Identifier name)] body))
(#Some [name #Nil (` {}) body])
- (^ (list [_ (#Form (list& [_ (#Symbol name)] args))] [meta-rec-cursor (#Record meta-rec-parts)] body))
+ (^ (list [_ (#Form (list& [_ (#Identifier name)] args))] [meta-rec-cursor (#Record meta-rec-parts)] body))
(#Some [name args [meta-rec-cursor (#Record meta-rec-parts)] body])
- (^ (list [_ (#Symbol name)] [meta-rec-cursor (#Record meta-rec-parts)] body))
+ (^ (list [_ (#Identifier name)] [meta-rec-cursor (#Record meta-rec-parts)] body))
(#Some [name #Nil [meta-rec-cursor (#Record meta-rec-parts)] body])
_
#None))]
(case name+args+meta+body??
(#Some [name args meta body])
- (let [name (symbol$ name)
+ (let [name (identifier$ name)
def-sig (case args
#Nil name
_ (` ((~ name) (~+ args))))]
@@ -3491,16 +3491,16 @@
(let [[exported? tokens'] (export^ tokens)
?parts (: (Maybe [Name (List Code) Code (List Code)])
(case tokens'
- (^ (list& [_ (#Form (list& [_ (#Symbol name)] args))] [meta-rec-cursor (#Record meta-rec-parts)] sigs))
+ (^ (list& [_ (#Form (list& [_ (#Identifier name)] args))] [meta-rec-cursor (#Record meta-rec-parts)] sigs))
(#Some name args [meta-rec-cursor (#Record meta-rec-parts)] sigs)
- (^ (list& [_ (#Symbol name)] [meta-rec-cursor (#Record meta-rec-parts)] sigs))
+ (^ (list& [_ (#Identifier name)] [meta-rec-cursor (#Record meta-rec-parts)] sigs))
(#Some name #Nil [meta-rec-cursor (#Record meta-rec-parts)] sigs)
- (^ (list& [_ (#Form (list& [_ (#Symbol name)] args))] sigs))
+ (^ (list& [_ (#Form (list& [_ (#Identifier name)] args))] sigs))
(#Some name args (` {}) sigs)
- (^ (list& [_ (#Symbol name)] sigs))
+ (^ (list& [_ (#Identifier name)] sigs))
(#Some name #Nil (` {}) sigs)
_
@@ -3515,14 +3515,14 @@
(: (-> Code (Meta [Text Code]))
(function (_ token)
(case token
- (^ [_ (#Form (list [_ (#Text "lux check")] type [_ (#Symbol ["" name])]))])
+ (^ [_ (#Form (list [_ (#Text "lux check")] type [_ (#Identifier ["" name])]))])
(wrap [name type])
_
(fail "Signatures require typed members!"))))
(list/join sigs')))
#let [[_module _name] name+
- def-name (symbol$ name)
+ def-name (identifier$ name)
sig-type (record$ (list/map (: (-> [Text Code] [Code Code])
(function (_ [m-name m-type])
[(tag$ ["" m-name]) m-type]))
@@ -3615,7 +3615,7 @@
(default 20 #.None) => 20"}
(case tokens
(^ (list else maybe))
- (let [g!temp (: Code [dummy-cursor (#Symbol ["" ""])])
+ (let [g!temp (: Code [dummy-cursor (#Identifier ["" ""])])
code (` (case (~ maybe)
(#.Some (~ g!temp))
(~ g!temp)
@@ -3867,7 +3867,7 @@
(: (-> Code (Meta [Code Code]))
(function (_ token)
(case token
- (^ [_ (#Form (list [_ (#Text "lux def")] [_ (#Symbol "" tag-name)] value meta))])
+ (^ [_ (#Form (list [_ (#Text "lux def")] [_ (#Identifier "" tag-name)] value meta))])
(case (get tag-name tag-mappings)
(#Some tag)
(wrap [tag value])
@@ -3918,21 +3918,21 @@
(case ?parts
(#Some [name args type meta definitions])
(case (case name
- [_ (#Symbol ["" "_"])]
+ [_ (#Identifier ["" "_"])]
(case type
- (^ [_ (#Form (list& [_ (#Symbol [_ sig-name])] sig-args))])
+ (^ [_ (#Form (list& [_ (#Identifier [_ sig-name])] sig-args))])
(case (: (Maybe (List Text))
(monad/map Monad<Maybe>
(function (_ sa)
(case sa
- [_ (#Symbol [_ arg-name])]
+ [_ (#Identifier [_ arg-name])]
(#Some arg-name)
_
#None))
sig-args))
(^ (#Some params))
- (#Some (symbol$ ["" ($_ text/compose sig-name "<" (|> params (interpose ",") text/join) ">")]))
+ (#Some (identifier$ ["" ($_ text/compose sig-name "<" (|> params (interpose ",") text/join) ">")]))
_
#None)
@@ -3983,22 +3983,22 @@
[#0 tokens'])
parts (: (Maybe [Text (List Code) Code (List Code)])
(case tokens'
- (^ (list [_ (#Symbol "" name)] [meta-cursor (#Record meta-parts)] [type-cursor (#Record type-parts)]))
+ (^ (list [_ (#Identifier "" name)] [meta-cursor (#Record meta-parts)] [type-cursor (#Record type-parts)]))
(#Some [name #Nil [meta-cursor (#Record meta-parts)] (list [type-cursor (#Record type-parts)])])
- (^ (list& [_ (#Symbol "" name)] [meta-cursor (#Record meta-parts)] type-code1 type-codes))
+ (^ (list& [_ (#Identifier "" name)] [meta-cursor (#Record meta-parts)] type-code1 type-codes))
(#Some [name #Nil [meta-cursor (#Record meta-parts)] (#Cons type-code1 type-codes)])
- (^ (list& [_ (#Symbol "" name)] type-codes))
+ (^ (list& [_ (#Identifier "" name)] type-codes))
(#Some [name #Nil (` {}) type-codes])
- (^ (list [_ (#Form (#Cons [_ (#Symbol "" name)] args))] [meta-cursor (#Record meta-parts)] [type-cursor (#Record type-parts)]))
+ (^ (list [_ (#Form (#Cons [_ (#Identifier "" name)] args))] [meta-cursor (#Record meta-parts)] [type-cursor (#Record type-parts)]))
(#Some [name args [meta-cursor (#Record meta-parts)] (list [type-cursor (#Record type-parts)])])
- (^ (list& [_ (#Form (#Cons [_ (#Symbol "" name)] args))] [meta-cursor (#Record meta-parts)] type-code1 type-codes))
+ (^ (list& [_ (#Form (#Cons [_ (#Identifier "" name)] args))] [meta-cursor (#Record meta-parts)] type-code1 type-codes))
(#Some [name args [meta-cursor (#Record meta-parts)] (#Cons type-code1 type-codes)])
- (^ (list& [_ (#Form (#Cons [_ (#Symbol "" name)] args))] type-codes))
+ (^ (list& [_ (#Form (#Cons [_ (#Identifier "" name)] args))] type-codes))
(#Some [name args (` {}) type-codes])
_
@@ -4008,7 +4008,7 @@
(do Monad<Meta>
[type+tags?? (unfold-type-def type-codes)
module-name current-module-name]
- (let [type-name (symbol$ ["" name])
+ (let [type-name (identifier$ ["" name])
[type tags??] type+tags??
type-meta (: Code
(case tags??
@@ -4021,8 +4021,8 @@
type' (: (Maybe Code)
(if rec?
(if (empty? args)
- (let [g!param (symbol$ ["" ""])
- prime-name (symbol$ ["" name])
+ (let [g!param (identifier$ ["" ""])
+ prime-name (identifier$ ["" name])
type+ (replace-syntax (list [name (` ((~ prime-name) .Nothing))]) type)]
(#Some (` ((All (~ prime-name) [(~ g!param)] (~ type+))
.Nothing))))
@@ -4076,11 +4076,11 @@
(: (-> Code (Meta Text))
(function (_ def)
(case def
- [_ (#Symbol ["" name])]
+ [_ (#Identifier ["" name])]
(return name)
_
- (fail "only/exclude requires symbols."))))
+ (fail "only/exclude requires identifiers."))))
defs))
(def: (parse-referrals tokens)
@@ -4116,11 +4116,11 @@
[structs' (monad/map Monad<Meta>
(function (_ struct)
(case struct
- [_ (#Symbol ["" struct-name])]
+ [_ (#Identifier ["" struct-name])]
(return struct-name)
_
- (fail "Expected all structures of opening form to be symbols.")))
+ (fail "Expected all structures of opening form to be identifiers.")))
structs)
next+remainder (parse-openings parts')]
(let [[next remainder] next+remainder]
@@ -4216,7 +4216,7 @@
(: (-> Code (Meta (List Importation)))
(function (_ token)
(case token
- [_ (#Symbol ["" m-name])]
+ [_ (#Identifier ["" m-name])]
(do Monad<Meta>
[m-name (clean-module nested? relative-root m-name)]
(wrap (list {#import-name m-name
@@ -4224,7 +4224,7 @@
#import-refer {#refer-defs #All
#refer-open (list)}})))
- (^ [_ (#Tuple (list& [_ (#Symbol ["" m-name])] extra))])
+ (^ [_ (#Tuple (list& [_ (#Identifier ["" m-name])] extra))])
(do Monad<Meta>
[import-name (clean-module nested? relative-root m-name)
referral+extra (parse-referrals extra)
@@ -4240,7 +4240,7 @@
#refer-open openings}}
sub-imports))))
- (^ [_ (#Tuple (list& [_ (#Text alias)] [_ (#Symbol ["" m-name])] extra))])
+ (^ [_ (#Tuple (list& [_ (#Text alias)] [_ (#Identifier ["" m-name])] extra))])
(do Monad<Meta>
[import-name (clean-module nested? relative-root m-name)
referral+extra (parse-referrals extra)
@@ -4501,7 +4501,7 @@
[g!temp (gensym "temp")]
(wrap (list& g!temp (` (..^open (~ g!temp) (~ (text$ alias)) (~ body))) branches)))
- (^ (list [_ (#Symbol name)] [_ (#Text alias)] body))
+ (^ (list [_ (#Identifier name)] [_ (#Text alias)] body))
(do Monad<Meta>
[init-type (find-type name)
struct-evidence (resolve-type-tags init-type)]
@@ -4515,7 +4515,7 @@
(function (recur source [tags members] target)
(let [pattern (record$ (list/map (function (_ [t-module t-name])
[(tag$ [t-module t-name])
- (symbol$ ["" (de-alias t-name alias)])])
+ (identifier$ ["" (de-alias t-name alias)])])
tags))]
(do Monad<Meta>
[enhanced-target (monad/fold Monad<Meta>
@@ -4532,7 +4532,7 @@
(wrap enhanced-target))))
target
(zip2 tags members))]
- (wrap (` ({(~ pattern) (~ enhanced-target)} (~ (symbol$ source)))))))))
+ (wrap (` ({(~ pattern) (~ enhanced-target)} (~ (identifier$ source)))))))))
name tags&members body)]
(wrap (list full-body)))))
@@ -4636,7 +4636,7 @@
(return (list/join decls')))
_
- (return (list (` ("lux def" (~ (symbol$ ["" (de-alias name alias)]))
+ (return (list (` ("lux def" (~ (identifier$ ["" (de-alias name alias)]))
(~ source+)
[(~ cursor-code) (#.Record #Nil)])))))))
@@ -4652,11 +4652,11 @@
(case tokens
(^ (list [_ (#Text alias)] struct))
(case struct
- [_ (#Symbol struct-name)]
+ [_ (#Identifier struct-name)]
(do Monad<Meta>
[struct-type (find-type struct-name)
output (resolve-type-tags struct-type)
- #let [source (symbol$ struct-name)]]
+ #let [source (identifier$ struct-name)]]
(case output
(#Some [tags members])
(do Monad<Meta>
@@ -4774,17 +4774,17 @@
(wrap (list)))
#let [defs (list/map (: (-> Text Code)
(function (_ def)
- (` ("lux def" (~ (symbol$ ["" def]))
- (~ (symbol$ [module-name def]))
+ (` ("lux def" (~ (identifier$ ["" def]))
+ (~ (identifier$ [module-name def]))
[(~ cursor-code)
(#.Record (#Cons [[(~ cursor-code) (#.Tag ["lux" "alias"])]
- [(~ cursor-code) (#.Symbol [(~ (text$ module-name)) (~ (text$ def))])]]
+ [(~ cursor-code) (#.Identifier [(~ (text$ module-name)) (~ (text$ def))])]]
#Nil))]))))
defs')
openings (join-map (: (-> Openings (List Code))
(function (_ [alias structs])
(list/map (function (_ name)
- (` (open: (~ (text$ alias)) (~ (symbol$ [module-name name])))))
+ (` (open: (~ (text$ alias)) (~ (identifier$ [module-name name])))))
structs)))
r-opens)]]
(wrap (list/compose defs openings))
@@ -4808,15 +4808,15 @@
(list (' #*))
(#Only defs)
- (list (form$ (list& (' #+) (list/map local-symbol$ defs))))
+ (list (form$ (list& (' #+) (list/map local-identifier$ defs))))
(#Exclude defs)
- (list (form$ (list& (' #-) (list/map local-symbol$ defs))))
+ (list (form$ (list& (' #-) (list/map local-identifier$ defs))))
#Nothing
(list)))
openings (list/map (function (_ [alias structs])
- (form$ (list& (text$ alias) (list/map local-symbol$ structs))))
+ (form$ (list& (text$ alias) (list/map local-identifier$ structs))))
r-opens)]
(` (..refer (~ (text$ module-name))
(~+ localizations)
@@ -4874,11 +4874,11 @@
## Also allows using that value as a function.
(:: Codec<Text,Int> encode 123)"}
(case tokens
- (^ (list struct [_ (#Symbol member)]))
- (return (list (` (let [(^open ".") (~ struct)] (~ (symbol$ member))))))
+ (^ (list struct [_ (#Identifier member)]))
+ (return (list (` (let [(^open ".") (~ struct)] (~ (identifier$ member))))))
- (^ (list& struct [_ (#Symbol member)] args))
- (return (list (` ((let [(^open ".") (~ struct)] (~ (symbol$ member))) (~+ args)))))
+ (^ (list& struct [_ (#Identifier member)] args))
+ (return (list (` ((let [(^open ".") (~ struct)] (~ (identifier$ member))) (~+ args)))))
_
(fail "Wrong syntax for ::")))
@@ -5130,7 +5130,7 @@
[#Rev]
[#Frac]
[#Text]
- [#Symbol]
+ [#Identifier]
[#Tag])
(^template [<tag>]
@@ -5241,7 +5241,7 @@
[#Int int/encode]
[#Frac frac/encode]
[#Text text/encode]
- [#Symbol name/encode]
+ [#Identifier name/encode]
[#Tag tag/encode])
(^template [<tag> <open> <close> <prep>]
@@ -5349,7 +5349,7 @@
(` (#Apply (~ (type-to-code arg)) (~ (type-to-code fun))))
(#Named [module name] type)
- (symbol$ [module name])))
+ (identifier$ [module name])))
(macro: #export (loop tokens)
{#.doc (doc "Allows arbitrary looping, using the \"recur\" form to re-start the loop."
@@ -5372,7 +5372,7 @@
(#.Some [name bindings body])
(^ (list [_ (#Tuple bindings)] body))
- (#.Some [(symbol$ ["" "recur"]) bindings body])
+ (#.Some [(identifier$ ["" "recur"]) bindings body])
_
#.None)]
@@ -5381,7 +5381,7 @@
(let [pairs (as-pairs bindings)
vars (list/map first pairs)
inits (list/map second pairs)]
- (if (every? symbol? inits)
+ (if (every? identifier? inits)
(do Monad<Meta>
[inits' (: (Meta (List Name))
(case (monad/map Monad<Maybe> get-name inits)
@@ -5432,7 +5432,7 @@
g!_ (gensym "_")
#let [[idx tags exported? type] output
slot-pairings (list/map (: (-> Name [Text Code])
- (function (_ [module name]) [name (symbol$ ["" name])]))
+ (function (_ [module name]) [name (identifier$ ["" name])]))
(list& hslot tslots))
pattern (record$ (list/map (: (-> Name [Code Code])
(function (_ [module name])
@@ -5452,7 +5452,7 @@
(^or [_ (#Bit _)] [_ (#Nat _)] [_ (#Int _)] [_ (#Rev _)] [_ (#Frac _)] [_ (#Text _)] [_ (#Tag _)])
(#Some (list target))
- [_ (#Symbol [prefix name])]
+ [_ (#Identifier [prefix name])]
(if (and (text/= "" prefix)
(text/= label name))
(#Some tokens)
@@ -5501,18 +5501,18 @@
[(frac 123.0) "123.0" [_ (#.Frac 123.0)]]
[(text "\n") "\"\\n\"" [_ (#.Text "\n")]]
[(tag ["yolo" "lol"]) "#yolo.lol" [_ (#.Tag ["yolo" "lol"])]]
- [(symbol ["yolo" "lol"]) "yolo.lol" [_ (#.Symbol ["yolo" "lol"])]]
+ [(identifier ["yolo" "lol"]) "yolo.lol" [_ (#.Identifier ["yolo" "lol"])]]
[(form (list (bit #1) (int 123))) "(#1 123)" (^ [_ (#.Form (list [_ (#.Bit #1)] [_ (#.Int 123)]))])]
[(tuple (list (bit #1) (int 123))) "[#1 123]" (^ [_ (#.Tuple (list [_ (#.Bit #1)] [_ (#.Int 123)]))])]
[(record (list [(bit #1) (int 123)])) "{#1 123}" (^ [_ (#.Record (list [[_ (#.Bit #1)] [_ (#.Int 123)]]))])]
[(local-tag "lol") "#lol" [_ (#.Tag ["" "lol"])]]
- [(local-symbol "lol") "lol" [_ (#.Symbol ["" "lol"])]]
+ [(local-identifier "lol") "lol" [_ (#.Identifier ["" "lol"])]]
)]
(test-all <tests>))))}
(case tokens
(^ (list& [_ (#Tuple bindings)] bodies))
(case bindings
- (^ (list& [_ (#Symbol ["" var-name])] macro-expr bindings'))
+ (^ (list& [_ (#Identifier ["" var-name])] macro-expr bindings'))
(do Monad<Meta>
[expansion (macro-expand-once macro-expr)]
(case (place-tokens var-name expansion (` (.with-expansions
@@ -5574,7 +5574,7 @@
(def: (anti-quote token)
(-> Code (Meta Code))
(case token
- [_ (#Symbol [def-prefix def-name])]
+ [_ (#Identifier [def-prefix def-name])]
(if (text/= "" def-prefix)
(:: Monad<Meta> return token)
(anti-quote-def [def-prefix def-name]))
@@ -5693,7 +5693,7 @@
(fail "Wrong syntax for ^multi")))
(macro: #export (name-for tokens)
- {#.doc (doc "Given a symbol or a tag, gives back a 2 tuple with the prefix and name parts, both as Text."
+ {#.doc (doc "Given an identifier or a tag, gives back a 2 tuple with the prefix and name parts, both as Text."
(name-for #.doc)
"=>"
["lux" "doc"])}
@@ -5701,7 +5701,7 @@
(^template [<tag>]
(^ (list [_ (<tag> [prefix name])]))
(return (list (` [(~ (text$ prefix)) (~ (text$ name))]))))
- ([#Symbol] [#Tag])
+ ([#Identifier] [#Tag])
_
(fail "Wrong syntax for name-for")))
@@ -5780,8 +5780,8 @@
+0
(to-list set))))}
(case tokens
- (^ (list& [_meta (#Form (list [_ (#Symbol ["" name])] pattern))] body branches))
- (let [g!whole (symbol$ ["" name])]
+ (^ (list& [_meta (#Form (list [_ (#Identifier ["" name])] pattern))] body branches))
+ (let [g!whole (identifier$ ["" name])]
(return (list& g!whole
(` (case (~ g!whole) (~ pattern) (~ body)))
branches)))
@@ -5795,8 +5795,8 @@
(^|> value [inc (n/% +10) (n/max +1)])
(foo value)))}
(case tokens
- (^ (list& [_meta (#Form (list [_ (#Symbol ["" name])] [_ (#Tuple steps)]))] body branches))
- (let [g!name (symbol$ ["" name])]
+ (^ (list& [_meta (#Form (list [_ (#Identifier ["" name])] [_ (#Tuple steps)]))] body branches))
+ (let [g!name (identifier$ ["" name])]
(return (list& g!name
(` (let [(~ g!name) (|> (~ g!name) (~+ steps))]
(~ body)))
@@ -5838,7 +5838,7 @@
"=="
Int)}
(case tokens
- (^ (list [_ (#Symbol var-name)]))
+ (^ (list [_ (#Identifier var-name)]))
(do Monad<Meta>
[var-type (find-type var-name)]
(wrap (list (type-to-code var-type))))
@@ -5849,12 +5849,12 @@
(def: (parse-complex-declaration tokens)
(-> (List Code) (Meta [[Text (List Text)] (List Code)]))
(case tokens
- (^ (list& [_ (#Form (list& [_ (#Symbol ["" name])] args'))] tokens'))
+ (^ (list& [_ (#Form (list& [_ (#Identifier ["" name])] args'))] tokens'))
(do Monad<Meta>
[args (monad/map Monad<Meta>
(function (_ arg')
(case arg'
- [_ (#Symbol ["" arg-name])]
+ [_ (#Identifier ["" arg-name])]
(wrap arg-name)
_
@@ -5924,13 +5924,13 @@
g!compiler (gensym "compiler")
g!_ (gensym "_")
#let [rep-env (list/map (function (_ arg)
- [arg (` ((~' ~) (~ (symbol$ ["" arg]))))])
+ [arg (` ((~' ~) (~ (identifier$ ["" arg]))))])
args)]]
(wrap (list (` (macro: (~+ (export export?))
- ((~ (symbol$ ["" name])) (~ g!tokens) (~ g!compiler))
+ ((~ (identifier$ ["" name])) (~ g!tokens) (~ g!compiler))
(~ anns)
(case (~ g!tokens)
- (^ (list (~+ (list/map (|>> [""] symbol$) args))))
+ (^ (list (~+ (list/map (|>> [""] identifier$) args))))
(#.Right [(~ g!compiler)
(list (~+ (list/map (function (_ template)
(` (` (~ (replace-syntax rep-env template)))))
@@ -6018,7 +6018,7 @@
(def: (label-code code)
(-> Code (Meta [(List [Code Code]) Code]))
(case code
- (^ [ann (#Form (list [_ (#Symbol ["" "~~"])] expansion))])
+ (^ [ann (#Form (list [_ (#Identifier ["" "~~"])] expansion))])
(do Monad<Meta>
[g!expansion (gensym "g!expansion")]
(wrap [(list [g!expansion expansion]) g!expansion]))
@@ -6091,7 +6091,7 @@
[#Frac "Frac" frac$]
[#Text "Text" text$]
[#Tag "Tag" name$]
- [#Symbol "Symbol" name$])
+ [#Identifier "Identifier" name$])
[_ (#Record fields)]
(do Monad<Meta>
@@ -6105,16 +6105,16 @@
g!meta (gensym "g!meta")]
(wrap (` [(~ g!meta) (#.Record (~ (untemplate-list =fields)))])))
- [_ (#Form (#Cons [[_ (#Symbol ["" "~"])] (#Cons [unquoted #Nil])]))]
+ [_ (#Form (#Cons [[_ (#Identifier ["" "~"])] (#Cons [unquoted #Nil])]))]
(return unquoted)
- [_ (#Form (#Cons [[_ (#Symbol ["" "~+"])] (#Cons [spliced #Nil])]))]
+ [_ (#Form (#Cons [[_ (#Identifier ["" "~+"])] (#Cons [spliced #Nil])]))]
(fail "Cannot use (~+) inside of ^code unless it is the last element in a form or a tuple.")
(^template [<tag>]
[_ (<tag> elems)]
(case (list/reverse elems)
- (#Cons [_ (#Form (#Cons [[_ (#Symbol ["" "~+"])] (#Cons [spliced #Nil])]))]
+ (#Cons [_ (#Form (#Cons [[_ (#Identifier ["" "~+"])] (#Cons [spliced #Nil])]))]
inits)
(do Monad<Meta>
[=inits (monad/map Monad<Meta> untemplate-pattern (list/reverse inits))