diff options
author | Eduardo Julian | 2017-11-15 23:22:30 -0400 |
---|---|---|
committer | Eduardo Julian | 2017-11-15 23:22:30 -0400 |
commit | 190b512a822fefbb9c66271feb189cc6ccebaf85 (patch) | |
tree | 6d317f54649be741c67e03c71a8b6006b83f00ec /stdlib/source | |
parent | f11c10f72d003555d76c9803954e2bd8b347362d (diff) |
- Re-named "lux/meta" to to "lux/macro".
Diffstat (limited to '')
44 files changed, 289 insertions, 289 deletions
diff --git a/stdlib/source/lux/cli.lux b/stdlib/source/lux/cli.lux index d7e296b2f..6d4036b18 100644 --- a/stdlib/source/lux/cli.lux +++ b/stdlib/source/lux/cli.lux @@ -7,9 +7,9 @@ text/format ["E" error]) [io] - [meta #+ with-gensyms] - (meta [code] - ["s" syntax #+ syntax: Syntax]))) + [macro #+ with-gensyms] + (macro [code] + ["s" syntax #+ syntax: Syntax]))) ## [Types] (type: #export (CLI a) diff --git a/stdlib/source/lux/concurrency/actor.lux b/stdlib/source/lux/concurrency/actor.lux index 7d5c41583..bdf0758c3 100644 --- a/stdlib/source/lux/concurrency/actor.lux +++ b/stdlib/source/lux/concurrency/actor.lux @@ -7,12 +7,12 @@ (data text/format (coll [list "list/" Monoid<List> Monad<List> Fold<List>]) [product]) - [meta #+ with-gensyms Monad<Meta>] - (meta [code] - ["s" syntax #+ syntax: Syntax] - (syntax ["cs" common] - (common ["csr" reader] - ["csw" writer]))) + [macro #+ with-gensyms Monad<Meta>] + (macro [code] + ["s" syntax #+ syntax: Syntax] + (syntax ["cs" common] + (common ["csr" reader] + ["csw" writer]))) (type opaque) (lang [type])) (.. ["A" atom] @@ -152,14 +152,14 @@ (def: #hidden (<resolve> name) (-> Ident (Meta Ident)) (do Monad<Meta> - [name (meta;normalize name) - [_ annotations _] (meta;find-def name)] - (case (meta;get-tag-ann (ident-for <tag>) annotations) + [name (macro;normalize name) + [_ annotations _] (macro;find-def name)] + (case (macro;get-tag-ann (ident-for <tag>) annotations) (#;Some actor-name) (wrap actor-name) _ - (meta;fail (format "Definition is not " <desc> ".")))))] + (macro;fail (format "Definition is not " <desc> ".")))))] [with-actor resolve-actor #;;actor "an actor"] [with-message resolve-message #;;message "a message"] @@ -224,7 +224,7 @@ (wrap output)))))} (with-gensyms [g!message g!self g!state g!init g!error g!return g!output] (do @ - [module meta;current-module-name + [module macro;current-module-name #let [g!type (code;local-symbol (state-name _name)) g!behavior (code;local-symbol (behavior-name _name)) g!actor (code;local-symbol _name) diff --git a/stdlib/source/lux/concurrency/frp.lux b/stdlib/source/lux/concurrency/frp.lux index 57789d708..d59b96563 100644 --- a/stdlib/source/lux/concurrency/frp.lux +++ b/stdlib/source/lux/concurrency/frp.lux @@ -8,8 +8,8 @@ [io #- run] (data (coll [list "L/" Monoid<List>]) text/format) - [meta] - (meta ["s" syntax #+ syntax: Syntax])) + [macro] + (macro ["s" syntax #+ syntax: Syntax])) (.. ["&" promise])) ## [Types] diff --git a/stdlib/source/lux/concurrency/promise.lux b/stdlib/source/lux/concurrency/promise.lux index 63cd88c77..115f60dc1 100644 --- a/stdlib/source/lux/concurrency/promise.lux +++ b/stdlib/source/lux/concurrency/promise.lux @@ -9,8 +9,8 @@ ["A" applicative] ["M" monad #+ do Monad] ["p" parser]) - [meta] - (meta ["s" syntax #+ syntax: Syntax]) + [macro] + (macro ["s" syntax #+ syntax: Syntax]) (concurrency [atom #+ Atom atom]) )) diff --git a/stdlib/source/lux/concurrency/space.lux b/stdlib/source/lux/concurrency/space.lux index df0ec47a9..8fe9fa583 100644 --- a/stdlib/source/lux/concurrency/space.lux +++ b/stdlib/source/lux/concurrency/space.lux @@ -9,12 +9,12 @@ (data [product] (coll [list "L/" Functor<List> Fold<List>])) [io #- run] - [meta #+ with-gensyms] - (meta [code] - ["s" syntax #+ syntax:] - (syntax ["cs" common] - (common ["csr" reader] - ["csw" writer]))))) + [macro #+ with-gensyms] + (macro [code] + ["s" syntax #+ syntax:] + (syntax ["cs" common] + (common ["csr" reader] + ["csw" writer]))))) (with-expansions [<Event> [e (A;Actor Top) (Space e)] diff --git a/stdlib/source/lux/concurrency/stm.lux b/stdlib/source/lux/concurrency/stm.lux index d1762ee01..7886dda36 100644 --- a/stdlib/source/lux/concurrency/stm.lux +++ b/stdlib/source/lux/concurrency/stm.lux @@ -12,9 +12,9 @@ maybe [number "Nat/" Codec<Text,Nat>] text/format) - [meta] - (meta [code] - ["s" syntax #+ syntax: Syntax]) + [macro] + (macro [code] + ["s" syntax #+ syntax: Syntax]) (concurrency [atom #+ Atom atom] ["P" promise] [frp]) diff --git a/stdlib/source/lux/concurrency/task.lux b/stdlib/source/lux/concurrency/task.lux index fbc3cbf1e..374acee46 100644 --- a/stdlib/source/lux/concurrency/task.lux +++ b/stdlib/source/lux/concurrency/task.lux @@ -6,8 +6,8 @@ monad ["ex" exception #+ Exception]) (concurrency ["P" promise]) - [meta] - (meta ["s" syntax #+ syntax: Syntax]) + [macro] + (macro ["s" syntax #+ syntax: Syntax]) )) (type: #export (Task a) diff --git a/stdlib/source/lux/control/concatenative.lux b/stdlib/source/lux/control/concatenative.lux index 549ac19b0..b0ed0f585 100644 --- a/stdlib/source/lux/control/concatenative.lux +++ b/stdlib/source/lux/control/concatenative.lux @@ -9,12 +9,12 @@ text/format [maybe "m/" Monad<Maybe>] (coll [list "L/" Fold<List> Functor<List>])) - [meta #+ with-gensyms Monad<Meta>] - (meta [code] - ["s" syntax #+ syntax:] - (syntax ["cs" common] - (common ["csr" reader] - ["csw" writer]))))) + [macro #+ with-gensyms Monad<Meta>] + (macro [code] + ["s" syntax #+ syntax:] + (syntax ["cs" common] + (common ["csr" reader] + ["csw" writer]))))) ## [Syntax] (type: Alias [Text Code]) @@ -57,8 +57,8 @@ (wrap singleton) _ - (meta;fail (format "Cannot expand to more than a single AST/Code node:\n" - (|> expansion (L/map %code) (text;join-with " "))))))) + (macro;fail (format "Cannot expand to more than a single AST/Code node:\n" + (|> expansion (L/map %code) (text;join-with " "))))))) (syntax: #export (=> [aliases aliases^] [inputs stack^] @@ -72,16 +72,16 @@ (|> outputs (get@ #bottom) (m/map (|>. code;nat (~) #;Bound (`))))] [(#;Some bottomI) (#;Some bottomO)] (monad;do @ - [inputC (singleton (meta;expand-all (stack-fold (get@ #top inputs) bottomI))) - outputC (singleton (meta;expand-all (stack-fold (get@ #top outputs) bottomO)))] + [inputC (singleton (macro;expand-all (stack-fold (get@ #top inputs) bottomI))) + outputC (singleton (macro;expand-all (stack-fold (get@ #top outputs) bottomO)))] (wrap (list (` (-> (~ (de-alias inputC)) (~ (de-alias outputC))))))) [?bottomI ?bottomO] (with-gensyms [g!stack] (monad;do @ - [inputC (singleton (meta;expand-all (stack-fold (get@ #top inputs) (maybe;default g!stack ?bottomI)))) - outputC (singleton (meta;expand-all (stack-fold (get@ #top outputs) (maybe;default g!stack ?bottomO))))] + [inputC (singleton (macro;expand-all (stack-fold (get@ #top inputs) (maybe;default g!stack ?bottomI)))) + outputC (singleton (macro;expand-all (stack-fold (get@ #top outputs) (maybe;default g!stack ?bottomO))))] (wrap (list (` (All [(~ g!stack)] (-> (~ (de-alias inputC)) (~ (de-alias outputC)))))))))))) @@ -124,7 +124,7 @@ (syntax: #export (apply [arity (|> s;nat (p;filter (;n.> +0)))]) (with-gensyms [g!func g!stack g!output] (monad;do @ - [g!inputs (|> (meta;gensym "input") (list;repeat arity) (monad;seq @))] + [g!inputs (|> (macro;gensym "input") (list;repeat arity) (monad;seq @))] (wrap (list (` (: (All [(~@ g!inputs) (~ g!output)] (-> (-> (~@ g!inputs) (~ g!output)) (=> [(~@ g!inputs)] [(~ g!output)]))) diff --git a/stdlib/source/lux/control/cont.lux b/stdlib/source/lux/control/cont.lux index 0db72d0fc..81f62eccb 100644 --- a/stdlib/source/lux/control/cont.lux +++ b/stdlib/source/lux/control/cont.lux @@ -4,9 +4,9 @@ ["A" applicative] monad) function - [meta #+ with-gensyms] - (meta [code] - [syntax #+ syntax:]))) + [macro #+ with-gensyms] + (macro [code] + [syntax #+ syntax:]))) (type: #export (Cont i o) {#;doc "Continuations."} diff --git a/stdlib/source/lux/control/contract.lux b/stdlib/source/lux/control/contract.lux index 5ff6309ec..cc3267715 100644 --- a/stdlib/source/lux/control/contract.lux +++ b/stdlib/source/lux/control/contract.lux @@ -2,9 +2,9 @@ lux (lux (control monad) (data text/format) - [meta] - (meta [code] - ["s" syntax #+ syntax:]))) + [macro] + (macro [code] + ["s" syntax #+ syntax:]))) (def: #export (assert! message test) (-> Text Bool []) @@ -30,7 +30,7 @@ (post i.even? (i.+ 2 2)))} (do @ - [g!output (meta;gensym "")] + [g!output (macro;gensym "")] (wrap (list (` (let [(~ g!output) (~ expr)] (exec (assert! (~ (code;text (format "Post-condition failed: " (%code test)))) ((~ test) (~ g!output))) diff --git a/stdlib/source/lux/control/exception.lux b/stdlib/source/lux/control/exception.lux index 9732cd185..010fb562f 100644 --- a/stdlib/source/lux/control/exception.lux +++ b/stdlib/source/lux/control/exception.lux @@ -4,12 +4,12 @@ (data ["e" error] [maybe] [text "text/" Monoid<Text>]) - [meta] - (meta [code] - ["s" syntax #+ syntax: Syntax] - (syntax ["cs" common] - (common ["csr" reader] - ["csw" writer]))))) + [macro] + (macro [code] + ["s" syntax #+ syntax: Syntax] + (syntax ["cs" common] + (common ["csr" reader] + ["csw" writer]))))) ## [Types] (type: #export Exception @@ -71,7 +71,7 @@ "It moslty just serves as a way to tag error messages for later catching." (exception: #export Some-Exception))} (do @ - [current-module meta;current-module-name + [current-module macro;current-module-name #let [descriptor ($_ text/compose "{" current-module ";" name "}" "\n") g!message (code;symbol ["" "message"])]] (wrap (list (` (def: (~@ (csw;export _ex-lev)) ((~ (code;symbol ["" name])) (~ g!message)) diff --git a/stdlib/source/lux/control/pipe.lux b/stdlib/source/lux/control/pipe.lux index f2a6950fb..6eb8e8156 100644 --- a/stdlib/source/lux/control/pipe.lux +++ b/stdlib/source/lux/control/pipe.lux @@ -3,9 +3,9 @@ (lux (control ["M" monad #+ do Monad] ["p" parser]) (data (coll [list #+ Monad<List> "L/" Fold<List> Monad<List>])) - [meta #+ with-gensyms] - (meta ["s" syntax #+ syntax: Syntax] - [code]) + [macro #+ with-gensyms] + (macro ["s" syntax #+ syntax: Syntax] + [code]) )) ## [Syntax] @@ -98,7 +98,7 @@ (exec> [int-to-nat %n log!]) (i.* 10)))} (do @ - [g!temp (meta;gensym "")] + [g!temp (macro;gensym "")] (wrap (list (` (let [(~ g!temp) (~ prev)] (exec (|> (~ g!temp) (~@ body)) (~ g!temp)))))))) @@ -112,7 +112,7 @@ [Int/encode])) "Will become: [50 2 \"5\"]")} (do @ - [g!temp (meta;gensym "")] + [g!temp (macro;gensym "")] (wrap (list (` (let [(~ g!temp) (~ prev)] [(~@ (L/map (function [body] (` (|> (~ g!temp) (~@ body)))) paths))])))))) diff --git a/stdlib/source/lux/data/coll/ordered/dict.lux b/stdlib/source/lux/data/coll/ordered/dict.lux index 1151a018b..24b6b7c3b 100644 --- a/stdlib/source/lux/data/coll/ordered/dict.lux +++ b/stdlib/source/lux/data/coll/ordered/dict.lux @@ -6,9 +6,9 @@ (data (coll [list "L/" Monad<List> Monoid<List> Fold<List>]) ["p" product] [maybe]) - [meta] - (meta [code] - ["s" syntax #+ syntax: Syntax]))) + [macro] + (macro [code] + ["s" syntax #+ syntax: Syntax]))) (def: error-message Text "Invariant violation") diff --git a/stdlib/source/lux/data/coll/ordered/set.lux b/stdlib/source/lux/data/coll/ordered/set.lux index 90026feab..376624033 100644 --- a/stdlib/source/lux/data/coll/ordered/set.lux +++ b/stdlib/source/lux/data/coll/ordered/set.lux @@ -7,9 +7,9 @@ (ordered ["d" dict])) ["p" product] ["M" maybe #+ Functor<Maybe>]) - [meta] - (meta [code] - ["s" syntax #+ syntax: Syntax]))) + [macro] + (macro [code] + ["s" syntax #+ syntax: Syntax]))) (type: #export (Set a) (d;Dict a a)) diff --git a/stdlib/source/lux/data/coll/sequence.lux b/stdlib/source/lux/data/coll/sequence.lux index c76735d3c..f85558c5e 100644 --- a/stdlib/source/lux/data/coll/sequence.lux +++ b/stdlib/source/lux/data/coll/sequence.lux @@ -12,9 +12,9 @@ [array "array/" Functor<Array> Fold<Array>]) [bit] [product]) - [meta #+ with-gensyms] - (meta [code] - ["s" syntax #+ syntax: Syntax]) + [macro #+ with-gensyms] + (macro [code] + ["s" syntax #+ syntax: Syntax]) )) ## [Utils] diff --git a/stdlib/source/lux/data/coll/stream.lux b/stdlib/source/lux/data/coll/stream.lux index 61e3b3e6c..43ed0087c 100644 --- a/stdlib/source/lux/data/coll/stream.lux +++ b/stdlib/source/lux/data/coll/stream.lux @@ -5,8 +5,8 @@ comonad [cont #+ pending Cont] ["p" parser]) - [meta #+ with-gensyms] - (meta ["s" syntax #+ syntax: Syntax]) + [macro #+ with-gensyms] + (macro ["s" syntax #+ syntax: Syntax]) (data (coll [list "List/" Monad<List>]) bool))) diff --git a/stdlib/source/lux/data/coll/tree/rose.lux b/stdlib/source/lux/data/coll/tree/rose.lux index b07f1ed84..546982dba 100644 --- a/stdlib/source/lux/data/coll/tree/rose.lux +++ b/stdlib/source/lux/data/coll/tree/rose.lux @@ -6,9 +6,9 @@ ["p" parser] fold) (data (coll [list "L/" Monad<List> Fold<List>])) - [meta] - (meta [code] - ["s" syntax #+ syntax: Syntax]))) + [macro] + (macro [code] + ["s" syntax #+ syntax: Syntax]))) ## [Types] (type: #export (Tree a) diff --git a/stdlib/source/lux/data/coll/tree/zipper.lux b/stdlib/source/lux/data/coll/tree/zipper.lux index ddab9d121..c8f9a9059 100644 --- a/stdlib/source/lux/data/coll/tree/zipper.lux +++ b/stdlib/source/lux/data/coll/tree/zipper.lux @@ -6,9 +6,9 @@ (tree [rose #+ Tree "T/" Functor<Tree>]) [stack #+ Stack]) [maybe "M/" Monad<Maybe>]) - [meta] - (meta [code] - ["s" syntax #+ syntax: Syntax]))) + [macro] + (macro [code] + ["s" syntax #+ syntax: Syntax]))) ## Adapted from the clojure.zip namespace in the Clojure standard library. diff --git a/stdlib/source/lux/data/format/json.lux b/stdlib/source/lux/data/format/json.lux index ddc2b48cf..029d8dde7 100644 --- a/stdlib/source/lux/data/format/json.lux +++ b/stdlib/source/lux/data/format/json.lux @@ -17,10 +17,10 @@ (coll [list "list/" Fold<List> Monad<List>] [sequence #+ Sequence sequence "sequence/" Monad<Sequence>] [dict #+ Dict])) - [meta #+ Monad<Meta> with-gensyms] - (meta ["s" syntax #+ syntax:] - [code] - [poly #+ poly:]) + [macro #+ Monad<Meta> with-gensyms] + (macro ["s" syntax #+ syntax:] + [code] + [poly #+ poly:]) (lang [type]) )) @@ -86,7 +86,7 @@ (wrap (` [(~ (code;text key-name)) (~ (wrapper value))])) _ - (meta;fail "Wrong syntax for JSON object."))) + (macro;fail "Wrong syntax for JSON object."))) pairs)] (wrap (list (` (: JSON (#Object (dict;from-list text;Hash<Text> (list (~@ pairs'))))))))) diff --git a/stdlib/source/lux/data/lazy.lux b/stdlib/source/lux/data/lazy.lux index 547418d51..e344c6a0a 100644 --- a/stdlib/source/lux/data/lazy.lux +++ b/stdlib/source/lux/data/lazy.lux @@ -5,8 +5,8 @@ ["A" applicative] monad) (concurrency ["a" atom]) - [meta] - (meta ["s" syntax #+ syntax:]) + [macro] + (macro ["s" syntax #+ syntax:]) (type opaque))) (opaque: #export (Lazy a) @@ -31,7 +31,7 @@ (syntax: #export (freeze expr) (do @ - [g!_ (meta;gensym "_")] + [g!_ (macro;gensym "_")] (wrap (list (` (freeze' (function [(~ g!_)] (~ expr)))))))) (struct: #export _ (F;Functor Lazy) diff --git a/stdlib/source/lux/data/number/complex.lux b/stdlib/source/lux/data/number/complex.lux index 870474890..7fc8af1dd 100644 --- a/stdlib/source/lux/data/number/complex.lux +++ b/stdlib/source/lux/data/number/complex.lux @@ -12,9 +12,9 @@ ["E" error] [maybe] (coll [list "L/" Monad<List>])) - [meta] - (meta [code] - ["s" syntax #+ syntax: Syntax]))) + [macro] + (macro [code] + ["s" syntax #+ syntax: Syntax]))) (type: #export Complex {#real Frac diff --git a/stdlib/source/lux/data/number/ratio.lux b/stdlib/source/lux/data/number/ratio.lux index d14e5e1f1..f3f9a1196 100644 --- a/stdlib/source/lux/data/number/ratio.lux +++ b/stdlib/source/lux/data/number/ratio.lux @@ -13,9 +13,9 @@ ["E" error] [product] [maybe]) - [meta] - (meta [code] - ["s" syntax #+ syntax: Syntax]))) + [macro] + (macro [code] + ["s" syntax #+ syntax: Syntax]))) (type: #export Ratio {#numerator Nat diff --git a/stdlib/source/lux/data/text/format.lux b/stdlib/source/lux/data/text/format.lux index 7fdd9f552..9f8d2b25f 100644 --- a/stdlib/source/lux/data/text/format.lux +++ b/stdlib/source/lux/data/text/format.lux @@ -12,9 +12,9 @@ (time [instant] [duration] [date]) - [meta] - (meta [code] - ["s" syntax #+ syntax: Syntax]) + [macro] + (macro [code] + ["s" syntax #+ syntax: Syntax]) (lang [type]))) ## [Syntax] diff --git a/stdlib/source/lux/data/text/lexer.lux b/stdlib/source/lux/data/text/lexer.lux index 9ae2bdd8f..5fc638354 100644 --- a/stdlib/source/lux/data/text/lexer.lux +++ b/stdlib/source/lux/data/text/lexer.lux @@ -7,7 +7,7 @@ [maybe] ["E" error] (coll [list])) - (meta [code]))) + (macro [code]))) (type: Offset Nat) diff --git a/stdlib/source/lux/data/text/regex.lux b/stdlib/source/lux/data/text/regex.lux index bcefa4331..07e2a6ea4 100644 --- a/stdlib/source/lux/data/text/regex.lux +++ b/stdlib/source/lux/data/text/regex.lux @@ -10,9 +10,9 @@ ["E" error] [maybe] (coll [list "L/" Fold<List> Monad<List>])) - [meta #- run] - (meta [code] - ["s" syntax #+ syntax:]))) + [macro #- run] + (macro [code] + ["s" syntax #+ syntax:]))) ## [Utils] (def: regex-char^ @@ -458,13 +458,13 @@ (regex "a(.)(.)|b(.)(.)") )} (do @ - [current-module meta;current-module-name] + [current-module macro;current-module-name] (case (|> (regex^ current-module) (p;before l;end) (l;run pattern)) (#E;Error error) - (meta;fail (format "Error while parsing regular-expression:\n" - error)) + (macro;fail (format "Error while parsing regular-expression:\n" + error)) (#E;Success regex) (wrap (list regex)) @@ -485,7 +485,7 @@ _ do-something-else))} (do @ - [g!temp (meta;gensym "temp")] + [g!temp (macro;gensym "temp")] (wrap (list& (` (^multi (~ g!temp) [(l;run (~ g!temp) (regex (~ (code;text pattern)))) (#E;Success (~ (maybe;default g!temp diff --git a/stdlib/source/lux/host.js.lux b/stdlib/source/lux/host.js.lux index e9c987532..fdbc752c4 100644 --- a/stdlib/source/lux/host.js.lux +++ b/stdlib/source/lux/host.js.lux @@ -3,9 +3,9 @@ (lux (control monad ["p" parser]) (data (coll [list #* "L/" Fold<List>])) - [meta #+ with-gensyms] - (meta [code] - ["s" syntax #+ syntax: Syntax]) + [macro #+ with-gensyms] + (macro [code] + ["s" syntax #+ syntax: Syntax]) )) (do-template [<name> <type>] diff --git a/stdlib/source/lux/host.jvm.lux b/stdlib/source/lux/host.jvm.lux index 1b77e3016..1298a56d1 100644 --- a/stdlib/source/lux/host.jvm.lux +++ b/stdlib/source/lux/host.jvm.lux @@ -11,9 +11,9 @@ [text "text/" Eq<Text> Monoid<Text>] text/format [bool "bool/" Codec<Text,Bool>]) - [meta #+ with-gensyms Functor<Meta> Monad<Meta>] - (meta [code] - ["s" syntax #+ syntax: Syntax]) + [macro #+ with-gensyms Functor<Meta> Monad<Meta>] + (macro [code] + ["s" syntax #+ syntax: Syntax]) (lang [type]) )) @@ -352,21 +352,21 @@ (def: (class-imports compiler) (-> Compiler ClassImports) - (case (meta;run compiler - (: (Meta ClassImports) - (do Monad<Meta> - [current-module meta;current-module-name - defs (meta;defs current-module)] - (wrap (list/fold (: (-> [Text Def] ClassImports ClassImports) - (function [[short-name [_ meta _]] imports] - (case (meta;get-text-ann (ident-for #;;jvm-class) meta) - (#;Some full-class-name) - (add-import [short-name full-class-name] imports) - - _ - imports))) - empty-imports - defs))))) + (case (macro;run compiler + (: (Meta ClassImports) + (do Monad<Meta> + [current-module macro;current-module-name + defs (macro;defs current-module)] + (wrap (list/fold (: (-> [Text Def] ClassImports ClassImports) + (function [[short-name [_ meta _]] imports] + (case (macro;get-text-ann (ident-for #;;jvm-class) meta) + (#;Some full-class-name) + (add-import [short-name full-class-name] imports) + + _ + imports))) + empty-imports + defs))))) (#;Left _) (list) (#;Right imports) imports)) @@ -1305,7 +1305,7 @@ "(.resolve! container [value]) for calling the \"resolve\" method." )} (do Monad<Meta> - [current-module meta;current-module-name + [current-module macro;current-module-name #let [fully-qualified-class-name (format (text;replace-all "/" "." current-module) "." full-class-name) field-parsers (list/map (field->parser fully-qualified-class-name) fields) method-parsers (list/map (method->parser (product;right class-decl) fully-qualified-class-name) methods) @@ -1435,7 +1435,7 @@ #;None (do @ - [g!obj (meta;gensym "obj")] + [g!obj (macro;gensym "obj")] (wrap (list (` (: (-> (primitive (~' java.lang.Object)) Bool) (function [(~ g!obj)] ((~ (code;text (format "jvm instanceof" ":" (simple-class$ (list) class)))) (~ g!obj)))))))) @@ -1540,7 +1540,7 @@ (:: Monad<Meta> wrap (class->type mode type-params (get@ #import-method-return method))) _ - (meta;fail "Only methods have return values."))) + (macro;fail "Only methods have return values."))) (def: (decorate-return-maybe member [return-type return-term]) (-> ImportMemberDecl [Code Code] [Code Code]) @@ -1842,7 +1842,7 @@ #Class)) (#;Left _) - (meta;fail (format "Unknown class: " class-name)))) + (macro;fail (format "Unknown class: " class-name)))) (syntax: #export (import [#let [imports (class-imports *compiler*)]] [long-name? (s;this? (' #long))] @@ -1937,7 +1937,7 @@ (#;Apply A F) (case (type;apply (list A) F) #;None - (meta;fail (format "Cannot apply type: " (type;to-text F) " to " (type;to-text A))) + (macro;fail (format "Cannot apply type: " (type;to-text F) " to " (type;to-text A))) (#;Some type') (type->class-name type')) @@ -1949,7 +1949,7 @@ (:: Monad<Meta> wrap "java.lang.Object") (^or #;Void (#;Var _) (#;Ex _) (#;Bound _) (#;Sum _) (#;Product _) (#;Function _) (#;UnivQ _) (#;ExQ _)) - (meta;fail (format "Cannot convert to JvmType: " (type;to-text type))) + (macro;fail (format "Cannot convert to JvmType: " (type;to-text type))) )) (syntax: #export (array-read idx array) @@ -1958,7 +1958,7 @@ (case array [_ (#;Symbol array-name)] (do Monad<Meta> - [array-type (meta;find-type array-name) + [array-type (macro;find-type array-name) array-jvm-type (type->class-name array-type)] (case array-jvm-type (^template [<type> <array-op>] @@ -1987,7 +1987,7 @@ (case array [_ (#;Symbol array-name)] (do Monad<Meta> - [array-type (meta;find-type array-name) + [array-type (macro;find-type array-name) array-jvm-type (type->class-name array-type)] (case array-jvm-type (^template [<type> <array-op>] @@ -2071,7 +2071,7 @@ (wrap fqcn) #;None - (meta;fail (text/compose "Unknown class: " class))))) + (macro;fail (text/compose "Unknown class: " class))))) (syntax: #export (type [#let [imports (class-imports *compiler*)]] [type (generic-type^ imports (list))]) diff --git a/stdlib/source/lux/lang/type.lux b/stdlib/source/lux/lang/type.lux index 9d6ed5162..974561605 100644 --- a/stdlib/source/lux/lang/type.lux +++ b/stdlib/source/lux/lang/type.lux @@ -7,7 +7,7 @@ [number "nat/" Codec<Text,Nat>] [maybe] (coll [list #+ "list/" Monad<List> Monoid<List> Fold<List>])) - (meta [code]) + (macro [code]) )) ## [Utils] diff --git a/stdlib/source/lux/meta.lux b/stdlib/source/lux/macro.lux index e65e09b58..e65e09b58 100644 --- a/stdlib/source/lux/meta.lux +++ b/stdlib/source/lux/macro.lux diff --git a/stdlib/source/lux/meta/code.lux b/stdlib/source/lux/macro/code.lux index d41dbe240..d41dbe240 100644 --- a/stdlib/source/lux/meta/code.lux +++ b/stdlib/source/lux/macro/code.lux diff --git a/stdlib/source/lux/meta/poly.lux b/stdlib/source/lux/macro/poly.lux index 08d91c5f0..7ed7fb2ee 100644 --- a/stdlib/source/lux/meta/poly.lux +++ b/stdlib/source/lux/macro/poly.lux @@ -13,12 +13,12 @@ [maybe] [ident "ident/" Eq<Ident> Codec<Text,Ident>] ["e" error]) - [meta #+ with-gensyms] - (meta [code] - ["s" syntax #+ syntax: Syntax] - (syntax ["cs" common] - (common ["csr" reader] - ["csw" writer]))) + [macro #+ with-gensyms] + (macro [code] + ["s" syntax #+ syntax: Syntax] + (syntax ["cs" common] + (common ["csr" reader] + ["csw" writer]))) (lang [type] (type [check])) )) @@ -343,8 +343,8 @@ (with-gensyms [g!type g!output] (let [g!name (code;symbol ["" name])] (wrap (;list (` (syntax: (~@ (csw;export export)) ((~ g!name) [(~ g!type) s;symbol]) - (do meta;Monad<Meta> - [(~ g!type) (meta;find-type-def (~ g!type))] + (do macro;Monad<Meta> + [(~ g!type) (macro;find-type-def (~ g!type))] (case (|> (~ body) (;function [(~ g!name)]) p;rec @@ -352,7 +352,7 @@ (;;run (~ g!type)) (: (;Either ;Text ;Code))) (#;Left (~ g!output)) - (meta;fail (~ g!output)) + (macro;fail (~ g!output)) (#;Right (~ g!output)) ((~' wrap) (;list (~ g!output)))))))))))) @@ -372,7 +372,7 @@ [[poly-func poly-args] (s;form (p;seq s;symbol (p;many s;symbol)))] [?custom-impl (p;maybe s;any)]) (do @ - [poly-args (monad;map @ meta;normalize poly-args) + [poly-args (monad;map @ macro;normalize poly-args) name (case ?name (#;Some name) (wrap name) diff --git a/stdlib/source/lux/meta/poly/eq.lux b/stdlib/source/lux/macro/poly/eq.lux index 0d63f0d35..099febb24 100644 --- a/stdlib/source/lux/meta/poly/eq.lux +++ b/stdlib/source/lux/macro/poly/eq.lux @@ -19,11 +19,11 @@ (time ["du" duration] ["da" date] ["i" instant]) - [meta] - (meta [code] - [syntax #+ syntax: Syntax] - (syntax [common]) - [poly #+ poly:]) + [macro] + (macro [code] + [syntax #+ syntax: Syntax] + (syntax [common]) + [poly #+ poly:]) (type [unit]) (lang [type]) )) diff --git a/stdlib/source/lux/meta/poly/functor.lux b/stdlib/source/lux/macro/poly/functor.lux index 0e140e9e4..ba847d35b 100644 --- a/stdlib/source/lux/meta/poly/functor.lux +++ b/stdlib/source/lux/macro/poly/functor.lux @@ -7,11 +7,11 @@ text/format (coll [list "L/" Monad<List> Monoid<List>]) [product]) - [meta] - (meta [code] - [syntax #+ syntax: Syntax] - (syntax [common]) - [poly #+ poly:]) + [macro] + (macro [code] + [syntax #+ syntax: Syntax] + (syntax [common]) + [poly #+ poly:]) (lang [type]) )) diff --git a/stdlib/source/lux/meta/poly/json.lux b/stdlib/source/lux/macro/poly/json.lux index 282c8ad7c..5c3a645ee 100644 --- a/stdlib/source/lux/meta/poly/json.lux +++ b/stdlib/source/lux/macro/poly/json.lux @@ -20,10 +20,10 @@ (time ["i" instant] ["du" duration] ["da" date]) - [meta #+ with-gensyms] - (meta ["s" syntax #+ syntax:] - [code] - [poly #+ poly:]) + [macro #+ with-gensyms] + (macro ["s" syntax #+ syntax:] + [code] + [poly #+ poly:]) (type [unit]) (lang [type]) )) diff --git a/stdlib/source/lux/meta/syntax.lux b/stdlib/source/lux/macro/syntax.lux index 5587693dd..917b7e094 100644 --- a/stdlib/source/lux/meta/syntax.lux +++ b/stdlib/source/lux/macro/syntax.lux @@ -1,6 +1,6 @@ (;module: lux - (lux [meta #+ with-gensyms] + (lux [macro #+ with-gensyms] (control [monad #+ do Monad] [eq #+ Eq] ["p" parser]) @@ -173,7 +173,7 @@ {#;doc "Run a Lux operation as if it was a Syntax parser."} (All [a] (-> Compiler (Meta a) (Syntax a))) (function [input] - (case (meta;run compiler action) + (case (macro;run compiler action) (#E;Error error) (#E;Error error) @@ -253,7 +253,7 @@ (case ?parts (#;Some [name args meta body]) (with-gensyms [g!tokens g!body g!msg] - (do meta;Monad<Meta> + (do macro;Monad<Meta> [vars+parsers (monad;map @ (: (-> Code (Meta [Code Code])) (function [arg] @@ -265,7 +265,7 @@ (wrap [(code;symbol var-name) (` any)]) _ - (meta;fail "Syntax pattern expects tuples or symbols.")))) + (macro;fail "Syntax pattern expects tuples or symbols.")))) args) #let [g!state (code;symbol ["" "*compiler*"]) error-msg (code;text (text/compose "Wrong syntax for " name)) @@ -284,7 +284,7 @@ (: (Syntax (Meta (List Code))) (do ;;_Monad<Parser>_ [(~@ (join-pairs vars+parsers))] - ((~' wrap) (do meta;Monad<Meta> + ((~' wrap) (do macro;Monad<Meta> [] (~ body)))))) {(#E;Success (~ g!body)) @@ -294,4 +294,4 @@ (#E;Error (text.join-with ": " (list (~ error-msg) (~ g!msg))))}))))))) _ - (meta;fail "Wrong syntax for syntax:")))) + (macro;fail "Wrong syntax for syntax:")))) diff --git a/stdlib/source/lux/meta/syntax/common.lux b/stdlib/source/lux/macro/syntax/common.lux index 72e52a4ab..72e52a4ab 100644 --- a/stdlib/source/lux/meta/syntax/common.lux +++ b/stdlib/source/lux/macro/syntax/common.lux diff --git a/stdlib/source/lux/meta/syntax/common/reader.lux b/stdlib/source/lux/macro/syntax/common/reader.lux index 83fdadc18..9ab6d6381 100644 --- a/stdlib/source/lux/meta/syntax/common/reader.lux +++ b/stdlib/source/lux/macro/syntax/common/reader.lux @@ -6,8 +6,8 @@ [ident "ident/" Eq<Ident>] [product] [maybe]) - [meta] - (meta ["s" syntax #+ syntax: Syntax])) + [macro] + (macro ["s" syntax #+ syntax: Syntax])) [.. #*]) ## Exports @@ -109,7 +109,7 @@ (do p;Monad<Parser> [definition-raw s;any me-definition-raw (s;on compiler - (meta;expand-all definition-raw))] + (macro;expand-all definition-raw))] (s;local me-definition-raw (s;form (do @ [_ (s;this (' "lux def")) diff --git a/stdlib/source/lux/meta/syntax/common/writer.lux b/stdlib/source/lux/macro/syntax/common/writer.lux index c7eaf6f00..72e4a11eb 100644 --- a/stdlib/source/lux/meta/syntax/common/writer.lux +++ b/stdlib/source/lux/macro/syntax/common/writer.lux @@ -2,7 +2,7 @@ lux (lux (data (coll [list "L/" Functor<List>]) [product]) - (meta [code])) + (macro [code])) [.. #*]) ## Exports diff --git a/stdlib/source/lux/math.lux b/stdlib/source/lux/math.lux index aa317368d..d1671537d 100644 --- a/stdlib/source/lux/math.lux +++ b/stdlib/source/lux/math.lux @@ -4,9 +4,9 @@ ["p" parser "p/" Functor<Parser>]) (data (coll [list "L/" Fold<List>]) [product]) - [meta] - (meta ["s" syntax #+ syntax: Syntax] - [code]))) + [macro] + (macro ["s" syntax #+ syntax: Syntax] + [code]))) ## [Values] (do-template [<name> <value>] diff --git a/stdlib/source/lux/test.lux b/stdlib/source/lux/test.lux index 3eae64eee..d296a9a2e 100644 --- a/stdlib/source/lux/test.lux +++ b/stdlib/source/lux/test.lux @@ -1,8 +1,8 @@ (;module: {#;doc "Tools for unit & property-based/generative testing."} lux - (lux [meta #+ Monad<Meta> with-gensyms] - (meta ["s" syntax #+ syntax: Syntax] - [code]) + (lux [macro #+ Monad<Meta> with-gensyms] + (macro ["s" syntax #+ syntax: Syntax] + [code]) (control [monad #+ do Monad] ["p" parser]) (concurrency [promise #+ Promise Monad<Promise>]) @@ -200,10 +200,10 @@ (def: (exported-tests module-name) (-> Text (Meta (List [Text Text Text]))) (do Monad<Meta> - [defs (meta;exports module-name)] + [defs (macro;exports module-name)] (wrap (|> defs (list/map (function [[def-name [_ def-anns _]]] - (case (meta;get-text-ann (ident-for #;;test) def-anns) + (case (macro;get-text-ann (ident-for #;;test) def-anns) (#;Some description) [true module-name def-name description] @@ -220,8 +220,8 @@ (run))} (with-gensyms [g!successes g!failures g!total-successes g!total-failures] (do @ - [current-module meta;current-module-name - modules (meta;imported-modules current-module) + [current-module macro;current-module-name + modules (macro;imported-modules current-module) tests (: (Meta (List [Text Text Text])) (|> (#;Cons current-module modules) list;reverse diff --git a/stdlib/source/lux/type/implicit.lux b/stdlib/source/lux/type/implicit.lux index 54fec2626..e23a5c8dd 100644 --- a/stdlib/source/lux/type/implicit.lux +++ b/stdlib/source/lux/type/implicit.lux @@ -11,9 +11,9 @@ [bool] [product] [maybe]) - [meta #+ Monad<Meta>] - (meta [code] - ["s" syntax #+ syntax: Syntax]) + [macro #+ Monad<Meta>] + (macro [code] + ["s" syntax #+ syntax: Syntax]) (lang [type] (type ["tc" check #+ Check Monad<Check>])) )) @@ -31,17 +31,17 @@ (:: Monad<Meta> wrap type)) (#;Some [_ #;None]) - (meta;fail (format "Unbound type-var " (%n id))) + (macro;fail (format "Unbound type-var " (%n id))) #;None - (meta;fail (format "Unknown type-var " (%n id))) + (macro;fail (format "Unknown type-var " (%n id))) )) (def: (resolve-type var-name) (-> Ident (Meta Type)) (do Monad<Meta> - [raw-type (meta;find-type var-name) - compiler meta;get-compiler] + [raw-type (macro;find-type var-name) + compiler macro;get-compiler] (case raw-type (#;Var id) (find-type-var id (get@ #;type-context compiler)) @@ -77,26 +77,26 @@ (-> Ident (Meta Ident)) (case member ["" simple-name] - (meta;either (do Monad<Meta> - [member (meta;normalize member) - _ (meta;resolve-tag member)] - (wrap member)) - (do Monad<Meta> - [this-module-name meta;current-module-name - imp-mods (meta;imported-modules this-module-name) - tag-lists (M;map @ meta;tag-lists imp-mods) - #let [tag-lists (|> tag-lists List/join (List/map product;left) List/join) - candidates (list;filter (. (Text/= simple-name) product;right) - tag-lists)]] - (case candidates - #;Nil - (meta;fail (format "Unknown tag: " (%ident member))) - - (#;Cons winner #;Nil) - (wrap winner) - - _ - (meta;fail (format "Too many candidate tags: " (%list %ident candidates)))))) + (macro;either (do Monad<Meta> + [member (macro;normalize member) + _ (macro;resolve-tag member)] + (wrap member)) + (do Monad<Meta> + [this-module-name macro;current-module-name + imp-mods (macro;imported-modules this-module-name) + tag-lists (M;map @ macro;tag-lists imp-mods) + #let [tag-lists (|> tag-lists List/join (List/map product;left) List/join) + candidates (list;filter (. (Text/= simple-name) product;right) + tag-lists)]] + (case candidates + #;Nil + (macro;fail (format "Unknown tag: " (%ident member))) + + (#;Cons winner #;Nil) + (wrap winner) + + _ + (macro;fail (format "Too many candidate tags: " (%list %ident candidates)))))) _ (:: Monad<Meta> wrap member))) @@ -105,21 +105,21 @@ (-> Ident (Meta [Nat Type])) (do Monad<Meta> [member (find-member-name member) - [idx tag-list sig-type] (meta;resolve-tag member)] + [idx tag-list sig-type] (macro;resolve-tag member)] (wrap [idx sig-type]))) (def: (prepare-defs this-module-name defs) (-> Text (List [Text Def]) (List [Ident Type])) (|> defs (list;filter (function [[name [def-type def-anns def-value]]] - (meta;struct? def-anns))) + (macro;struct? def-anns))) (List/map (function [[name [def-type def-anns def-value]]] [[this-module-name name] def-type])))) (def: local-env (Meta (List [Ident Type])) (do Monad<Meta> - [local-batches meta;locals + [local-batches macro;locals #let [total-locals (List/fold (function [[name type] table] (dict;put~ name type table)) (: (dict;Dict Text Type) @@ -132,18 +132,18 @@ (def: local-structs (Meta (List [Ident Type])) (do Monad<Meta> - [this-module-name meta;current-module-name - defs (meta;defs this-module-name)] + [this-module-name macro;current-module-name + defs (macro;defs this-module-name)] (wrap (prepare-defs this-module-name defs)))) (def: import-structs (Meta (List [Ident Type])) (do Monad<Meta> - [this-module-name meta;current-module-name - imp-mods (meta;imported-modules this-module-name) + [this-module-name macro;current-module-name + imp-mods (macro;imported-modules this-module-name) export-batches (M;map @ (function [imp-mod] (do @ - [exports (meta;exports imp-mod)] + [exports (macro;exports imp-mod)] (wrap (prepare-defs imp-mod exports)))) imp-mods)] (wrap (List/join export-batches)))) @@ -200,7 +200,7 @@ Type-Context Type (List [Ident Type]) (Meta (List Instance))) (do Monad<Meta> - [compiler meta;get-compiler] + [compiler macro;get-compiler] (case (|> alts (List/map (function [[alt-name alt-type]] (case (tc;run context @@ -218,18 +218,18 @@ (list [alt-name =deps])))) List/join) #;Nil - (meta;fail (format "No candidates for provisioning: " (%type dep))) + (macro;fail (format "No candidates for provisioning: " (%type dep))) found (wrap found)))) (def: (provision compiler context dep) (-> Compiler Type-Context Type (Check Instance)) - (case (meta;run compiler - ($_ meta;either - (do Monad<Meta> [alts local-env] (test-provision provision context dep alts)) - (do Monad<Meta> [alts local-structs] (test-provision provision context dep alts)) - (do Monad<Meta> [alts import-structs] (test-provision provision context dep alts)))) + (case (macro;run compiler + ($_ macro;either + (do Monad<Meta> [alts local-env] (test-provision provision context dep alts)) + (do Monad<Meta> [alts local-structs] (test-provision provision context dep alts)) + (do Monad<Meta> [alts import-structs] (test-provision provision context dep alts)))) (#;Left error) (tc;fail error) @@ -248,8 +248,8 @@ (def: (test-alternatives sig-type member-idx input-types output-type alts) (-> Type Nat (List Type) Type (List [Ident Type]) (Meta (List Instance))) (do Monad<Meta> - [compiler meta;get-compiler - context meta;type-context] + [compiler macro;get-compiler + context macro;type-context] (case (|> alts (List/map (function [[alt-name alt-type]] (case (tc;run context @@ -269,7 +269,7 @@ (list [alt-name =deps])))) List/join) #;Nil - (meta;fail (format "No alternatives for " (%type (type;function input-types output-type)))) + (macro;fail (format "No alternatives for " (%type (type;function input-types output-type)))) found (wrap found)))) @@ -277,7 +277,7 @@ (def: (find-alternatives sig-type member-idx input-types output-type) (-> Type Nat (List Type) Type (Meta (List Instance))) (let [test (test-alternatives sig-type member-idx input-types output-type)] - ($_ meta;either + ($_ macro;either (do Monad<Meta> [alts local-env] (test alts)) (do Monad<Meta> [alts local-structs] (test alts)) (do Monad<Meta> [alts import-structs] (test alts))))) @@ -335,11 +335,11 @@ (do @ [[member-idx sig-type] (resolve-member member) input-types (M;map @ resolve-type args) - output-type meta;expected-type + output-type macro;expected-type chosen-ones (find-alternatives sig-type member-idx input-types output-type)] (case chosen-ones #;Nil - (meta;fail (format "No structure option could be found for member: " (%ident member))) + (macro;fail (format "No structure option could be found for member: " (%ident member))) (#;Cons chosen #;Nil) (wrap (list (` (:: (~ (instance$ chosen)) @@ -347,16 +347,16 @@ (~@ (List/map code;symbol args)))))) _ - (meta;fail (format "Too many options available: " - (|> chosen-ones - (List/map (. %ident product;left)) - (text;join-with ", ")) - " --- for type: " (%type sig-type))))) + (macro;fail (format "Too many options available: " + (|> chosen-ones + (List/map (. %ident product;left)) + (text;join-with ", ")) + " --- for type: " (%type sig-type))))) (#;Right [args _]) (do @ [labels (M;seq @ (list;repeat (list;size args) - (meta;gensym ""))) + (macro;gensym ""))) #let [retry (` (let [(~@ (|> (list;zip2 labels args) (List/map join-pair) List/join))] (;;::: (~ (code;symbol member)) (~@ labels))))]] (wrap (list retry))) diff --git a/stdlib/source/lux/type/object.lux b/stdlib/source/lux/type/object.lux index 0eb354242..fc68dcdae 100644 --- a/stdlib/source/lux/type/object.lux +++ b/stdlib/source/lux/type/object.lux @@ -9,12 +9,12 @@ [ident #+ "Ident/" Eq<Ident>] (coll [list "L/" Functor<List> Fold<List> Monoid<List>] [set #+ Set])) - [meta #+ Monad<Meta> "Meta/" Monad<Meta>] - (meta [code] - ["s" syntax #+ syntax:] - (syntax ["cs" common] - (common ["csr" reader] - ["csw" writer]))) + [macro #+ Monad<Meta> "Macro/" Monad<Meta>] + (macro [code] + ["s" syntax #+ syntax:] + (syntax ["cs" common] + (common ["csr" reader] + ["csw" writer]))) (lang [type]))) ## [Common] @@ -143,10 +143,10 @@ [(def: (<name> name) (-> Ident (Meta [Ident (List Ident)])) (do Monad<Meta> - [name (meta;normalize name) - [_ annotations _] (meta;find-def name)] - (case [(meta;get-tag-ann (ident-for <name-tag>) annotations) - (meta;get-tag-ann (ident-for <parent-tag>) annotations)] + [name (macro;normalize name) + [_ annotations _] (macro;find-def name)] + (case [(macro;get-tag-ann (ident-for <name-tag>) annotations) + (macro;get-tag-ann (ident-for <parent-tag>) annotations)] [(#;Some real-name) (#;Some parent)] (if (Ident/= no-parent parent) (wrap [real-name (list)]) @@ -155,7 +155,7 @@ (wrap [real-name (#;Cons parent ancestors)]))) _ - (meta;fail (format "Wrong format for " <desc> " lineage.")))))] + (macro;fail (format "Wrong format for " <desc> " lineage.")))))] [interfaceN #;;interface-name #;;interface-parent "interface"] [classN #;;class-name #;;class-parent "class"] @@ -171,10 +171,10 @@ (#;Function inputT outputT) (let [[stateT+ objectT] (type;flatten-function currentT)] - (Meta/wrap [depth stateT+])) + (Macro/wrap [depth stateT+])) _ - (meta;fail (format "Cannot extract inheritance from type: " (type;to-text newT)))))) + (macro;fail (format "Cannot extract inheritance from type: " (type;to-text newT)))))) (def: (specialize mappings typeC) (-> (List Code) Code Code) @@ -319,10 +319,10 @@ (~@ paramsC+))))) #;Void - (Meta/wrap (` (;|))) + (Macro/wrap (` (;|))) #;Unit - (Meta/wrap (` (;&))) + (Macro/wrap (` (;&))) (^template [<tag> <macro> <flatten>] (<tag> _) @@ -341,7 +341,7 @@ (^template [<tag>] (<tag> idx) - (Meta/wrap (` (<tag> (~ (code;nat idx)))))) + (Macro/wrap (` (<tag> (~ (code;nat idx)))))) ([#;Bound] [#;Var] [#;Ex]) @@ -354,10 +354,10 @@ (wrap (` ((~ funcC) (~@ argsC+))))) (#;Named name unnamedT) - (Meta/wrap (code;symbol name)) + (Macro/wrap (code;symbol name)) _ - (meta;fail (format "Cannot convert type to code: " (type;to-text type))))) + (macro;fail (format "Cannot convert type to code: " (type;to-text type))))) (syntax: #export (interface: [export csr;export] [(^@ decl [interface parameters]) declarationS] @@ -365,9 +365,9 @@ [alias aliasS] [annotations (p;default cs;empty-annotations csr;annotations)] [methods (p;many (method (var-set parameters)))]) - (meta;with-gensyms [g!self-class g!child g!ext] + (macro;with-gensyms [g!self-class g!child g!ext] (do @ - [module meta;current-module-name + [module macro;current-module-name [parent ancestors mappings] (: (Meta [Ident (List Ident) (List Code)]) (case ?extends #;None @@ -433,9 +433,9 @@ [super (p;maybe inheritance)] state-type [impls (p;many s;any)]) - (meta;with-gensyms [g!init g!extension] + (macro;with-gensyms [g!init g!extension] (do @ - [module meta;current-module-name + [module macro;current-module-name [interface _] (interfaceN interface) [parent ancestors parent-mappings] (: (Meta [Ident (List Ident) (List Code)]) (case super @@ -450,7 +450,7 @@ (if (no-parent? parent) (wrap (list)) (do @ - [newT (meta;find-def-type (product;both id newN parent)) + [newT (macro;find-def-type (product;both id newN parent)) [depth rawT+] (extract newT) codeT+ (M;map @ type-to-code rawT+)] (wrap (L/map (specialize parent-mappings) codeT+))))) @@ -466,7 +466,7 @@ g!parent-structs (if (no-parent? parent) (list) (L/map (|>. (product;both id structN) code;symbol) (list& parent ancestors)))] - g!parent-inits (M;map @ (function [_] (meta;gensym "parent-init")) + g!parent-inits (M;map @ (function [_] (macro;gensym "parent-init")) g!parent-structs) #let [g!full-init (L/fold (function [[parent-struct parent-state] child] (` [(~ parent-struct) (~ parent-state) (~ child)])) diff --git a/stdlib/source/lux/type/opaque.lux b/stdlib/source/lux/type/opaque.lux index acd73d6a4..3b50fcbc2 100644 --- a/stdlib/source/lux/type/opaque.lux +++ b/stdlib/source/lux/type/opaque.lux @@ -6,12 +6,12 @@ (data [text "text/" Eq<Text> Monoid<Text>] ["E" error] (coll [list "list/" Functor<List> Monoid<List>])) - [meta] - (meta [code] - ["s" syntax #+ syntax:] - (syntax ["cs" common] - (common ["csr" reader] - ["csw" writer]))))) + [macro] + (macro [code] + ["s" syntax #+ syntax:] + (syntax ["cs" common] + (common ["csr" reader] + ["csw" writer]))))) (def: (get k plist) (All [a] @@ -60,8 +60,8 @@ (def: (install-casts' this-module-name name type-vars) (-> Text Text (List Text) (Meta Unit)) - (do meta;Monad<Meta> - [this-module (meta;find-module this-module-name) + (do macro;Monad<Meta> + [this-module (macro;find-module this-module-name) #let [type-varsC (list/map code;local-symbol type-vars) opaque-declaration (` ((~ (code;local-symbol name)) (~@ type-varsC))) representation-declaration (` ((~ (code;local-symbol (representation-name name))) (~@ type-varsC))) @@ -77,7 +77,7 @@ (~ value))))) _ - (meta;fail ($_ text/compose "Wrong syntax for " down-cast))))]))) + (macro;fail ($_ text/compose "Wrong syntax for " down-cast))))]))) (update@ #;defs (put up-cast (: Def [Macro macro-anns (function [tokens] @@ -89,15 +89,15 @@ (~ value))))) _ - (meta;fail ($_ text/compose "Wrong syntax for " up-cast))))]))))]] + (macro;fail ($_ text/compose "Wrong syntax for " up-cast))))]))))]] (function [compiler] (#E;Success [(update@ #;modules (put this-module-name this-module) compiler) []])))) (def: (un-install-casts' this-module-name) (-> Text (Meta Unit)) - (do meta;Monad<Meta> - [this-module (meta;find-module this-module-name) + (do macro;Monad<Meta> + [this-module (macro;find-module this-module-name) #let [this-module (|> this-module (update@ #;defs (remove down-cast)) (update@ #;defs (remove up-cast)))]] @@ -108,9 +108,9 @@ (syntax: #hidden (install-casts [name s;local-symbol] [type-vars (s;tuple (p;some s;local-symbol))]) (do @ - [this-module-name meta;current-module-name - ?down-cast (meta;find-macro [this-module-name down-cast]) - ?up-cast (meta;find-macro [this-module-name up-cast])] + [this-module-name macro;current-module-name + ?down-cast (macro;find-macro [this-module-name down-cast]) + ?up-cast (macro;find-macro [this-module-name up-cast])] (case [?down-cast ?up-cast] [#;None #;None] (do @ @@ -118,16 +118,16 @@ (wrap (list))) _ - (meta;fail ($_ text/compose - "Cannot temporarily define casting functions (" - down-cast " & " up-cast - ") because definitions like that already exist."))))) + (macro;fail ($_ text/compose + "Cannot temporarily define casting functions (" + down-cast " & " up-cast + ") because definitions like that already exist."))))) (syntax: #hidden (un-install-casts) - (do meta;Monad<Meta> - [this-module-name meta;current-module-name - ?down-cast (meta;find-macro [this-module-name down-cast]) - ?up-cast (meta;find-macro [this-module-name up-cast])] + (do macro;Monad<Meta> + [this-module-name macro;current-module-name + ?down-cast (macro;find-macro [this-module-name down-cast]) + ?up-cast (macro;find-macro [this-module-name up-cast])] (case [?down-cast ?up-cast] [(#;Some _) (#;Some _)] (do @ @@ -135,10 +135,10 @@ (wrap (list))) _ - (meta;fail ($_ text/compose - "Cannot un-define casting functions (" - down-cast " & " up-cast - ") because they do not exist."))))) + (macro;fail ($_ text/compose + "Cannot un-define casting functions (" + down-cast " & " up-cast + ") because they do not exist."))))) (def: declaration (s;Syntax [Text (List Text)]) diff --git a/stdlib/source/lux/type/unit.lux b/stdlib/source/lux/type/unit.lux index de00fb82d..ef8f5410a 100644 --- a/stdlib/source/lux/type/unit.lux +++ b/stdlib/source/lux/type/unit.lux @@ -7,12 +7,12 @@ [enum #+ Enum]) (data text/format (number ["r" ratio])) - [meta] - (meta [code] - ["s" syntax #+ syntax:] - (syntax ["cs" common] - (common ["csr" reader] - ["csw" writer]))))) + [macro] + (macro [code] + ["s" syntax #+ syntax:] + (syntax ["cs" common] + (common ["csr" reader] + ["csw" writer]))))) (type: #export (Qty unit) [Int unit]) |