diff options
Diffstat (limited to '')
447 files changed, 3409 insertions, 3409 deletions
diff --git a/stdlib/source/library/lux.lux b/stdlib/source/library/lux.lux index e9b07fe8f..7fad8a9a5 100644 --- a/stdlib/source/library/lux.lux +++ b/stdlib/source/library/lux.lux @@ -3745,30 +3745,30 @@ (in_meta name) _ - (failure "#only/#+ and #exclude/#- require identifiers.")))) + (failure "only/+ and exclude/- require identifiers.")))) defs)) (def: (referrals_parser tokens) (-> (List Code) (Meta [Referrals (List Code)])) (case tokens - (^or (^ (list& [_ (#Form (list& [_ (#Tag ["" "+"])] defs))] tokens')) - (^ (list& [_ (#Form (list& [_ (#Tag ["" "only"])] defs))] tokens'))) + (^or (^ (list& [_ (#Record (list [[_ (#Text "+")] [_ (#Tuple defs)]]))] tokens')) + (^ (list& [_ (#Record (list [[_ (#Text "only")] [_ (#Tuple defs)]]))] tokens'))) (do meta_monad [defs' (..referral_references defs)] (in [(#Only defs') tokens'])) - (^or (^ (list& [_ (#Form (list& [_ (#Tag ["" "-"])] defs))] tokens')) - (^ (list& [_ (#Form (list& [_ (#Tag ["" "exclude"])] defs))] tokens'))) + (^or (^ (list& [_ (#Record (list [[_ (#Text "-")] [_ (#Tuple defs)]]))] tokens')) + (^ (list& [_ (#Record (list [[_ (#Text "exclude")] [_ (#Tuple defs)]]))] tokens'))) (do meta_monad [defs' (..referral_references defs)] (in [(#Exclude defs') tokens'])) - (^or (^ (list& [_ (#Tag ["" "*"])] tokens')) - (^ (list& [_ (#Tag ["" "all"])] tokens'))) + (^or (^ (list& [_ (#Text "*")] tokens')) + (^ (list& [_ (#Text "all")] tokens'))) (in_meta [#All tokens']) - (^or (^ (list& [_ (#Tag ["" "_"])] tokens')) - (^ (list& [_ (#Tag ["" "ignore"])] tokens'))) + (^or (^ (list& [_ (#Text "_")] tokens')) + (^ (list& [_ (#Text "ignore")] tokens'))) (in_meta [#Ignore tokens']) _ @@ -4501,13 +4501,13 @@ localizations (: (List Code) (case r_defs #All - (list (' #*)) + (list (' "*")) (#Only defs) - (list (form$ (list& (' #+) (list\each local_identifier$ defs)))) + (list (record$ (list [(' "+") (tuple$ (list\each local_identifier$ defs))]))) (#Exclude defs) - (list (form$ (list& (' #-) (list\each local_identifier$ defs)))) + (list (record$ (list [(' "-") (tuple$ (list\each local_identifier$ defs))]))) #Ignore (list) diff --git a/stdlib/source/library/lux/abstract/algebra.lux b/stdlib/source/library/lux/abstract/algebra.lux index 9a4ea848d..63ce1f2f8 100644 --- a/stdlib/source/library/lux/abstract/algebra.lux +++ b/stdlib/source/library/lux/abstract/algebra.lux @@ -1,8 +1,8 @@ (.module: [library - [lux #* + [lux "*" [control - [functor (#+ Fix)]]]]) + [functor {"+" [Fix]}]]]]) (type: .public (Algebra f a) (-> (f a) a)) diff --git a/stdlib/source/library/lux/abstract/apply.lux b/stdlib/source/library/lux/abstract/apply.lux index c6f6a18a6..f50403a4b 100644 --- a/stdlib/source/library/lux/abstract/apply.lux +++ b/stdlib/source/library/lux/abstract/apply.lux @@ -1,10 +1,10 @@ (.module: [library - [lux #* + [lux "*" ["@" target]]] [// - [monad (#+ Monad)] - ["." functor (#+ Functor)]]) + [monad {"+" [Monad]}] + ["." functor {"+" [Functor]}]]) (type: .public (Apply f) (Interface diff --git a/stdlib/source/library/lux/abstract/codec.lux b/stdlib/source/library/lux/abstract/codec.lux index e5cb66d50..7308a0cd7 100644 --- a/stdlib/source/library/lux/abstract/codec.lux +++ b/stdlib/source/library/lux/abstract/codec.lux @@ -1,10 +1,10 @@ (.module: [library - [lux #* + [lux "*" [control - ["." try (#+ Try)]]]] + ["." try {"+" [Try]}]]]] [// - [monad (#+ do)] + [monad {"+" [do]}] ["." functor]]) (type: .public (Codec m a) diff --git a/stdlib/source/library/lux/abstract/comonad.lux b/stdlib/source/library/lux/abstract/comonad.lux index 06d8640e4..98d8649e8 100644 --- a/stdlib/source/library/lux/abstract/comonad.lux +++ b/stdlib/source/library/lux/abstract/comonad.lux @@ -1,6 +1,6 @@ (.module: [library - [lux #* + [lux "*" [data [collection ["." list ("#\." mix)]]] @@ -10,7 +10,7 @@ [meta ["." location]]]] [// - [functor (#+ Functor)]]) + [functor {"+" [Functor]}]]) (type: .public (CoMonad w) (Interface diff --git a/stdlib/source/library/lux/abstract/comonad/cofree.lux b/stdlib/source/library/lux/abstract/comonad/cofree.lux index f9bfc2dd1..a711f60f1 100644 --- a/stdlib/source/library/lux/abstract/comonad/cofree.lux +++ b/stdlib/source/library/lux/abstract/comonad/cofree.lux @@ -1,9 +1,9 @@ (.module: [library - [lux #*]] - [// (#+ CoMonad) + [lux "*"]] + [// {"+" [CoMonad]} [// - [functor (#+ Functor)]]]) + [functor {"+" [Functor]}]]]) (type: .public (CoFree F a) [a (F (CoFree F a))]) diff --git a/stdlib/source/library/lux/abstract/enum.lux b/stdlib/source/library/lux/abstract/enum.lux index 509669587..fdd7e30e1 100644 --- a/stdlib/source/library/lux/abstract/enum.lux +++ b/stdlib/source/library/lux/abstract/enum.lux @@ -1,8 +1,8 @@ (.module: [library - [lux #*]] + [lux "*"]] [// - ["." order (#+ Order)]]) + ["." order {"+" [Order]}]]) (type: .public (Enum e) (Interface diff --git a/stdlib/source/library/lux/abstract/equivalence.lux b/stdlib/source/library/lux/abstract/equivalence.lux index d51ef9d9a..6e6b2e834 100644 --- a/stdlib/source/library/lux/abstract/equivalence.lux +++ b/stdlib/source/library/lux/abstract/equivalence.lux @@ -1,6 +1,6 @@ (.module: [library - [lux #*]] + [lux "*"]] [// [functor ["." contravariant]]]) diff --git a/stdlib/source/library/lux/abstract/functor.lux b/stdlib/source/library/lux/abstract/functor.lux index a43110453..50ad52f37 100644 --- a/stdlib/source/library/lux/abstract/functor.lux +++ b/stdlib/source/library/lux/abstract/functor.lux @@ -1,6 +1,6 @@ (.module: [library - [lux (#- Or And)]]) + [lux {"-" [Or And]}]]) (type: .public (Functor f) (Interface diff --git a/stdlib/source/library/lux/abstract/functor/contravariant.lux b/stdlib/source/library/lux/abstract/functor/contravariant.lux index 15b8053e6..2e4b563aa 100644 --- a/stdlib/source/library/lux/abstract/functor/contravariant.lux +++ b/stdlib/source/library/lux/abstract/functor/contravariant.lux @@ -1,6 +1,6 @@ (.module: [library - [lux #*]]) + [lux "*"]]) (type: .public (Functor f) (Interface diff --git a/stdlib/source/library/lux/abstract/hash.lux b/stdlib/source/library/lux/abstract/hash.lux index 9b8a599ec..4ad150417 100644 --- a/stdlib/source/library/lux/abstract/hash.lux +++ b/stdlib/source/library/lux/abstract/hash.lux @@ -1,8 +1,8 @@ (.module: [library - [lux #*]] + [lux "*"]] [// - ["." equivalence (#+ Equivalence)] + ["." equivalence {"+" [Equivalence]}] [functor ["." contravariant]]]) diff --git a/stdlib/source/library/lux/abstract/interval.lux b/stdlib/source/library/lux/abstract/interval.lux index d2af3e21c..66b57a5e6 100644 --- a/stdlib/source/library/lux/abstract/interval.lux +++ b/stdlib/source/library/lux/abstract/interval.lux @@ -1,11 +1,11 @@ ... https://en.wikipedia.org/wiki/Interval_(mathematics) (.module: [library - [lux #*]] + [lux "*"]] [// - [equivalence (#+ Equivalence)] + [equivalence {"+" [Equivalence]}] ["." order] - [enum (#+ Enum)]]) + [enum {"+" [Enum]}]]) (type: .public (Interval a) (Interface diff --git a/stdlib/source/library/lux/abstract/mix.lux b/stdlib/source/library/lux/abstract/mix.lux index 432fa6472..0999616bc 100644 --- a/stdlib/source/library/lux/abstract/mix.lux +++ b/stdlib/source/library/lux/abstract/mix.lux @@ -1,8 +1,8 @@ (.module: [library - [lux #*]] + [lux "*"]] [// - [monoid (#+ Monoid)]]) + [monoid {"+" [Monoid]}]]) (type: .public (Mix F) (Interface diff --git a/stdlib/source/library/lux/abstract/monad.lux b/stdlib/source/library/lux/abstract/monad.lux index b4d2eb7ed..d7a9aaf1b 100644 --- a/stdlib/source/library/lux/abstract/monad.lux +++ b/stdlib/source/library/lux/abstract/monad.lux @@ -1,10 +1,10 @@ (.module: [library - [lux #* + [lux "*" [meta ["." location]]]] [// - [functor (#+ Functor)]]) + [functor {"+" [Functor]}]]) (def: (list\mix f init xs) (All (_ a b) diff --git a/stdlib/source/library/lux/abstract/monad/free.lux b/stdlib/source/library/lux/abstract/monad/free.lux index 3dde675a6..2f4d88fcc 100644 --- a/stdlib/source/library/lux/abstract/monad/free.lux +++ b/stdlib/source/library/lux/abstract/monad/free.lux @@ -1,10 +1,10 @@ (.module: [library - [lux #*]] + [lux "*"]] [/// - [functor (#+ Functor)] - [apply (#+ Apply)] - [monad (#+ Monad)]]) + [functor {"+" [Functor]}] + [apply {"+" [Apply]}] + [monad {"+" [Monad]}]]) (type: .public (Free F a) (Variant diff --git a/stdlib/source/library/lux/abstract/monad/indexed.lux b/stdlib/source/library/lux/abstract/monad/indexed.lux index f74790dca..704213215 100644 --- a/stdlib/source/library/lux/abstract/monad/indexed.lux +++ b/stdlib/source/library/lux/abstract/monad/indexed.lux @@ -1,14 +1,14 @@ (.module: [library - [lux #* + [lux "*" [control ["<>" parser - ["<.>" code (#+ Parser)]]] + ["<.>" code {"+" [Parser]}]]] [data [collection ["." list ("#\." functor mix)]]] ["." macro - [syntax (#+ syntax:)] + [syntax {"+" [syntax:]}] ["." code]]]] ["." //]) diff --git a/stdlib/source/library/lux/abstract/monoid.lux b/stdlib/source/library/lux/abstract/monoid.lux index b8a31a356..36b2fe502 100644 --- a/stdlib/source/library/lux/abstract/monoid.lux +++ b/stdlib/source/library/lux/abstract/monoid.lux @@ -1,6 +1,6 @@ (.module: [library - [lux (#- and)]]) + [lux {"-" [and]}]]) (type: .public (Monoid a) (Interface diff --git a/stdlib/source/library/lux/abstract/order.lux b/stdlib/source/library/lux/abstract/order.lux index 6da64656d..067e21e91 100644 --- a/stdlib/source/library/lux/abstract/order.lux +++ b/stdlib/source/library/lux/abstract/order.lux @@ -1,10 +1,10 @@ (.module: [library - [lux #* + [lux "*" [control ["." function]]]] [// - ["." equivalence (#+ Equivalence)] + ["." equivalence {"+" [Equivalence]}] [functor ["." contravariant]]]) diff --git a/stdlib/source/library/lux/abstract/predicate.lux b/stdlib/source/library/lux/abstract/predicate.lux index 16c927ac4..ca38d26d3 100644 --- a/stdlib/source/library/lux/abstract/predicate.lux +++ b/stdlib/source/library/lux/abstract/predicate.lux @@ -1,10 +1,10 @@ (.module: [library - [lux (#- or and) + [lux {"-" [or and]} [control ["." function]]]] [// - [monoid (#+ Monoid)] + [monoid {"+" [Monoid]}] [functor ["." contravariant]]]) diff --git a/stdlib/source/library/lux/control/concatenative.lux b/stdlib/source/library/lux/control/concatenative.lux index 7e8e04ba2..801e9b186 100644 --- a/stdlib/source/library/lux/control/concatenative.lux +++ b/stdlib/source/library/lux/control/concatenative.lux @@ -1,6 +1,6 @@ (.module: [library - [lux (#- Alias if loop) + [lux {"-" [Alias if loop]} ["." meta] [abstract ["." monad]] @@ -8,13 +8,13 @@ ["." maybe ("#\." monad)]] [data ["." text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." list ("#\." mix functor)]]] - ["." macro (#+ with_identifiers) + ["." macro {"+" [with_identifiers]} ["." code] ["." template] - [syntax (#+ syntax:) + [syntax {"+" [syntax:]} ["|.|" annotations]]] [math [number @@ -24,7 +24,7 @@ ["f" frac]]]]] [// ["<>" parser ("#\." monad) - ["<.>" code (#+ Parser)]]]) + ["<.>" code {"+" [Parser]}]]]) (type: Alias [Text Code]) diff --git a/stdlib/source/library/lux/control/concurrency/actor.lux b/stdlib/source/library/lux/control/concurrency/actor.lux index 7353bad84..569a20bd2 100644 --- a/stdlib/source/library/lux/control/concurrency/actor.lux +++ b/stdlib/source/library/lux/control/concurrency/actor.lux @@ -1,40 +1,40 @@ (.module: [library - [lux #* + [lux "*" ["." debug] [abstract monad] [control - [pipe (#+ case>)] + [pipe {"+" [case>]}] ["." function] - ["." try (#+ Try)] - ["." exception (#+ exception:)] - ["." io (#+ IO io)] + ["." try {"+" [Try]}] + ["." exception {"+" [exception:]}] + ["." io {"+" [IO io]}] ["<>" parser ("#\." monad) - ["<.>" code (#+ Parser)]]] + ["<.>" code {"+" [Parser]}]]] [data ["." bit] ["." product] [text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." list ("#\." monoid monad)]]] - ["." macro (#+ with_identifiers) + ["." macro {"+" [with_identifiers]} ["." code] - [syntax (#+ syntax:) + [syntax {"+" [syntax:]} ["|.|" input] ["|.|" annotations]]] [math [number ["n" nat]]] - ["." meta (#+ monad) + ["." meta {"+" [monad]} ["." annotation]] - [type (#+ :sharing) - ["." abstract (#+ abstract: :representation :abstraction)]]]] + [type {"+" [:sharing]} + ["." abstract {"+" [abstract: :representation :abstraction]}]]]] [// - ["." atom (#+ Atom atom)] - ["." async (#+ Async Resolver) ("#\." monad)] - ["." frp (#+ Channel)]]) + ["." atom {"+" [Atom atom]}] + ["." async {"+" [Async Resolver]} ("#\." monad)] + ["." frp {"+" [Channel]}]]) (exception: .public poisoned) (exception: .public dead) diff --git a/stdlib/source/library/lux/control/concurrency/async.lux b/stdlib/source/library/lux/control/concurrency/async.lux index 90229a9f5..6da6384cb 100644 --- a/stdlib/source/library/lux/control/concurrency/async.lux +++ b/stdlib/source/library/lux/control/concurrency/async.lux @@ -1,21 +1,21 @@ (.module: [library - [lux (#- and or) + [lux {"-" [and or]} [abstract - [functor (#+ Functor)] - [apply (#+ Apply)] - ["." monad (#+ Monad do)]] + [functor {"+" [Functor]}] + [apply {"+" [Apply]}] + ["." monad {"+" [Monad do]}]] [control - [pipe (#+ case>)] + [pipe {"+" [case>]}] ["." function] - ["." io (#+ IO io)]] + ["." io {"+" [IO io]}]] [data ["." product]] - [type (#+ :sharing) + [type {"+" [:sharing]} abstract]]] [// ["." thread] - ["." atom (#+ Atom atom)]]) + ["." atom {"+" [Atom atom]}]]) (abstract: .public (Async a) {} diff --git a/stdlib/source/library/lux/control/concurrency/atom.lux b/stdlib/source/library/lux/control/concurrency/atom.lux index 53120a3c4..c1ffafb17 100644 --- a/stdlib/source/library/lux/control/concurrency/atom.lux +++ b/stdlib/source/library/lux/control/concurrency/atom.lux @@ -1,14 +1,14 @@ (.module: [library - [lux #* + [lux "*" ["." macro] ["." ffi] ["@" target] [abstract - [monad (#+ do)]] + [monad {"+" [do]}]] [control ["." function] - ["." io (#+ IO) ("#\." functor)]] + ["." io {"+" [IO]} ("#\." functor)]] [data ["." product] [collection diff --git a/stdlib/source/library/lux/control/concurrency/frp.lux b/stdlib/source/library/lux/control/concurrency/frp.lux index 7c13df0f4..e318bbcd9 100644 --- a/stdlib/source/library/lux/control/concurrency/frp.lux +++ b/stdlib/source/library/lux/control/concurrency/frp.lux @@ -1,21 +1,21 @@ (.module: [library - [lux (#- list) + [lux {"-" [list]} [abstract - [equivalence (#+ Equivalence)] - [functor (#+ Functor)] - [apply (#+ Apply)] - ["." monad (#+ Monad do)]] + [equivalence {"+" [Equivalence]}] + [functor {"+" [Functor]}] + [apply {"+" [Apply]}] + ["." monad {"+" [Monad do]}]] [control ["." maybe ("#\." functor)] - ["." try (#+ Try)] - ["." exception (#+ exception:)] - ["." io (#+ IO io)]] - [type (#+ :sharing) + ["." try {"+" [Try]}] + ["." exception {"+" [exception:]}] + ["." io {"+" [IO io]}]] + [type {"+" [:sharing]} abstract]]] [// - ["." atom (#+ Atom)] - ["." async (#+ Async) ("#\." functor)]]) + ["." atom {"+" [Atom]}] + ["." async {"+" [Async]} ("#\." functor)]]) (type: .public (Channel a) (Async (Maybe [a (Channel a)]))) diff --git a/stdlib/source/library/lux/control/concurrency/semaphore.lux b/stdlib/source/library/lux/control/concurrency/semaphore.lux index 64f3c4af4..806305f0a 100644 --- a/stdlib/source/library/lux/control/concurrency/semaphore.lux +++ b/stdlib/source/library/lux/control/concurrency/semaphore.lux @@ -1,18 +1,18 @@ (.module: [library - [lux #* + [lux "*" [abstract - [monad (#+ do)]] + [monad {"+" [do]}]] [control - [pipe (#+ if>)] - ["." io (#+ IO)] - ["." try (#+ Try)] - ["." exception (#+ exception:)]] + [pipe {"+" [if>]}] + ["." io {"+" [IO]}] + ["." try {"+" [Try]}] + ["." exception {"+" [exception:]}]] [data [text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection - ["." queue (#+ Queue)]]] + ["." queue {"+" [Queue]}]]] [math [number ["n" nat] @@ -21,8 +21,8 @@ abstract ["." refinement]]]] [// - ["." atom (#+ Atom)] - ["." async (#+ Async Resolver)]]) + ["." atom {"+" [Atom]}] + ["." async {"+" [Async Resolver]}]]) (type: State (Record diff --git a/stdlib/source/library/lux/control/concurrency/stm.lux b/stdlib/source/library/lux/control/concurrency/stm.lux index 523227a27..db8b266c8 100644 --- a/stdlib/source/library/lux/control/concurrency/stm.lux +++ b/stdlib/source/library/lux/control/concurrency/stm.lux @@ -1,12 +1,12 @@ (.module: [library - [lux #* + [lux "*" [abstract - [functor (#+ Functor)] - [apply (#+ Apply)] - ["." monad (#+ Monad do)]] + [functor {"+" [Functor]}] + [apply {"+" [Apply]}] + ["." monad {"+" [Monad do]}]] [control - ["." io (#+ IO io)] + ["." io {"+" [IO io]}] ["." maybe] ["." try]] [data @@ -16,9 +16,9 @@ [type abstract]]] [// - ["." atom (#+ Atom atom)] - ["." async (#+ Async Resolver)] - ["." frp (#+ Channel Sink)]]) + ["." atom {"+" [Atom atom]}] + ["." async {"+" [Async Resolver]}] + ["." frp {"+" [Channel Sink]}]]) (type: (Observer a) (-> a (IO Any))) diff --git a/stdlib/source/library/lux/control/concurrency/thread.lux b/stdlib/source/library/lux/control/concurrency/thread.lux index e3a5606c3..40c3d1029 100644 --- a/stdlib/source/library/lux/control/concurrency/thread.lux +++ b/stdlib/source/library/lux/control/concurrency/thread.lux @@ -1,14 +1,14 @@ (.module: [library - [lux #* + [lux "*" ["@" target] ["." ffi] [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control ["." try] - ["." exception (#+ exception:)] - ["." io (#+ IO io)]] + ["." exception {"+" [exception:]}] + ["." io {"+" [IO io]}]] [data ["." text] [collection @@ -20,7 +20,7 @@ [time ["." instant]]]] [// - ["." atom (#+ Atom)]]) + ["." atom {"+" [Atom]}]]) (with_expansions [<jvm> (as_is (ffi.import: java/lang/Object) diff --git a/stdlib/source/library/lux/control/continuation.lux b/stdlib/source/library/lux/control/continuation.lux index ab9ec5ad7..48b752ef5 100644 --- a/stdlib/source/library/lux/control/continuation.lux +++ b/stdlib/source/library/lux/control/continuation.lux @@ -1,16 +1,16 @@ (.module: [library - [lux #* + [lux "*" [abstract - [functor (#+ Functor)] - [apply (#+ Apply)] - [monad (#+ Monad do)]] + [functor {"+" [Functor]}] + [apply {"+" [Apply]}] + [monad {"+" [Monad do]}]] [control ["." function] [parser ["<.>" code]]] - [macro (#+ with_identifiers) - [syntax (#+ syntax:)] + [macro {"+" [with_identifiers]} + [syntax {"+" [syntax:]}] ["." code]]]]) (type: .public (Cont i o) diff --git a/stdlib/source/library/lux/control/exception.lux b/stdlib/source/library/lux/control/exception.lux index 17de72095..49daeec7e 100644 --- a/stdlib/source/library/lux/control/exception.lux +++ b/stdlib/source/library/lux/control/exception.lux @@ -1,14 +1,14 @@ (.module: [library - [lux #* + [lux "*" ["." macro] ["." meta] [abstract - [monad (#+ do)]] + [monad {"+" [do]}]] [control ["." maybe] ["<>" parser ("#\." monad) - ["<.>" code (#+ Parser)]]] + ["<.>" code {"+" [Parser]}]]] [data ["." product] ["." text ("#\." monoid)] @@ -16,15 +16,15 @@ ["." list ("#\." functor mix)]]] [macro ["." code] - [syntax (#+ syntax:) + [syntax {"+" [syntax:]} ["|.|" input] - ["." type #_ + ["." type "_" ["|#_.|" variable]]]] [math [number ["n" nat ("#\." decimal)]]]]] [// - ["//" try (#+ Try)]]) + ["//" try {"+" [Try]}]]) (type: .public (Exception a) (Record diff --git a/stdlib/source/library/lux/control/function.lux b/stdlib/source/library/lux/control/function.lux index 41ac6eeeb..d8ff77379 100644 --- a/stdlib/source/library/lux/control/function.lux +++ b/stdlib/source/library/lux/control/function.lux @@ -1,8 +1,8 @@ (.module: [library - [lux #* + [lux "*" [abstract - [monoid (#+ Monoid)]]]]) + [monoid {"+" [Monoid]}]]]]) (def: .public identity (All (_ a) (-> a a)) diff --git a/stdlib/source/library/lux/control/function/contract.lux b/stdlib/source/library/lux/control/function/contract.lux index b568a7068..b101cc43f 100644 --- a/stdlib/source/library/lux/control/function/contract.lux +++ b/stdlib/source/library/lux/control/function/contract.lux @@ -1,15 +1,15 @@ (.module: [library - [lux #* + [lux "*" [control - ["." exception (#+ exception:)] + ["." exception {"+" [exception:]}] [parser ["<.>" code]]] [data [text - ["%" format (#+ format)]]] - [macro (#+ with_identifiers) - [syntax (#+ syntax:)] + ["%" format {"+" [format]}]]] + [macro {"+" [with_identifiers]} + [syntax {"+" [syntax:]}] ["." code]] [math [number diff --git a/stdlib/source/library/lux/control/function/memo.lux b/stdlib/source/library/lux/control/function/memo.lux index 233ee8d07..40b9dbc7e 100644 --- a/stdlib/source/library/lux/control/function/memo.lux +++ b/stdlib/source/library/lux/control/function/memo.lux @@ -2,18 +2,18 @@ ... "The Different Aspects of Monads and Mixins" by Bruno C. d. S. Oliveira (.module: [library - [lux #* + [lux "*" [abstract - [hash (#+ Hash)] - [monad (#+ do)]] + [hash {"+" [Hash]}] + [monad {"+" [do]}]] [control - ["." state (#+ State)]] + ["." state {"+" [State]}]] [data ["." product] [collection - ["." dictionary (#+ Dictionary)]]]]] - ["." // #_ - ["#" mixin (#+ Mixin Recursive)]]) + ["." dictionary {"+" [Dictionary]}]]]]] + ["." // "_" + ["#" mixin {"+" [Mixin Recursive]}]]) (def: .public memoization (All (_ i o) diff --git a/stdlib/source/library/lux/control/function/mixin.lux b/stdlib/source/library/lux/control/function/mixin.lux index 357fdb7c1..7c3c0779a 100644 --- a/stdlib/source/library/lux/control/function/mixin.lux +++ b/stdlib/source/library/lux/control/function/mixin.lux @@ -3,11 +3,11 @@ (.module: [library - [lux #* + [lux "*" [abstract - [monoid (#+ Monoid)] - [predicate (#+ Predicate)] - [monad (#+ Monad do)]]]]) + [monoid {"+" [Monoid]}] + [predicate {"+" [Predicate]}] + [monad {"+" [Monad do]}]]]]) (type: .public (Mixin i o) (-> (-> i o) (-> i o) (-> i o))) diff --git a/stdlib/source/library/lux/control/function/mutual.lux b/stdlib/source/library/lux/control/function/mutual.lux index f303eff44..11c2ca416 100644 --- a/stdlib/source/library/lux/control/function/mutual.lux +++ b/stdlib/source/library/lux/control/function/mutual.lux @@ -1,27 +1,27 @@ (.module: [library - [lux (#- Definition let def: macro) + [lux {"-" [Definition let def: macro]} ["." meta] [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control - ["." try (#+ Try)] - ["." exception (#+ exception:)] + ["." try {"+" [Try]}] + ["." exception {"+" [exception:]}] ["<>" parser ("#\." monad) - ["<.>" code (#+ Parser)]]] + ["<.>" code {"+" [Parser]}]]] [data ["." product] [text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." list ("#\." functor)] [dictionary - ["." plist (#+ PList)]]]] + ["." plist {"+" [PList]}]]]] ["." macro ["." local] ["." code] - [syntax (#+ syntax:) - ["." declaration (#+ Declaration)]]]]] + [syntax {"+" [syntax:]} + ["." declaration {"+" [Declaration]}]]]]] ["." //]) (type: Mutual diff --git a/stdlib/source/library/lux/control/io.lux b/stdlib/source/library/lux/control/io.lux index c72bffa73..d7aac7fed 100644 --- a/stdlib/source/library/lux/control/io.lux +++ b/stdlib/source/library/lux/control/io.lux @@ -1,17 +1,17 @@ (.module: [library - [lux #* + [lux "*" [abstract - [functor (#+ Functor)] - [apply (#+ Apply)] - [monad (#+ Monad do)]] + [functor {"+" [Functor]}] + [apply {"+" [Apply]}] + [monad {"+" [Monad do]}]] [control [parser ["<.>" code]]] [type abstract] - [macro (#+ with_identifiers) - [syntax (#+ syntax:)] + [macro {"+" [with_identifiers]} + [syntax {"+" [syntax:]}] ["." template]]]]) (abstract: .public (IO a) diff --git a/stdlib/source/library/lux/control/lazy.lux b/stdlib/source/library/lux/control/lazy.lux index 4539fdc15..b4a3567d4 100644 --- a/stdlib/source/library/lux/control/lazy.lux +++ b/stdlib/source/library/lux/control/lazy.lux @@ -1,19 +1,19 @@ (.module: [library - [lux #* + [lux "*" [abstract - [functor (#+ Functor)] - [apply (#+ Apply)] - [monad (#+ Monad do)] - [equivalence (#+ Equivalence)]] + [functor {"+" [Functor]}] + [apply {"+" [Apply]}] + [monad {"+" [Monad do]}] + [equivalence {"+" [Equivalence]}]] [control ["." io] [parser ["<.>" code]] [concurrency ["." atom]]] - [macro (#+ with_identifiers) - [syntax (#+ syntax:)]] + [macro {"+" [with_identifiers]} + [syntax {"+" [syntax:]}]] [type abstract]]]) diff --git a/stdlib/source/library/lux/control/maybe.lux b/stdlib/source/library/lux/control/maybe.lux index cccf64ddf..1131dbe49 100644 --- a/stdlib/source/library/lux/control/maybe.lux +++ b/stdlib/source/library/lux/control/maybe.lux @@ -1,13 +1,13 @@ (.module: [library - [lux (#- list) + [lux {"-" [list]} [abstract - [monoid (#+ Monoid)] - [equivalence (#+ Equivalence)] - [hash (#+ Hash)] - [apply (#+ Apply)] - ["." functor (#+ Functor)] - ["." monad (#+ Monad do)]] + [monoid {"+" [Monoid]}] + [equivalence {"+" [Equivalence]}] + [hash {"+" [Hash]}] + [apply {"+" [Apply]}] + ["." functor {"+" [Functor]}] + ["." monad {"+" [Monad do]}]] [meta ["." location]]]]) diff --git a/stdlib/source/library/lux/control/parser.lux b/stdlib/source/library/lux/control/parser.lux index 376ca3f53..0bb2b1782 100644 --- a/stdlib/source/library/lux/control/parser.lux +++ b/stdlib/source/library/lux/control/parser.lux @@ -1,13 +1,13 @@ (.module: [library - [lux (#- or and not) + [lux {"-" [or and not]} [abstract - [functor (#+ Functor)] - [apply (#+ Apply)] - [monad (#+ Monad do)] - [codec (#+ Codec)]] + [functor {"+" [Functor]}] + [apply {"+" [Apply]}] + [monad {"+" [Monad do]}] + [codec {"+" [Codec]}]] [control - ["." try (#+ Try)]] + ["." try {"+" [Try]}]] [data ["." product] [collection diff --git a/stdlib/source/library/lux/control/parser/analysis.lux b/stdlib/source/library/lux/control/parser/analysis.lux index e069d4e9f..0744391c2 100644 --- a/stdlib/source/library/lux/control/parser/analysis.lux +++ b/stdlib/source/library/lux/control/parser/analysis.lux @@ -1,16 +1,16 @@ (.module: [library - [lux (#- Tuple Variant nat int rev local) + [lux {"-" [Tuple Variant nat int rev local]} [abstract - [monad (#+ do)]] + [monad {"+" [do]}]] [control - ["." try (#+ Try)] - ["." exception (#+ exception:)]] + ["." try {"+" [Try]}] + ["." exception {"+" [exception:]}]] [data ["." bit] ["." name] ["." text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." list ("#\." functor)]]] [macro @@ -24,12 +24,12 @@ ["." frac]]] [tool [compiler - [arity (#+ Arity)] - [reference (#+) - [variable (#+)]] + [arity {"+" [Arity]}] + [reference {"+" []} + [variable {"+" []}]] [language [lux - ["/" analysis (#+ Variant Tuple Environment Analysis)]]]]]]] + ["/" analysis {"+" [Variant Tuple Environment Analysis]}]]]]]]] ["." //]) (def: (remaining_inputs asts) diff --git a/stdlib/source/library/lux/control/parser/binary.lux b/stdlib/source/library/lux/control/parser/binary.lux index 6c0f82a06..d55ac46ff 100644 --- a/stdlib/source/library/lux/control/parser/binary.lux +++ b/stdlib/source/library/lux/control/parser/binary.lux @@ -1,23 +1,23 @@ (.module: [library - [lux (#- and or nat int rev list type) - [type (#+ :sharing)] + [lux {"-" [and or nat int rev list type]} + [type {"+" [:sharing]}] [abstract - [hash (#+ Hash)] - [monad (#+ do)]] + [hash {"+" [Hash]}] + [monad {"+" [do]}]] [control - ["." try (#+ Try)] - ["." exception (#+ exception:)]] + ["." try {"+" [Try]}] + ["." exception {"+" [exception:]}]] [data - ["/" binary (#+ Binary)] + ["/" binary {"+" [Binary]}] [text - ["%" format (#+ format)] + ["%" format {"+" [format]}] [encoding ["." utf8]]] [collection ["." list] - ["." row (#+ Row)] - ["." set (#+ Set)]]] + ["." row {"+" [Row]}] + ["." set {"+" [Set]}]]] [macro ["." template]] [math diff --git a/stdlib/source/library/lux/control/parser/cli.lux b/stdlib/source/library/lux/control/parser/cli.lux index 75ab5ab4b..4a7e4149e 100644 --- a/stdlib/source/library/lux/control/parser/cli.lux +++ b/stdlib/source/library/lux/control/parser/cli.lux @@ -1,13 +1,13 @@ (.module: [library - [lux #* + [lux "*" [abstract - [monad (#+ do)]] + [monad {"+" [do]}]] [control - ["." try (#+ Try)]] + ["." try {"+" [Try]}]] [data ["." text ("#\." equivalence) - ["%" format (#+ format)]]]]] + ["%" format {"+" [format]}]]]]] ["." //]) (type: .public (Parser a) diff --git a/stdlib/source/library/lux/control/parser/code.lux b/stdlib/source/library/lux/control/parser/code.lux index 63b33e341..2b8e7d799 100644 --- a/stdlib/source/library/lux/control/parser/code.lux +++ b/stdlib/source/library/lux/control/parser/code.lux @@ -1,10 +1,10 @@ (.module: [library - [lux (#- nat int rev local not) + [lux {"-" [nat int rev local not]} [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control - ["." try (#+ Try)]] + ["." try {"+" [Try]}]] [data ["." bit] ["." text ("#\." monoid)] diff --git a/stdlib/source/library/lux/control/parser/environment.lux b/stdlib/source/library/lux/control/parser/environment.lux index 8ca8e2890..ad4d2c3c9 100644 --- a/stdlib/source/library/lux/control/parser/environment.lux +++ b/stdlib/source/library/lux/control/parser/environment.lux @@ -1,15 +1,15 @@ (.module: [library - [lux #* + [lux "*" [control - ["." try (#+ Try)] - ["." exception (#+ exception:)]] + ["." try {"+" [Try]}] + ["." exception {"+" [exception:]}]] [data ["." product] ["." text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection - ["." dictionary (#+ Dictionary)]]]]] + ["." dictionary {"+" [Dictionary]}]]]]] ["." //]) (type: .public Property diff --git a/stdlib/source/library/lux/control/parser/json.lux b/stdlib/source/library/lux/control/parser/json.lux index f73bf4ce8..02b5c406a 100644 --- a/stdlib/source/library/lux/control/parser/json.lux +++ b/stdlib/source/library/lux/control/parser/json.lux @@ -1,20 +1,20 @@ (.module: [library - [lux #* + [lux "*" [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control - ["." try (#+ Try)] - ["." exception (#+ exception:)]] + ["." try {"+" [Try]}] + ["." exception {"+" [exception:]}]] [data ["." bit] ["." text ("#\." equivalence monoid)] [collection ["." list ("#\." functor)] ["." row] - ["." dictionary (#+ Dictionary)]] + ["." dictionary {"+" [Dictionary]}]] [format - ["/" json (#+ JSON)]]] + ["/" json {"+" [JSON]}]]] [macro ["." code]] [math diff --git a/stdlib/source/library/lux/control/parser/synthesis.lux b/stdlib/source/library/lux/control/parser/synthesis.lux index 07406f1d9..224eee314 100644 --- a/stdlib/source/library/lux/control/parser/synthesis.lux +++ b/stdlib/source/library/lux/control/parser/synthesis.lux @@ -1,16 +1,16 @@ (.module: [library - [lux (#- Tuple Variant function loop i64 local) + [lux {"-" [Tuple Variant function loop i64 local]} [abstract - [monad (#+ do)]] + [monad {"+" [do]}]] [control - ["." try (#+ Try)] - ["." exception (#+ exception:)]] + ["." try {"+" [Try]}] + ["." exception {"+" [exception:]}]] [data ["." bit] ["." name] ["." text - ["%" format (#+ format)]]] + ["%" format {"+" [format]}]]] [math [number ["n" nat] @@ -18,13 +18,13 @@ ["." frac]]] [tool [compiler - [reference (#+) - [variable (#+ Register)]] - [arity (#+ Arity)] + [reference {"+" []} + [variable {"+" [Register]}]] + [arity {"+" [Arity]}] [language [lux - [analysis (#+ Variant Tuple Environment)] - ["/" synthesis (#+ Synthesis Abstraction)]]]]]]] + [analysis {"+" [Variant Tuple Environment]}] + ["/" synthesis {"+" [Synthesis Abstraction]}]]]]]]] ["." //]) (exception: .public (cannot_parse {input (List Synthesis)}) diff --git a/stdlib/source/library/lux/control/parser/text.lux b/stdlib/source/library/lux/control/parser/text.lux index e19eb72a4..2d3e404d8 100644 --- a/stdlib/source/library/lux/control/parser/text.lux +++ b/stdlib/source/library/lux/control/parser/text.lux @@ -1,14 +1,14 @@ (.module: [library - [lux (#- or and not local) + [lux {"-" [or and not local]} [abstract - [monad (#+ Monad do)]] + [monad {"+" [Monad do]}]] [control ["." maybe] - ["." try (#+ Try)] - ["." exception (#+ exception:)]] + ["." try {"+" [Try]}] + ["." exception {"+" [exception:]}]] [data - ["/" text (#+ Char) ("#\." monoid)] + ["/" text {"+" [Char]} ("#\." monoid)] ["." product] [collection ["." list ("#\." mix)]]] diff --git a/stdlib/source/library/lux/control/parser/tree.lux b/stdlib/source/library/lux/control/parser/tree.lux index 4c87f17f3..4b8f9e2a3 100644 --- a/stdlib/source/library/lux/control/parser/tree.lux +++ b/stdlib/source/library/lux/control/parser/tree.lux @@ -1,15 +1,15 @@ (.module: [library - [lux #* + [lux "*" [abstract - [monad (#+ do)]] + [monad {"+" [do]}]] [control - ["." try (#+ Try)] - ["." exception (#+ exception:)]] + ["." try {"+" [Try]}] + ["." exception {"+" [exception:]}]] [data [collection - [tree (#+ Tree) - ["." zipper (#+ Zipper)]]]]]] + [tree {"+" [Tree]} + ["." zipper {"+" [Zipper]}]]]]]] ["." //]) (type: .public (Parser t a) diff --git a/stdlib/source/library/lux/control/parser/type.lux b/stdlib/source/library/lux/control/parser/type.lux index 96a2c6230..6c033af34 100644 --- a/stdlib/source/library/lux/control/parser/type.lux +++ b/stdlib/source/library/lux/control/parser/type.lux @@ -1,18 +1,18 @@ (.module: [library - [lux (#- function local) + [lux {"-" [function local]} [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control - ["." try (#+ Try)] - ["." exception (#+ exception:)] + ["." try {"+" [Try]}] + ["." exception {"+" [exception:]}] ["." function]] [data ["." text ("#\." monoid) - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." list ("#\." functor)] - ["." dictionary (#+ Dictionary)]]] + ["." dictionary {"+" [Dictionary]}]]] [macro ["." code]] [math diff --git a/stdlib/source/library/lux/control/parser/xml.lux b/stdlib/source/library/lux/control/parser/xml.lux index 4a41dd75d..66b5da36f 100644 --- a/stdlib/source/library/lux/control/parser/xml.lux +++ b/stdlib/source/library/lux/control/parser/xml.lux @@ -1,20 +1,20 @@ (.module: [library - [lux #* + [lux "*" [abstract - [monad (#+ do)]] + [monad {"+" [do]}]] [control - ["." try (#+ Try) ("#\." functor)] - ["." exception (#+ exception:)]] + ["." try {"+" [Try]} ("#\." functor)] + ["." exception {"+" [exception:]}]] [data ["." name ("#\." equivalence codec)] ["." text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." list] ["." dictionary]] [format - ["/" xml (#+ Attribute Attrs Tag XML)]]]]] + ["/" xml {"+" [Attribute Attrs Tag XML]}]]]]] ["." //]) (type: .public (Parser a) diff --git a/stdlib/source/library/lux/control/pipe.lux b/stdlib/source/library/lux/control/pipe.lux index 760dfb143..f8370f8b1 100644 --- a/stdlib/source/library/lux/control/pipe.lux +++ b/stdlib/source/library/lux/control/pipe.lux @@ -1,18 +1,18 @@ (.module: [library - [lux #* + [lux "*" [abstract - [monad (#+ do)]] + [monad {"+" [do]}]] [control ["." try] ["<>" parser - ["<.>" code (#+ Parser)]]] + ["<.>" code {"+" [Parser]}]]] [data ["." identity] [collection ["." list ("#\." monad)]]] - [macro (#+ with_identifiers) - [syntax (#+ syntax:)] + [macro {"+" [with_identifiers]} + [syntax {"+" [syntax:]}] ["." code]] [math [number diff --git a/stdlib/source/library/lux/control/reader.lux b/stdlib/source/library/lux/control/reader.lux index 6800a5e3c..91439facf 100644 --- a/stdlib/source/library/lux/control/reader.lux +++ b/stdlib/source/library/lux/control/reader.lux @@ -1,10 +1,10 @@ (.module: [library - [lux (#- local) + [lux {"-" [local]} [abstract - [apply (#+ Apply)] - ["." functor (#+ Functor)] - ["." monad (#+ Monad do)]]]]) + [apply {"+" [Apply]}] + ["." functor {"+" [Functor]}] + ["." monad {"+" [Monad do]}]]]]) (type: .public (Reader r a) (-> r a)) diff --git a/stdlib/source/library/lux/control/region.lux b/stdlib/source/library/lux/control/region.lux index e07656688..536b34391 100644 --- a/stdlib/source/library/lux/control/region.lux +++ b/stdlib/source/library/lux/control/region.lux @@ -1,19 +1,19 @@ (.module: [library - [lux #* + [lux "*" [abstract - [functor (#+ Functor)] - [apply (#+ Apply)] - ["." monad (#+ Monad do)]] + [functor {"+" [Functor]}] + [apply {"+" [Apply]}] + ["." monad {"+" [Monad do]}]] [control - ["." try (#+ Try)]] + ["." try {"+" [Try]}]] [data ["." text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." list ("#\." mix)]]]]] [// - ["." exception (#+ Exception exception:)]]) + ["." exception {"+" [Exception exception:]}]]) (type: (Cleaner r !) (-> r (! (Try Any)))) diff --git a/stdlib/source/library/lux/control/remember.lux b/stdlib/source/library/lux/control/remember.lux index 8ba79f6a7..f220af759 100644 --- a/stdlib/source/library/lux/control/remember.lux +++ b/stdlib/source/library/lux/control/remember.lux @@ -1,25 +1,25 @@ (.module: [library - [lux #* + [lux "*" [abstract - [monad (#+ do)]] + [monad {"+" [do]}]] [control ["." io] ["." try] - ["." exception (#+ exception:)] + ["." exception {"+" [exception:]}] ["<>" parser ("#\." functor) - ["<c>" code (#+ Parser)]]] + ["<c>" code {"+" [Parser]}]]] [data ["." text - ["%" format (#+ format)]]] + ["%" format {"+" [format]}]]] [time ["." instant] - ["." date (#+ Date) ("#\." order)]] + ["." date {"+" [Date]} ("#\." order)]] ["." meta] [macro ["." code] ["." template] - [syntax (#+ syntax:)]]]]) + [syntax {"+" [syntax:]}]]]]) (exception: .public (must_remember {deadline Date} {today Date} {message Text} {focus (Maybe Code)}) (exception.report diff --git a/stdlib/source/library/lux/control/security/capability.lux b/stdlib/source/library/lux/control/security/capability.lux index e6d2617c9..9c41e5899 100644 --- a/stdlib/source/library/lux/control/security/capability.lux +++ b/stdlib/source/library/lux/control/security/capability.lux @@ -1,17 +1,17 @@ (.module: [library - [lux #* + [lux "*" [abstract - [monad (#+ do)]] + [monad {"+" [do]}]] [control - ["." io (#+ IO)] + ["." io {"+" [IO]}] ["<>" parser ["<c>" code]] [concurrency - ["." async (#+ Async)]]] + ["." async {"+" [Async]}]]] [data [text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." list ("#\." functor)]]] [type @@ -19,7 +19,7 @@ ["." meta] ["." macro ["." code] - [syntax (#+ syntax:) + [syntax {"+" [syntax:]} ["|.|" export] ["|.|" declaration] ["|.|" annotations]]]]]) diff --git a/stdlib/source/library/lux/control/security/policy.lux b/stdlib/source/library/lux/control/security/policy.lux index 44d233cde..498469d63 100644 --- a/stdlib/source/library/lux/control/security/policy.lux +++ b/stdlib/source/library/lux/control/security/policy.lux @@ -1,10 +1,10 @@ (.module: [library - [lux #* + [lux "*" [abstract - [functor (#+ Functor)] - [apply (#+ Apply)] - [monad (#+ Monad)]] + [functor {"+" [Functor]}] + [apply {"+" [Apply]}] + [monad {"+" [Monad]}]] [type abstract]]]) diff --git a/stdlib/source/library/lux/control/state.lux b/stdlib/source/library/lux/control/state.lux index a056cb49b..b8430ce91 100644 --- a/stdlib/source/library/lux/control/state.lux +++ b/stdlib/source/library/lux/control/state.lux @@ -1,10 +1,10 @@ (.module: [library - [lux (#- local) + [lux {"-" [local]} [abstract - [functor (#+ Functor)] - [apply (#+ Apply)] - [monad (#+ Monad do)]]]]) + [functor {"+" [Functor]}] + [apply {"+" [Apply]}] + [monad {"+" [Monad do]}]]]]) (type: .public (State s a) (-> s [s a])) diff --git a/stdlib/source/library/lux/control/thread.lux b/stdlib/source/library/lux/control/thread.lux index d938ddb88..660be7bd1 100644 --- a/stdlib/source/library/lux/control/thread.lux +++ b/stdlib/source/library/lux/control/thread.lux @@ -1,16 +1,16 @@ (.module: [library - [lux #* + [lux "*" ["@" target] [abstract - [functor (#+ Functor)] - [apply (#+ Apply)] - [monad (#+ Monad do)]] + [functor {"+" [Functor]}] + [apply {"+" [Apply]}] + [monad {"+" [Monad do]}]] [control - ["." io (#+ IO)]] + ["." io {"+" [IO]}]] [data [collection - ["." array (#+ Array)]]] + ["." array {"+" [Array]}]]] [type abstract]]]) diff --git a/stdlib/source/library/lux/control/try.lux b/stdlib/source/library/lux/control/try.lux index a4ceae85d..1d3535ba2 100644 --- a/stdlib/source/library/lux/control/try.lux +++ b/stdlib/source/library/lux/control/try.lux @@ -1,11 +1,11 @@ (.module: [library - [lux #* + [lux "*" [abstract - [apply (#+ Apply)] - [equivalence (#+ Equivalence)] - ["." functor (#+ Functor)] - ["." monad (#+ Monad do)]] + [apply {"+" [Apply]}] + [equivalence {"+" [Equivalence]}] + ["." functor {"+" [Functor]}] + ["." monad {"+" [Monad do]}]] [meta ["." location]]]]) diff --git a/stdlib/source/library/lux/control/writer.lux b/stdlib/source/library/lux/control/writer.lux index 771bb95a5..74b0c997b 100644 --- a/stdlib/source/library/lux/control/writer.lux +++ b/stdlib/source/library/lux/control/writer.lux @@ -1,12 +1,12 @@ (.module: [library - [lux #* + [lux "*" ["@" target] [abstract - [monoid (#+ Monoid)] - [apply (#+ Apply)] - ["." functor (#+ Functor)] - ["." monad (#+ Monad do)]]]]) + [monoid {"+" [Monoid]}] + [apply {"+" [Apply]}] + ["." functor {"+" [Functor]}] + ["." monad {"+" [Monad do]}]]]]) (type: .public (Writer log value) (Record diff --git a/stdlib/source/library/lux/data/binary.lux b/stdlib/source/library/lux/data/binary.lux index c4dd05e8e..2f56f33aa 100644 --- a/stdlib/source/library/lux/data/binary.lux +++ b/stdlib/source/library/lux/data/binary.lux @@ -1,23 +1,23 @@ (.module: [library - [lux (#- i64) + [lux {"-" [i64]} ["@" target] ["." ffi] [abstract - [monad (#+ do)] - [equivalence (#+ Equivalence)] - [monoid (#+ Monoid)]] + [monad {"+" [do]}] + [equivalence {"+" [Equivalence]}] + [monoid {"+" [Monoid]}]] [control ["." maybe] - ["." try (#+ Try)] - ["." exception (#+ exception:)]] + ["." try {"+" [Try]}] + ["." exception {"+" [exception:]}]] [data [text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." array]]] [math - [number (#+ hex) + [number {"+" [hex]} ["n" nat] ["f" frac] ["." i64]]]]]) diff --git a/stdlib/source/library/lux/data/bit.lux b/stdlib/source/library/lux/data/bit.lux index 238f87e5d..b0fd566db 100644 --- a/stdlib/source/library/lux/data/bit.lux +++ b/stdlib/source/library/lux/data/bit.lux @@ -1,11 +1,11 @@ (.module: [library - [lux #* + [lux "*" [abstract - [monoid (#+ Monoid)] - [equivalence (#+ Equivalence)] - [hash (#+ Hash)] - [codec (#+ Codec)]] + [monoid {"+" [Monoid]}] + [equivalence {"+" [Equivalence]}] + [hash {"+" [Hash]}] + [codec {"+" [Codec]}]] [control ["." function]]]]) diff --git a/stdlib/source/library/lux/data/collection/array.lux b/stdlib/source/library/lux/data/collection/array.lux index 92586e228..0574b2fe7 100644 --- a/stdlib/source/library/lux/data/collection/array.lux +++ b/stdlib/source/library/lux/data/collection/array.lux @@ -1,13 +1,13 @@ (.module: [library - [lux (#- list) + [lux {"-" [list]} ["@" target] [abstract - [monoid (#+ Monoid)] - [functor (#+ Functor)] - [equivalence (#+ Equivalence)] - [mix (#+ Mix)] - [predicate (#+ Predicate)]] + [monoid {"+" [Monoid]}] + [functor {"+" [Functor]}] + [equivalence {"+" [Equivalence]}] + [mix {"+" [Mix]}] + [predicate {"+" [Predicate]}]] [control ["." maybe]] [data diff --git a/stdlib/source/library/lux/data/collection/bits.lux b/stdlib/source/library/lux/data/collection/bits.lux index 34e45b10f..b218e57bf 100644 --- a/stdlib/source/library/lux/data/collection/bits.lux +++ b/stdlib/source/library/lux/data/collection/bits.lux @@ -1,14 +1,14 @@ (.module: [library - [lux (#- not and or) + [lux {"-" [not and or]} [abstract - [equivalence (#+ Equivalence)]] + [equivalence {"+" [Equivalence]}]] [control pipe ["." maybe]] [data [collection - ["." array (#+ Array) ("#\." mix)]]] + ["." array {"+" [Array]} ("#\." mix)]]] [math [number ["n" nat] diff --git a/stdlib/source/library/lux/data/collection/dictionary.lux b/stdlib/source/library/lux/data/collection/dictionary.lux index becef793e..1418b56d6 100644 --- a/stdlib/source/library/lux/data/collection/dictionary.lux +++ b/stdlib/source/library/lux/data/collection/dictionary.lux @@ -1,19 +1,19 @@ (.module: [library - [lux #* + [lux "*" [abstract - [hash (#+ Hash)] - [equivalence (#+ Equivalence)] - [functor (#+ Functor)]] + [hash {"+" [Hash]}] + [equivalence {"+" [Equivalence]}] + [functor {"+" [Functor]}]] [control ["." maybe] - ["." try (#+ Try)] - ["." exception (#+ exception:)]] + ["." try {"+" [Try]}] + ["." exception {"+" [exception:]}]] [data ["." product] [collection ["." list ("#\." mix functor monoid)] - ["." array (#+ Array) ("#\." functor mix)]]] + ["." array {"+" [Array]} ("#\." functor mix)]]] [math ["." number ["n" nat] diff --git a/stdlib/source/library/lux/data/collection/dictionary/ordered.lux b/stdlib/source/library/lux/data/collection/dictionary/ordered.lux index 81096ddef..a18f5b7ce 100644 --- a/stdlib/source/library/lux/data/collection/dictionary/ordered.lux +++ b/stdlib/source/library/lux/data/collection/dictionary/ordered.lux @@ -1,10 +1,10 @@ (.module: [library - [lux #* + [lux "*" [abstract equivalence - [monad (#+ Monad do)] - ["." order (#+ Order)]] + [monad {"+" [Monad do]}] + ["." order {"+" [Order]}]] [control ["." maybe]] [data diff --git a/stdlib/source/library/lux/data/collection/dictionary/plist.lux b/stdlib/source/library/lux/data/collection/dictionary/plist.lux index b5f04aa4a..d26859f71 100644 --- a/stdlib/source/library/lux/data/collection/dictionary/plist.lux +++ b/stdlib/source/library/lux/data/collection/dictionary/plist.lux @@ -1,8 +1,8 @@ (.module: [library - [lux #* + [lux "*" [abstract - [equivalence (#+ Equivalence)]] + [equivalence {"+" [Equivalence]}]] [data ["." product] ["." text ("#\." equivalence)] diff --git a/stdlib/source/library/lux/data/collection/list.lux b/stdlib/source/library/lux/data/collection/list.lux index 5649dacec..ce9b246bd 100644 --- a/stdlib/source/library/lux/data/collection/list.lux +++ b/stdlib/source/library/lux/data/collection/list.lux @@ -1,16 +1,16 @@ (.module: [library - [lux #* + [lux "*" ["@" target] [abstract - [monoid (#+ Monoid)] - [apply (#+ Apply)] - [equivalence (#+ Equivalence)] - [hash (#+ Hash)] - [mix (#+ Mix)] - [predicate (#+ Predicate)] - ["." functor (#+ Functor)] - ["." monad (#+ do Monad)] + [monoid {"+" [Monoid]}] + [apply {"+" [Apply]}] + [equivalence {"+" [Equivalence]}] + [hash {"+" [Hash]}] + [mix {"+" [Mix]}] + [predicate {"+" [Predicate]}] + ["." functor {"+" [Functor]}] + ["." monad {"+" [Monad do]}] ["." enum]] [data ["." bit] diff --git a/stdlib/source/library/lux/data/collection/queue.lux b/stdlib/source/library/lux/data/collection/queue.lux index deb07edb2..12bb5b68e 100644 --- a/stdlib/source/library/lux/data/collection/queue.lux +++ b/stdlib/source/library/lux/data/collection/queue.lux @@ -1,9 +1,9 @@ (.module: [library - [lux (#- list) + [lux {"-" [list]} [abstract - [equivalence (#+ Equivalence)] - [functor (#+ Functor)]] + [equivalence {"+" [Equivalence]}] + [functor {"+" [Functor]}]] [data [collection ["." list ("#\." monoid functor)]]] diff --git a/stdlib/source/library/lux/data/collection/queue/priority.lux b/stdlib/source/library/lux/data/collection/queue/priority.lux index d3fb97cbb..7d609c439 100644 --- a/stdlib/source/library/lux/data/collection/queue/priority.lux +++ b/stdlib/source/library/lux/data/collection/queue/priority.lux @@ -1,20 +1,20 @@ (.module: [library - [lux #* + [lux "*" [abstract - [equivalence (#+ Equivalence)] - [monad (#+ do)]] + [equivalence {"+" [Equivalence]}] + [monad {"+" [do]}]] [control ["." maybe]] [data [collection - ["." tree #_ - ["#" finger (#+ Tree)]]]] + ["." tree "_" + ["#" finger {"+" [Tree]}]]]] [math [number ["n" nat ("#\." interval)]]] - [type (#+ :by_example) - [abstract (#+ abstract: :abstraction :representation)]]]]) + [type {"+" [:by_example]} + [abstract {"+" [abstract: :abstraction :representation]}]]]]) (type: .public Priority Nat) diff --git a/stdlib/source/library/lux/data/collection/row.lux b/stdlib/source/library/lux/data/collection/row.lux index 6c04e7dd4..1b2b0764d 100644 --- a/stdlib/source/library/lux/data/collection/row.lux +++ b/stdlib/source/library/lux/data/collection/row.lux @@ -3,29 +3,29 @@ ... https://hypirion.com/musings/understanding-persistent-vector-pt-3 (.module: [library - [lux (#- list) + [lux {"-" [list]} ["@" target] [abstract - [functor (#+ Functor)] - [apply (#+ Apply)] - [monad (#+ Monad do)] - [equivalence (#+ Equivalence)] - [monoid (#+ Monoid)] - [mix (#+ Mix)] - [predicate (#+ Predicate)]] + [functor {"+" [Functor]}] + [apply {"+" [Apply]}] + [monad {"+" [Monad do]}] + [equivalence {"+" [Equivalence]}] + [monoid {"+" [Monoid]}] + [mix {"+" [Mix]}] + [predicate {"+" [Predicate]}]] [control ["." maybe] - ["." try (#+ Try)] - ["." exception (#+ exception:)] + ["." try {"+" [Try]}] + ["." exception {"+" [exception:]}] ["<>" parser - ["<.>" code (#+ Parser)]]] + ["<.>" code {"+" [Parser]}]]] [data ["." product] [collection ["." list ("#\." mix functor monoid)] - ["." array (#+ Array) ("#\." functor mix)]]] + ["." array {"+" [Array]} ("#\." functor mix)]]] [macro - [syntax (#+ syntax:)] + [syntax {"+" [syntax:]}] ["." code]] [math [number diff --git a/stdlib/source/library/lux/data/collection/sequence.lux b/stdlib/source/library/lux/data/collection/sequence.lux index 72821bf95..35b9a1102 100644 --- a/stdlib/source/library/lux/data/collection/sequence.lux +++ b/stdlib/source/library/lux/data/collection/sequence.lux @@ -1,15 +1,15 @@ (.module: [library - [lux #* + [lux "*" [abstract - [functor (#+ Functor)] - [comonad (#+ CoMonad)]] + [functor {"+" [Functor]}] + [comonad {"+" [CoMonad]}]] [control - ["//" continuation (#+ Cont)] + ["//" continuation {"+" [Cont]}] ["<>" parser - ["<.>" code (#+ Parser)]]] - [macro (#+ with_identifiers) - [syntax (#+ syntax:)] + ["<.>" code {"+" [Parser]}]]] + [macro {"+" [with_identifiers]} + [syntax {"+" [syntax:]}] ["." code]] [data ["." bit] diff --git a/stdlib/source/library/lux/data/collection/set.lux b/stdlib/source/library/lux/data/collection/set.lux index 62e155534..32fabd6b7 100644 --- a/stdlib/source/library/lux/data/collection/set.lux +++ b/stdlib/source/library/lux/data/collection/set.lux @@ -1,19 +1,19 @@ (.module: [library - [lux (#- list) + [lux {"-" [list]} [abstract - [equivalence (#+ Equivalence)] - [hash (#+ Hash)] - [predicate (#+ Predicate)] - [monoid (#+ Monoid)]] + [equivalence {"+" [Equivalence]}] + [hash {"+" [Hash]}] + [predicate {"+" [Predicate]}] + [monoid {"+" [Monoid]}]] [data [collection ["." list ("#\." mix)]]] [math [number ["n" nat]]]]] - ["." // #_ - ["#" dictionary (#+ Dictionary)]]) + ["." // "_" + ["#" dictionary {"+" [Dictionary]}]]) (type: .public (Set a) (Dictionary a Any)) diff --git a/stdlib/source/library/lux/data/collection/set/multi.lux b/stdlib/source/library/lux/data/collection/set/multi.lux index 62aa7a52f..abc0836c5 100644 --- a/stdlib/source/library/lux/data/collection/set/multi.lux +++ b/stdlib/source/library/lux/data/collection/set/multi.lux @@ -1,10 +1,10 @@ ... https://en.wikipedia.org/wiki/Multiset (.module: [library - [lux (#- list) + [lux {"-" [list]} [abstract - [equivalence (#+ Equivalence)] - [hash (#+ Hash)]] + [equivalence {"+" [Equivalence]}] + [hash {"+" [Hash]}]] [control ["." function] ["." maybe]] @@ -12,11 +12,11 @@ [number ["n" nat]]] [type - [abstract (#+ abstract: :abstraction :representation ^:representation)]]]] + [abstract {"+" [abstract: :abstraction :representation ^:representation]}]]]] ["." // [// ["." list ("#\." mix monoid)] - ["." dictionary (#+ Dictionary)]]]) + ["." dictionary {"+" [Dictionary]}]]]) (abstract: .public (Set a) {} diff --git a/stdlib/source/library/lux/data/collection/set/ordered.lux b/stdlib/source/library/lux/data/collection/set/ordered.lux index ac8c54ac0..dc8a825e6 100644 --- a/stdlib/source/library/lux/data/collection/set/ordered.lux +++ b/stdlib/source/library/lux/data/collection/set/ordered.lux @@ -1,9 +1,9 @@ (.module: [library - [lux (#- list) + [lux {"-" [list]} [abstract - [equivalence (#+ Equivalence)] - [order (#+ Order)]] + [equivalence {"+" [Equivalence]}] + [order {"+" [Order]}]] [data [collection ["." list ("#\." mix)] diff --git a/stdlib/source/library/lux/data/collection/stack.lux b/stdlib/source/library/lux/data/collection/stack.lux index 8bb20bff3..f8ed6aab6 100644 --- a/stdlib/source/library/lux/data/collection/stack.lux +++ b/stdlib/source/library/lux/data/collection/stack.lux @@ -1,9 +1,9 @@ (.module: [library - [lux #* + [lux "*" [abstract - [equivalence (#+ Equivalence)] - [functor (#+ Functor)]] + [equivalence {"+" [Equivalence]}] + [functor {"+" [Functor]}]] [data [collection ["//" list]]] diff --git a/stdlib/source/library/lux/data/collection/tree.lux b/stdlib/source/library/lux/data/collection/tree.lux index 26c385f7e..2216a7b11 100644 --- a/stdlib/source/library/lux/data/collection/tree.lux +++ b/stdlib/source/library/lux/data/collection/tree.lux @@ -1,19 +1,19 @@ (.module: [library - [lux #* + [lux "*" [abstract - [functor (#+ Functor)] - [equivalence (#+ Equivalence)] - [mix (#+ Mix)] - [monad (#+ do)]] + [functor {"+" [Functor]}] + [equivalence {"+" [Equivalence]}] + [mix {"+" [Mix]}] + [monad {"+" [do]}]] [control ["<>" parser - ["<.>" code (#+ Parser)]]] + ["<.>" code {"+" [Parser]}]]] [data [collection ["." list ("#\." monad mix)]]] [macro - [syntax (#+ syntax:)] + [syntax {"+" [syntax:]}] ["." code]]]]) (type: .public (Tree a) diff --git a/stdlib/source/library/lux/data/collection/tree/finger.lux b/stdlib/source/library/lux/data/collection/tree/finger.lux index c675916aa..40a70ac2d 100644 --- a/stdlib/source/library/lux/data/collection/tree/finger.lux +++ b/stdlib/source/library/lux/data/collection/tree/finger.lux @@ -1,14 +1,14 @@ (.module: [library - [lux #* + [lux "*" [abstract - [predicate (#+ Predicate)] - ["." monoid (#+ Monoid)]] + [predicate {"+" [Predicate]}] + ["." monoid {"+" [Monoid]}]] [data [collection ["." list ("#\." monoid)]]] [type - [abstract (#+ abstract: :abstraction :representation)]]]]) + [abstract {"+" [abstract: :abstraction :representation]}]]]]) ... https://en.wikipedia.org/wiki/Finger_tree (abstract: .public (Tree @ t v) diff --git a/stdlib/source/library/lux/data/collection/tree/zipper.lux b/stdlib/source/library/lux/data/collection/tree/zipper.lux index 15265bf94..613e3aeed 100644 --- a/stdlib/source/library/lux/data/collection/tree/zipper.lux +++ b/stdlib/source/library/lux/data/collection/tree/zipper.lux @@ -1,21 +1,21 @@ (.module: [library - [lux #* + [lux "*" ["@" target] [abstract - [functor (#+ Functor)] - [comonad (#+ CoMonad)] - [monad (#+ do)] - [equivalence (#+ Equivalence)]] + [functor {"+" [Functor]}] + [comonad {"+" [CoMonad]}] + [monad {"+" [do]}] + [equivalence {"+" [Equivalence]}]] [control ["." maybe ("#\." monad)]] [data ["." product] [text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." list ("#\." functor monoid)]]]]] - ["." // (#+ Tree) ("#\." functor)]) + ["." // {"+" [Tree]} ("#\." functor)]) (type: (Family Zipper a) (Record diff --git a/stdlib/source/library/lux/data/color.lux b/stdlib/source/library/lux/data/color.lux index 11c31b184..52b4cfac0 100644 --- a/stdlib/source/library/lux/data/color.lux +++ b/stdlib/source/library/lux/data/color.lux @@ -1,10 +1,10 @@ (.module: [library - [lux #* + [lux "*" [abstract - [equivalence (#+ Equivalence)] - [monoid (#+ Monoid)] - ["." hash (#+ Hash)]] + [equivalence {"+" [Equivalence]}] + [monoid {"+" [Monoid]}] + ["." hash {"+" [Hash]}]] [control [parser ["<.>" code]]] diff --git a/stdlib/source/library/lux/data/color/named.lux b/stdlib/source/library/lux/data/color/named.lux index 5d6a92463..b2d26139a 100644 --- a/stdlib/source/library/lux/data/color/named.lux +++ b/stdlib/source/library/lux/data/color/named.lux @@ -1,9 +1,9 @@ (.module: [library - [lux #* + [lux "*" [math - [number (#+ hex)]]]] - ["." // (#+ Color)]) + [number {"+" [hex]}]]]] + ["." // {"+" [Color]}]) (template [<red> <green> <blue> <name>] [(`` (def: .public <name> diff --git a/stdlib/source/library/lux/data/format/binary.lux b/stdlib/source/library/lux/data/format/binary.lux index 8ffed2724..e57bbf11c 100644 --- a/stdlib/source/library/lux/data/format/binary.lux +++ b/stdlib/source/library/lux/data/format/binary.lux @@ -1,27 +1,27 @@ (.module: [library - [lux (#- and or nat int rev list type) + [lux {"-" [and or nat int rev list type]} [abstract - [monoid (#+ Monoid)] - [monad (#+ Monad do)] - [equivalence (#+ Equivalence)]] + [monoid {"+" [Monoid]}] + [monad {"+" [Monad do]}] + [equivalence {"+" [Equivalence]}]] [control - [pipe (#+ case>)] + [pipe {"+" [case>]}] ["." function] - ["." try (#+ Try)] + ["." try {"+" [Try]}] ["<>" parser ("#\." monad) - ["/" binary (#+ Offset Size Parser)]]] + ["/" binary {"+" [Offset Size Parser]}]]] [data ["." product] - ["." binary (#+ Binary)] + ["." binary {"+" [Binary]}] [text - ["%" format (#+ format)] + ["%" format {"+" [format]}] [encoding ["." utf8]]] [collection ["." list] - ["." row (#+ Row) ("#\." functor)] - ["." set (#+ Set)]]] + ["." row {"+" [Row]} ("#\." functor)] + ["." set {"+" [Set]}]]] [math [number ["." i64] diff --git a/stdlib/source/library/lux/data/format/css.lux b/stdlib/source/library/lux/data/format/css.lux index 36c94ef17..7fd5e28d9 100644 --- a/stdlib/source/library/lux/data/format/css.lux +++ b/stdlib/source/library/lux/data/format/css.lux @@ -1,26 +1,26 @@ (.module: [library - [lux (#- and) + [lux {"-" [and]} [control ["." maybe]] [data [number ["." nat]] ["." text - ["%" format (#+ format)] - ["." encoding (#+ Encoding)]] + ["%" format {"+" [format]}] + ["." encoding {"+" [Encoding]}]] [collection ["." list ("#\." functor)]]] [type abstract] [world - [net (#+ URL)]]]] - ["." / #_ - ["#." selector (#+ Selector Combinator)] - ["#." value (#+ Value Animation Percentage)] - ["#." font (#+ Font)] - ["#." style (#+ Style)] - ["#." query (#+ Query)]]) + [net {"+" [URL]}]]]] + ["." / "_" + ["#." selector {"+" [Selector Combinator]}] + ["#." value {"+" [Value Animation Percentage]}] + ["#." font {"+" [Font]}] + ["#." style {"+" [Style]}] + ["#." query {"+" [Query]}]]) (abstract: .public Common {} Any) (abstract: .public Special {} Any) diff --git a/stdlib/source/library/lux/data/format/css/font.lux b/stdlib/source/library/lux/data/format/css/font.lux index 198621e16..21f983a86 100644 --- a/stdlib/source/library/lux/data/format/css/font.lux +++ b/stdlib/source/library/lux/data/format/css/font.lux @@ -1,17 +1,17 @@ (.module: [library - [lux #* + [lux "*" [type abstract] [control [parser ["s" code]]] ["." macro - [syntax (#+ syntax:)]] + [syntax {"+" [syntax:]}]] [world - [net (#+ URL)]]]] - ["." // #_ - ["#." value (#+ Value Font_Stretch Font_Style Font_Weight)]]) + [net {"+" [URL]}]]]] + ["." // "_" + ["#." value {"+" [Value Font_Stretch Font_Style Font_Weight]}]]) (type: .public Unicode_Range (Record diff --git a/stdlib/source/library/lux/data/format/css/property.lux b/stdlib/source/library/lux/data/format/css/property.lux index 0bb70c48d..0f0553b77 100644 --- a/stdlib/source/library/lux/data/format/css/property.lux +++ b/stdlib/source/library/lux/data/format/css/property.lux @@ -1,6 +1,6 @@ (.module: [library - [lux (#- All Cursor) + [lux {"-" [All Cursor]} [control [parser ["s" code]]] @@ -9,48 +9,48 @@ [macro ["." template] ["." code] - [syntax (#+ syntax:)]]]] + [syntax {"+" [syntax:]}]]]] [// - [value (#+ All - Number - Length Thickness Time - Color - Location Fit - Slice - Alignment Animation_Direction - Animation Animation_Fill - Column_Fill Column_Span - Iteration Count - Play - Timing Visibility Attachment - Blend Span Image - Angle Repeat Border - Collapse Box_Decoration_Break Caption - Float Clear - Content - Cursor - Shadow Clip - Text_Direction - Display Empty - Filter - Flex_Direction Flex_Wrap - Font Font_Kerning Font_Size Font_Variant - Grid Grid_Content Grid_Flow Grid_Span Grid_Template - Hanging_Punctuation Hyphens Isolation - List_Style_Position List_Style_Type - Overflow Page_Break Pointer_Events - Position - Quotes - Resize Scroll_Behavior Table_Layout - Text_Align Text_Align_Last - Text_Decoration_Line Text_Decoration_Style - Text_Justification Text_Overflow Text_Transform - Transform Transform_Origin Transform_Style - Transition - Bidi User_Select - Vertical_Align - White_Space Word_Break Word_Wrap Writing_Mode - Z_Index)]]) + [value {"+" [All + Number + Length Thickness Time + Color + Location Fit + Slice + Alignment Animation_Direction + Animation Animation_Fill + Column_Fill Column_Span + Iteration Count + Play + Timing Visibility Attachment + Blend Span Image + Angle Repeat Border + Collapse Box_Decoration_Break Caption + Float Clear + Content + Cursor + Shadow Clip + Text_Direction + Display Empty + Filter + Flex_Direction Flex_Wrap + Font Font_Kerning Font_Size Font_Variant + Grid Grid_Content Grid_Flow Grid_Span Grid_Template + Hanging_Punctuation Hyphens Isolation + List_Style_Position List_Style_Type + Overflow Page_Break Pointer_Events + Position + Quotes + Resize Scroll_Behavior Table_Layout + Text_Align Text_Align_Last + Text_Decoration_Line Text_Decoration_Style + Text_Justification Text_Overflow Text_Transform + Transform Transform_Origin Transform_Style + Transition + Bidi User_Select + Vertical_Align + White_Space Word_Break Word_Wrap Writing_Mode + Z_Index]}]]) (syntax: (text_identifier [identifier s.text]) (in (list (code.local_identifier (text.replaced "-" "_" identifier))))) diff --git a/stdlib/source/library/lux/data/format/css/query.lux b/stdlib/source/library/lux/data/format/css/query.lux index 3743b7033..e48c1716c 100644 --- a/stdlib/source/library/lux/data/format/css/query.lux +++ b/stdlib/source/library/lux/data/format/css/query.lux @@ -1,25 +1,25 @@ (.module: [library - [lux (#- and or not) + [lux {"-" [and or not]} [control [parser ["s" code]]] [data [text - ["%" format (#+ format)]]] + ["%" format {"+" [format]}]]] [macro ["." template] ["." code] - [syntax (#+ syntax:)]] + [syntax {"+" [syntax:]}]] [type abstract]]] - ["." // #_ - ["#." value (#+ Value Length Count Resolution Ratio - Orientation Scan Boolean Update - Block_Overflow Inline_Overflow - Display_Mode Color_Gamut Inverted_Colors - Pointer Hover - Light Scripting Motion Color_Scheme)]]) + ["." // "_" + ["#." value {"+" [Value Length Count Resolution Ratio + Orientation Scan Boolean Update + Block_Overflow Inline_Overflow + Display_Mode Color_Gamut Inverted_Colors + Pointer Hover + Light Scripting Motion Color_Scheme]}]]) (syntax: (text_identifier [identifier s.text]) (in (list (code.local_identifier (text.replaced "-" "_" identifier))))) diff --git a/stdlib/source/library/lux/data/format/css/selector.lux b/stdlib/source/library/lux/data/format/css/selector.lux index f8aab3f86..f73ddcd9c 100644 --- a/stdlib/source/library/lux/data/format/css/selector.lux +++ b/stdlib/source/library/lux/data/format/css/selector.lux @@ -1,16 +1,16 @@ (.module: [library - [lux (#- or and for same? not) + [lux {"-" [or and for same? not]} [data ["." text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [number ["i" int]]] [type abstract] [macro ["." template]] - ["." locale (#+ Locale)]]]) + ["." locale {"+" [Locale]}]]]) (type: .public Label Text) diff --git a/stdlib/source/library/lux/data/format/css/style.lux b/stdlib/source/library/lux/data/format/css/style.lux index 5aae7d013..fa13ff2e1 100644 --- a/stdlib/source/library/lux/data/format/css/style.lux +++ b/stdlib/source/library/lux/data/format/css/style.lux @@ -1,14 +1,14 @@ (.module: [library - [lux #* + [lux "*" [data [text - ["%" format (#+ format)]]] + ["%" format {"+" [format]}]]] [type abstract]]] - ["." // #_ - ["#." value (#+ Value)] - ["#." property (#+ Property)]]) + ["." // "_" + ["#." value {"+" [Value]}] + ["#." property {"+" [Property]}]]) (abstract: .public Style {#.doc "The style associated with a CSS selector."} diff --git a/stdlib/source/library/lux/data/format/css/value.lux b/stdlib/source/library/lux/data/format/css/value.lux index e49398298..037bec265 100644 --- a/stdlib/source/library/lux/data/format/css/value.lux +++ b/stdlib/source/library/lux/data/format/css/value.lux @@ -1,6 +1,6 @@ (.module: [library - [lux (#- All Cursor and static false true) + [lux {"-" [All Cursor and static false true]} [control ["." maybe] [parser @@ -14,7 +14,7 @@ ["r" rev] ["f" frac]] ["." text - ["%" format (#+ Format format)]] + ["%" format {"+" [Format format]}]] [collection ["." list ("#\." functor)]]] [type @@ -22,11 +22,11 @@ [macro ["." template] ["." code] - [syntax (#+ syntax:)]] + [syntax {"+" [syntax:]}]] [world - [net (#+ URL)]]]] + [net {"+" [URL]}]]]] [// - [selector (#+ Label)]]) + [selector {"+" [Label]}]]) (syntax: (text_identifier [identifier s.text]) (in (list (code.local_identifier (text.replaced "-" "_" identifier))))) diff --git a/stdlib/source/library/lux/data/format/html.lux b/stdlib/source/library/lux/data/format/html.lux index b47416398..c58187017 100644 --- a/stdlib/source/library/lux/data/format/html.lux +++ b/stdlib/source/library/lux/data/format/html.lux @@ -1,13 +1,13 @@ (.module: [library - [lux (#- Meta Source comment and) + [lux {"-" [Meta Source comment and]} [control ["." function] ["." maybe ("#\." functor)]] [data ["." product] ["." text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." list ("#\." functor mix)]]] [type @@ -17,12 +17,12 @@ [macro ["." template]] [world - [net (#+ URL)]]]] + [net {"+" [URL]}]]]] [// [css ["." selector] - ["." style (#+ Style)]] - ["." xml (#+ XML)]]) + ["." style {"+" [Style]}]] + ["." xml {"+" [XML]}]]) (type: .public Tag selector.Tag) (type: .public ID selector.ID) diff --git a/stdlib/source/library/lux/data/format/json.lux b/stdlib/source/library/lux/data/format/json.lux index 6aec38ce5..5c27a69af 100644 --- a/stdlib/source/library/lux/data/format/json.lux +++ b/stdlib/source/library/lux/data/format/json.lux @@ -1,18 +1,18 @@ (.module: [library - [lux #* - ["." meta (#+ monad)] + [lux "*" + ["." meta {"+" [monad]}] [abstract - [equivalence (#+ Equivalence)] - [codec (#+ Codec)] - [predicate (#+ Predicate)] - ["." monad (#+ do)]] + [equivalence {"+" [Equivalence]}] + [codec {"+" [Codec]}] + [predicate {"+" [Predicate]}] + ["." monad {"+" [do]}]] [control pipe ["." maybe] - ["." try (#+ Try)] + ["." try {"+" [Try]}] ["<>" parser ("#\." monad) - ["<.>" text (#+ Parser)] + ["<.>" text {"+" [Parser]}] ["<.>" code]]] [data ["." bit] @@ -20,10 +20,10 @@ ["." text ("#\." equivalence monoid)] [collection ["." list ("#\." mix functor)] - ["." row (#+ Row row) ("#\." monad)] - ["." dictionary (#+ Dictionary)]]] + ["." row {"+" [Row row]} ("#\." monad)] + ["." dictionary {"+" [Dictionary]}]]] [macro - [syntax (#+ syntax:)] + [syntax {"+" [syntax:]}] ["." code]] [math [number diff --git a/stdlib/source/library/lux/data/format/markdown.lux b/stdlib/source/library/lux/data/format/markdown.lux index 88746a059..c2dd1778e 100644 --- a/stdlib/source/library/lux/data/format/markdown.lux +++ b/stdlib/source/library/lux/data/format/markdown.lux @@ -1,15 +1,15 @@ (.module: [library - [lux (#- and) + [lux {"-" [and]} [data ["." text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." list ("#\." functor)]]] [type abstract] [world - [net (#+ URL)]]]]) + [net {"+" [URL]}]]]]) ... https://www.markdownguide.org/basic-syntax/ diff --git a/stdlib/source/library/lux/data/format/tar.lux b/stdlib/source/library/lux/data/format/tar.lux index 6450bdf01..e8335ce9d 100644 --- a/stdlib/source/library/lux/data/format/tar.lux +++ b/stdlib/source/library/lux/data/format/tar.lux @@ -1,32 +1,32 @@ (.module: [library - [lux (#- Mode Name and) + [lux {"-" [Mode Name and]} [abstract - [monad (#+ do)]] + [monad {"+" [do]}]] [control - [pipe (#+ case>)] - ["." try (#+ Try)] - ["." exception (#+ exception:)] + [pipe {"+" [case>]}] + ["." try {"+" [Try]}] + ["." exception {"+" [exception:]}] ["<>" parser - ["<.>" binary (#+ Parser)]]] + ["<.>" binary {"+" [Parser]}]]] [data ["." product] - ["." binary (#+ Binary)] - ["." text (#+ Char) - ["%" format (#+ format)] + ["." binary {"+" [Binary]}] + ["." text {"+" [Char]} + ["%" format {"+" [format]}] [encoding ["." utf8]]] - ["." format #_ - ["#" binary (#+ Writer) ("#\." monoid)]] + ["." format "_" + ["#" binary {"+" [Writer]} ("#\." monoid)]] [collection ["." list ("#\." mix)] - ["." row (#+ Row) ("#\." mix)]]] + ["." row {"+" [Row]} ("#\." mix)]]] [math ["." number ["n" nat] ["." i64]]] [time - ["." instant (#+ Instant)] + ["." instant {"+" [Instant]}] ["." duration]] [world ["." file]] diff --git a/stdlib/source/library/lux/data/format/xml.lux b/stdlib/source/library/lux/data/format/xml.lux index ab5981b4f..1cb7ecce4 100644 --- a/stdlib/source/library/lux/data/format/xml.lux +++ b/stdlib/source/library/lux/data/format/xml.lux @@ -1,21 +1,21 @@ (.module: [library - [lux #* + [lux "*" [abstract - [monad (#+ do)] - [equivalence (#+ Equivalence)] - [codec (#+ Codec)]] + [monad {"+" [do]}] + [equivalence {"+" [Equivalence]}] + [codec {"+" [Codec]}]] [control - [try (#+ Try)] + [try {"+" [Try]}] ["<>" parser ("#\." monad) - ["<.>" text (#+ Parser)]]] + ["<.>" text {"+" [Parser]}]]] [data ["." product] ["." name ("#\." equivalence codec)] ["." text ("#\." equivalence monoid)] [collection ["." list ("#\." functor)] - ["." dictionary (#+ Dictionary)]]] + ["." dictionary {"+" [Dictionary]}]]] [math [number ["n" nat] diff --git a/stdlib/source/library/lux/data/identity.lux b/stdlib/source/library/lux/data/identity.lux index ac82be699..68af3d52a 100644 --- a/stdlib/source/library/lux/data/identity.lux +++ b/stdlib/source/library/lux/data/identity.lux @@ -1,11 +1,11 @@ (.module: [library - [lux #* + [lux "*" [abstract - [functor (#+ Functor)] - [apply (#+ Apply)] - [monad (#+ Monad)] - [comonad (#+ CoMonad)]] + [functor {"+" [Functor]}] + [apply {"+" [Apply]}] + [monad {"+" [Monad]}] + [comonad {"+" [CoMonad]}]] [control ["." function]]]]) diff --git a/stdlib/source/library/lux/data/name.lux b/stdlib/source/library/lux/data/name.lux index bb0216ba5..7235c0a5c 100644 --- a/stdlib/source/library/lux/data/name.lux +++ b/stdlib/source/library/lux/data/name.lux @@ -1,11 +1,11 @@ (.module: [library - [lux #* + [lux "*" [abstract - [equivalence (#+ Equivalence)] - [hash (#+ Hash)] - [order (#+ Order)] - [codec (#+ Codec)]] + [equivalence {"+" [Equivalence]}] + [hash {"+" [Hash]}] + [order {"+" [Order]}] + [codec {"+" [Codec]}]] [data ["." text ("#\." equivalence monoid)] ["." product]]]]) diff --git a/stdlib/source/library/lux/data/product.lux b/stdlib/source/library/lux/data/product.lux index 3ad1ba207..df2df9ed1 100644 --- a/stdlib/source/library/lux/data/product.lux +++ b/stdlib/source/library/lux/data/product.lux @@ -1,9 +1,9 @@ (.module: [library - [lux #* + [lux "*" [abstract - [equivalence (#+ Equivalence)] - [hash (#+ Hash)]]]]) + [equivalence {"+" [Equivalence]}] + [hash {"+" [Hash]}]]]]) (template [<name>] [(def: .public (<name> [left right]) diff --git a/stdlib/source/library/lux/data/store.lux b/stdlib/source/library/lux/data/store.lux index de09fe022..005c9d69c 100644 --- a/stdlib/source/library/lux/data/store.lux +++ b/stdlib/source/library/lux/data/store.lux @@ -1,8 +1,8 @@ (.module: [library - [lux #* + [lux "*" [abstract - [functor (#+ Functor)] + [functor {"+" [Functor]}] comonad] [type implicit]]]) diff --git a/stdlib/source/library/lux/data/sum.lux b/stdlib/source/library/lux/data/sum.lux index 7c8696012..85d27f12b 100644 --- a/stdlib/source/library/lux/data/sum.lux +++ b/stdlib/source/library/lux/data/sum.lux @@ -1,9 +1,9 @@ (.module: [library - [lux #* + [lux "*" [abstract - [equivalence (#+ Equivalence)] - [hash (#+ Hash)]]]]) + [equivalence {"+" [Equivalence]}] + [hash {"+" [Hash]}]]]]) (template [<right?> <name>] [(def: .public (<name> value) diff --git a/stdlib/source/library/lux/data/text.lux b/stdlib/source/library/lux/data/text.lux index 31e42bfa5..e553d69b1 100644 --- a/stdlib/source/library/lux/data/text.lux +++ b/stdlib/source/library/lux/data/text.lux @@ -1,14 +1,14 @@ (.module: [library - [lux (#- char) + [lux {"-" [char]} ["@" target] [abstract - [hash (#+ Hash)] - [monoid (#+ Monoid)] - [equivalence (#+ Equivalence)] - [order (#+ Order)] - [monad (#+ do)] - [codec (#+ Codec)]] + [hash {"+" [Hash]}] + [monoid {"+" [Monoid]}] + [equivalence {"+" [Equivalence]}] + [order {"+" [Order]}] + [monad {"+" [do]}] + [codec {"+" [Codec]}]] [control ["." maybe]] [data diff --git a/stdlib/source/library/lux/data/text/buffer.lux b/stdlib/source/library/lux/data/text/buffer.lux index ddbf123c6..a9c3c7a41 100644 --- a/stdlib/source/library/lux/data/text/buffer.lux +++ b/stdlib/source/library/lux/data/text/buffer.lux @@ -1,17 +1,17 @@ (.module: [library - [lux #* + [lux "*" ["@" target] - ["." ffi (#+ import:)] + ["." ffi {"+" [import:]}] [control ["." function]] [data ["." product] [text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." array] - ["." row (#+ Row) ("#\." mix)]]] + ["." row {"+" [Row]} ("#\." mix)]]] [math [number ["n" nat]]] diff --git a/stdlib/source/library/lux/data/text/encoding.lux b/stdlib/source/library/lux/data/text/encoding.lux index b1947bf67..3e139fde1 100644 --- a/stdlib/source/library/lux/data/text/encoding.lux +++ b/stdlib/source/library/lux/data/text/encoding.lux @@ -1,6 +1,6 @@ (.module: [library - [lux #* + [lux "*" [macro ["." template]] [type diff --git a/stdlib/source/library/lux/data/text/encoding/utf8.lux b/stdlib/source/library/lux/data/text/encoding/utf8.lux index b8c821afd..f95ce62c3 100644 --- a/stdlib/source/library/lux/data/text/encoding/utf8.lux +++ b/stdlib/source/library/lux/data/text/encoding/utf8.lux @@ -1,14 +1,14 @@ (.module: [library - [lux #* + [lux "*" ["@" target] ["." ffi] [abstract - [codec (#+ Codec)]] + [codec {"+" [Codec]}]] [control - ["." try (#+ Try)]] + ["." try {"+" [Try]}]] [data - ["." binary (#+ Binary)]]]] + ["." binary {"+" [Binary]}]]]] ["." //]) (with_expansions [<jvm> (as_is (ffi.import: java/lang/String diff --git a/stdlib/source/library/lux/data/text/escape.lux b/stdlib/source/library/lux/data/text/escape.lux index 4d99b6c8c..2dcbbbece 100644 --- a/stdlib/source/library/lux/data/text/escape.lux +++ b/stdlib/source/library/lux/data/text/escape.lux @@ -1,23 +1,23 @@ (.module: [library - [lux #* + [lux "*" ["." meta] [abstract - [monad (#+ do)]] + [monad {"+" [do]}]] [control ["." maybe] - ["." try (#+ Try)] - ["." exception (#+ exception:)] + ["." try {"+" [Try]}] + ["." exception {"+" [exception:]}] ["<>" parser ["<.>" code]]] [math - [number (#+ hex) + [number {"+" [hex]} ["n" nat]]] [macro - [syntax (#+ syntax:)] + [syntax {"+" [syntax:]}] ["." code]]]] - ["." // (#+ Char) - ["%" format (#+ format)]]) + ["." // {"+" [Char]} + ["%" format {"+" [format]}]]) (def: sigil "\") diff --git a/stdlib/source/library/lux/data/text/format.lux b/stdlib/source/library/lux/data/text/format.lux index a41022153..d79aed559 100644 --- a/stdlib/source/library/lux/data/text/format.lux +++ b/stdlib/source/library/lux/data/text/format.lux @@ -1,13 +1,13 @@ (.module: [library - [lux (#- list nat int rev type) + [lux {"-" [list nat int rev type]} [abstract - [monad (#+ do)] + [monad {"+" [do]}] [functor ["." contravariant]]] [control ["<>" parser - ["<.>" code (#+ Parser)]]] + ["<.>" code {"+" [Parser]}]]] [data ["." bit] ["." name] @@ -32,7 +32,7 @@ ["." frac] ["." ratio]]] [macro - [syntax (#+ syntax:)] + [syntax {"+" [syntax:]}] ["." code] ["." template]] [meta diff --git a/stdlib/source/library/lux/data/text/regex.lux b/stdlib/source/library/lux/data/text/regex.lux index bdab7c6a1..4b4339ebc 100644 --- a/stdlib/source/library/lux/data/text/regex.lux +++ b/stdlib/source/library/lux/data/text/regex.lux @@ -1,28 +1,28 @@ (.module: [library - [lux #* + [lux "*" ["." meta] [abstract monad] [control ["." maybe] ["." try] - ["." exception (#+ exception:)] + ["." exception {"+" [exception:]}] ["<>" parser ("#\." monad) - ["<.>" text (#+ Parser)] + ["<.>" text {"+" [Parser]}] ["<.>" code]]] [data ["." product] [collection ["." list ("#\." mix monad)]]] - [macro (#+ with_identifiers) - [syntax (#+ syntax:)] + [macro {"+" [with_identifiers]} + [syntax {"+" [syntax:]}] ["." code]] [math - [number (#+ hex) + [number {"+" [hex]} ["n" nat ("#\." decimal)]]]]] ["." // - ["%" format (#+ format)]]) + ["%" format {"+" [format]}]]) (def: regex_char^ (Parser Text) diff --git a/stdlib/source/library/lux/data/text/unicode/block.lux b/stdlib/source/library/lux/data/text/unicode/block.lux index a4f4d9eb2..f001fe99b 100644 --- a/stdlib/source/library/lux/data/text/unicode/block.lux +++ b/stdlib/source/library/lux/data/text/unicode/block.lux @@ -1,18 +1,18 @@ (.module: [library - [lux #* + [lux "*" [abstract - [equivalence (#+ Equivalence)] - [hash (#+ Hash)] - [monoid (#+ Monoid)] - ["." interval (#+ Interval)]] + [equivalence {"+" [Equivalence]}] + [hash {"+" [Hash]}] + [monoid {"+" [Monoid]}] + ["." interval {"+" [Interval]}]] [math - [number (#+ hex) + [number {"+" [hex]} ["n" nat ("#\." interval)] ["." i64]]] [type abstract]]] - [/// (#+ Char)]) + [/// {"+" [Char]}]) (abstract: .public Block {} diff --git a/stdlib/source/library/lux/data/text/unicode/set.lux b/stdlib/source/library/lux/data/text/unicode/set.lux index ef489af08..fe2f5d6fe 100644 --- a/stdlib/source/library/lux/data/text/unicode/set.lux +++ b/stdlib/source/library/lux/data/text/unicode/set.lux @@ -1,20 +1,20 @@ (.module: [library - [lux #* + [lux "*" [abstract - [equivalence (#+ Equivalence)]] + [equivalence {"+" [Equivalence]}]] [data [collection ["." list ("#\." mix functor)] ["." set ("#\." equivalence)] - ["." tree #_ - ["#" finger (#+ Tree)]]]] - [type (#+ :by_example) + ["." tree "_" + ["#" finger {"+" [Tree]}]]]] + [type {"+" [:by_example]} abstract]]] - ["." / #_ - ["/#" // #_ - [// (#+ Char)] - ["#." block (#+ Block)]]]) + ["." / "_" + ["/#" // "_" + [// {"+" [Char]}] + ["#." block {"+" [Block]}]]]) (def: builder (tree.builder //block.monoid)) diff --git a/stdlib/source/library/lux/data/trace.lux b/stdlib/source/library/lux/data/trace.lux index b0819574c..9d5698bbc 100644 --- a/stdlib/source/library/lux/data/trace.lux +++ b/stdlib/source/library/lux/data/trace.lux @@ -1,9 +1,9 @@ (.module: [library - [lux #* + [lux "*" [abstract - ["." monoid (#+ Monoid)] - [functor (#+ Functor)] + ["." monoid {"+" [Monoid]}] + [functor {"+" [Functor]}] comonad] function]]) diff --git a/stdlib/source/library/lux/debug.lux b/stdlib/source/library/lux/debug.lux index 531bb7cd8..5ed2bbaaa 100644 --- a/stdlib/source/library/lux/debug.lux +++ b/stdlib/source/library/lux/debug.lux @@ -1,25 +1,25 @@ (.module: [library - [lux (#- type private) + [lux {"-" [type private]} ["@" target] ["." type] - ["." ffi (#+ import:)] + ["." ffi {"+" [import:]}] ["." meta] [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control - [pipe (#+ new>)] + [pipe {"+" [new>]}] ["." function] - ["." try (#+ Try)] - ["." exception (#+ exception:)] + ["." try {"+" [Try]}] + ["." exception {"+" [exception:]}] ["<>" parser - ["<.>" type (#+ Parser)] + ["<.>" type {"+" [Parser]}] ["<.>" code]]] [data ["." text - ["%" format (#+ Format)]] + ["%" format {"+" [Format]}]] [format - [xml (#+ XML)] + [xml {"+" [XML]}] ["." json]] [collection ["." array] @@ -27,19 +27,19 @@ ["." dictionary]]] [macro ["." template] - ["." syntax (#+ syntax:)] + ["." syntax {"+" [syntax:]}] ["." code]] [math [number - [ratio (#+ Ratio)] + [ratio {"+" [Ratio]}] ["n" nat] ["i" int]]] - [time (#+ Time) - [instant (#+ Instant)] - [duration (#+ Duration)] - [date (#+ Date)] - [month (#+ Month)] - [day (#+ Day)]]]]) + [time {"+" [Time]} + [instant {"+" [Instant]}] + [duration {"+" [Duration]}] + [date {"+" [Date]}] + [month {"+" [Month]}] + [day {"+" [Day]}]]]]) (with_expansions [<jvm> (as_is (import: java/lang/String) diff --git a/stdlib/source/library/lux/documentation.lux b/stdlib/source/library/lux/documentation.lux index d11d897d0..59c4b4a32 100644 --- a/stdlib/source/library/lux/documentation.lux +++ b/stdlib/source/library/lux/documentation.lux @@ -1,28 +1,28 @@ (.module: [library - [lux (#- Definition Module type) + [lux {"-" [Definition Module type]} ["." meta] ["." type ("#\." equivalence)] [abstract - [monad (#+ do)] + [monad {"+" [do]}] ["." enum]] [control ["." maybe ("#\." functor)] - ["." exception (#+ exception:)] + ["." exception {"+" [exception:]}] ["<>" parser ("#\." monad) - ["<.>" code (#+ Parser)]]] + ["<.>" code {"+" [Parser]}]]] [data ["." product] - ["." text (#+ \n) ("#\." order) - ["%" format (#+ format)]] + ["." text {"+" [\n]} ("#\." order) + ["%" format {"+" [format]}]] [collection ["." list ("#\." monad mix monoid)] - ["." set (#+ Set)] - ["." sequence (#+ Sequence)]] + ["." set {"+" [Set]}] + ["." sequence {"+" [Sequence]}]] [format - ["md" markdown (#+ Markdown Block)]]] + ["md" markdown {"+" [Markdown Block]}]]] ["." macro - [syntax (#+ syntax:)] + [syntax {"+" [syntax:]}] ["." code] ["." template]] [math diff --git a/stdlib/source/library/lux/extension.lux b/stdlib/source/library/lux/extension.lux index a2334c5f7..e72731be4 100644 --- a/stdlib/source/library/lux/extension.lux +++ b/stdlib/source/library/lux/extension.lux @@ -1,20 +1,20 @@ (.module: [library - [lux #* + [lux "*" [abstract ["." monad]] [control ["<>" parser ("#\." monad) - ["<c>" code (#+ Parser)] + ["<c>" code {"+" [Parser]}] ["<a>" analysis] ["<s>" synthesis]]] [data ["." product] [collection ["." list ("#\." functor)]]] - [macro (#+ with_identifiers) + [macro {"+" [with_identifiers]} ["." code] - [syntax (#+ syntax:)]] + [syntax {"+" [syntax:]}]] [tool [compiler ["." phase]]]]]) diff --git a/stdlib/source/library/lux/ffi.js.lux b/stdlib/source/library/lux/ffi.js.lux index 1d25fab7d..c93a0ab0d 100644 --- a/stdlib/source/library/lux/ffi.js.lux +++ b/stdlib/source/library/lux/ffi.js.lux @@ -1,14 +1,14 @@ (.module: [library - [lux #* + [lux "*" ["." meta] [abstract - [monad (#+ do)]] + [monad {"+" [do]}]] [control ["." io] ["." maybe] ["<>" parser ("#\." monad) - ["<.>" code (#+ Parser)]]] + ["<.>" code {"+" [Parser]}]]] [data ["." product] ["." text @@ -17,8 +17,8 @@ ["." list ("#\." functor)]]] [type abstract] - [macro (#+ with_identifiers) - [syntax (#+ syntax:)] + [macro {"+" [with_identifiers]} + [syntax {"+" [syntax:]}] ["." code] ["." template]]]]) diff --git a/stdlib/source/library/lux/ffi.jvm.lux b/stdlib/source/library/lux/ffi.jvm.lux index eac74c9f7..df421ffc3 100644 --- a/stdlib/source/library/lux/ffi.jvm.lux +++ b/stdlib/source/library/lux/ffi.jvm.lux @@ -1,28 +1,28 @@ (.module: [library - ["." lux (#- Type type int char :as) + ["." lux {"-" [Type type int char :as]} ["#_." type ("#\." equivalence)] [abstract - ["." monad (#+ Monad do)] + ["." monad {"+" [Monad do]}] ["." enum]] [control ["." function] ["." io] ["." maybe] - ["." try (#+ Try)] - ["." exception (#+ Exception exception:)] + ["." try {"+" [Try]}] + ["." exception {"+" [Exception exception:]}] ["<>" parser ("#\." monad) - ["<.>" code (#+ Parser)]]] + ["<.>" code {"+" [Parser]}]]] [data ["." product] ["." text ("#\." equivalence) - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." array] ["." list ("#\." monad mix monoid)] - ["." dictionary (#+ Dictionary)]]] - [macro (#+ with_identifiers) - [syntax (#+ syntax:)] + ["." dictionary {"+" [Dictionary]}]]] + [macro {"+" [with_identifiers]} + [syntax {"+" [syntax:]}] ["." code] ["." template]] ["." meta @@ -30,9 +30,9 @@ [target [jvm [encoding - ["." name (#+ External)]] - ["." type (#+ Type Argument Typed) - ["." category (#+ Void Value' Value Return' Return Method Primitive Object Class Array Var Parameter Declaration)] + ["." name {"+" [External]}]] + ["." type {"+" [Type Argument Typed]} + ["." category {"+" [Void Value' Value Return' Return Method Primitive Object Class Array Var Parameter Declaration]}] ["." box] ["." descriptor] ["." signature] diff --git a/stdlib/source/library/lux/ffi.lua.lux b/stdlib/source/library/lux/ffi.lua.lux index 60e8a8d48..8a8abbe14 100644 --- a/stdlib/source/library/lux/ffi.lua.lux +++ b/stdlib/source/library/lux/ffi.lua.lux @@ -1,15 +1,15 @@ (.module: [library - [lux #* + [lux "*" ["@" target] ["." meta] [abstract - [monad (#+ do)]] + [monad {"+" [do]}]] [control ["." io] ["." maybe] ["<>" parser ("#\." monad) - ["<.>" code (#+ Parser)]]] + ["<.>" code {"+" [Parser]}]]] [data ["." product] ["." text @@ -18,8 +18,8 @@ ["." list ("#\." functor mix)]]] [type abstract] - [macro (#+ with_identifiers) - [syntax (#+ syntax:)] + [macro {"+" [with_identifiers]} + [syntax {"+" [syntax:]}] ["." code] ["." template]]]]) diff --git a/stdlib/source/library/lux/ffi.old.lux b/stdlib/source/library/lux/ffi.old.lux index 2512530d4..6bab5e94f 100644 --- a/stdlib/source/library/lux/ffi.old.lux +++ b/stdlib/source/library/lux/ffi.old.lux @@ -1,27 +1,27 @@ (.module: [library - [lux (#- type) + [lux {"-" [type]} ["." type ("#\." equivalence)] [abstract - ["." monad (#+ Monad do)] + ["." monad {"+" [Monad do]}] ["." enum]] [control ["." function] ["." io] ["." maybe] - ["." try (#+ Try)] + ["." try {"+" [Try]}] ["<>" parser - ["<.>" code (#+ Parser)]]] + ["<.>" code {"+" [Parser]}]]] [data ["." product] ["." bit ("#\." codec)] ["." text ("#\." equivalence monoid) - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection - ["." array (#+ Array)] + ["." array {"+" [Array]}] ["." list ("#\." monad mix monoid)]]] - ["." macro (#+ with_identifiers) - [syntax (#+ syntax:)] + ["." macro {"+" [with_identifiers]} + [syntax {"+" [syntax:]}] ["." code] ["." template]] ["." meta diff --git a/stdlib/source/library/lux/ffi.php.lux b/stdlib/source/library/lux/ffi.php.lux index 2cc3fb56f..668ff816d 100644 --- a/stdlib/source/library/lux/ffi.php.lux +++ b/stdlib/source/library/lux/ffi.php.lux @@ -1,15 +1,15 @@ (.module: [library - [lux (#- Alias) + [lux {"-" [Alias]} ["." meta] ["@" target] [abstract - [monad (#+ do)]] + [monad {"+" [do]}]] [control ["." io] ["." maybe] ["<>" parser ("#\." monad) - ["<.>" code (#+ Parser)]]] + ["<.>" code {"+" [Parser]}]]] [data ["." product] ["." text @@ -18,8 +18,8 @@ ["." list ("#\." functor)]]] [type abstract] - [macro (#+ with_identifiers) - [syntax (#+ syntax:)] + [macro {"+" [with_identifiers]} + [syntax {"+" [syntax:]}] ["." code] ["." template]]]]) diff --git a/stdlib/source/library/lux/ffi.py.lux b/stdlib/source/library/lux/ffi.py.lux index 3c47972ed..9a4a20ff3 100644 --- a/stdlib/source/library/lux/ffi.py.lux +++ b/stdlib/source/library/lux/ffi.py.lux @@ -1,15 +1,15 @@ (.module: [library - [lux #* + [lux "*" ["." meta] ["@" target] [abstract - [monad (#+ do)]] + [monad {"+" [do]}]] [control ["." io] ["." maybe] ["<>" parser - ["<.>" code (#+ Parser)]]] + ["<.>" code {"+" [Parser]}]]] [data ["." product] ["." text @@ -18,8 +18,8 @@ ["." list ("#\." functor mix)]]] [type abstract] - [macro (#+ with_identifiers) - [syntax (#+ syntax:)] + [macro {"+" [with_identifiers]} + [syntax {"+" [syntax:]}] ["." code] ["." template]]]]) diff --git a/stdlib/source/library/lux/ffi.rb.lux b/stdlib/source/library/lux/ffi.rb.lux index 485fd904c..4781ec987 100644 --- a/stdlib/source/library/lux/ffi.rb.lux +++ b/stdlib/source/library/lux/ffi.rb.lux @@ -1,15 +1,15 @@ (.module: [library - [lux (#- Alias) + [lux {"-" [Alias]} ["@" target] ["." meta] [abstract - [monad (#+ do)]] + [monad {"+" [do]}]] [control ["." io] ["." maybe] ["<>" parser ("#\." monad) - ["<.>" code (#+ Parser)]]] + ["<.>" code {"+" [Parser]}]]] [data ["." product] ["." text @@ -18,8 +18,8 @@ ["." list ("#\." functor)]]] [type abstract] - [macro (#+ with_identifiers) - [syntax (#+ syntax:)] + [macro {"+" [with_identifiers]} + [syntax {"+" [syntax:]}] ["." code] ["." template]]]]) diff --git a/stdlib/source/library/lux/ffi.scm.lux b/stdlib/source/library/lux/ffi.scm.lux index 01717e47b..6e861cb86 100644 --- a/stdlib/source/library/lux/ffi.scm.lux +++ b/stdlib/source/library/lux/ffi.scm.lux @@ -1,25 +1,25 @@ (.module: [library - [lux (#- Alias) + [lux {"-" [Alias]} ["@" target] ["." meta] [abstract - [monad (#+ do)]] + [monad {"+" [do]}]] [control ["." io] ["." maybe] ["<>" parser ("#\." monad) - ["<.>" code (#+ Parser)]]] + ["<.>" code {"+" [Parser]}]]] [data ["." product] ["." text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." list ("#\." functor)]]] [type abstract] - [macro (#+ with_identifiers) - [syntax (#+ syntax:)] + [macro {"+" [with_identifiers]} + [syntax {"+" [syntax:]}] ["." code] ["." template]]]]) diff --git a/stdlib/source/library/lux/locale.lux b/stdlib/source/library/lux/locale.lux index ac8c05384..53b363c45 100644 --- a/stdlib/source/library/lux/locale.lux +++ b/stdlib/source/library/lux/locale.lux @@ -1,20 +1,20 @@ (.module: [library - [lux #* + [lux "*" [abstract - [equivalence (#+ Equivalence)] - ["." hash (#+ Hash)]] + [equivalence {"+" [Equivalence]}] + ["." hash {"+" [Hash]}]] [control ["." maybe ("#\." functor)]] [data ["." text - ["%" format (#+ format)] - ["." encoding (#+ Encoding)]]] + ["%" format {"+" [format]}] + ["." encoding {"+" [Encoding]}]]] [type abstract]]] [/ - ["." language (#+ Language)] - ["." territory (#+ Territory)]]) + ["." language {"+" [Language]}] + ["." territory {"+" [Territory]}]]) (abstract: .public Locale {} diff --git a/stdlib/source/library/lux/locale/language.lux b/stdlib/source/library/lux/locale/language.lux index 117fc5a73..38da0fd18 100644 --- a/stdlib/source/library/lux/locale/language.lux +++ b/stdlib/source/library/lux/locale/language.lux @@ -1,9 +1,9 @@ (.module: [library - [lux #* + [lux "*" [abstract - [equivalence (#+ Equivalence)] - [hash (#+ Hash)]] + [equivalence {"+" [Equivalence]}] + [hash {"+" [Hash]}]] [data ["." text]] [type diff --git a/stdlib/source/library/lux/locale/territory.lux b/stdlib/source/library/lux/locale/territory.lux index ae762a0fa..9a30ff70d 100644 --- a/stdlib/source/library/lux/locale/territory.lux +++ b/stdlib/source/library/lux/locale/territory.lux @@ -1,9 +1,9 @@ (.module: [library - [lux #* + [lux "*" [abstract - [equivalence (#+ Equivalence)] - [hash (#+ Hash)]] + [equivalence {"+" [Equivalence]}] + [hash {"+" [Hash]}]] [data ["." text]] [type diff --git a/stdlib/source/library/lux/macro.lux b/stdlib/source/library/lux/macro.lux index a5be7a729..98f7da1a7 100644 --- a/stdlib/source/library/lux/macro.lux +++ b/stdlib/source/library/lux/macro.lux @@ -1,8 +1,8 @@ (.module: [library - [lux #* + [lux "*" [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [data ["." text ("#\." monoid)] ["." name ("#\." codec)] @@ -14,7 +14,7 @@ [number ["." nat] ["." int]]]]] - ["." // #_ + ["." // "_" ["#" meta ["." location]]]) diff --git a/stdlib/source/library/lux/macro/code.lux b/stdlib/source/library/lux/macro/code.lux index b27e28c8c..fb4b6498e 100644 --- a/stdlib/source/library/lux/macro/code.lux +++ b/stdlib/source/library/lux/macro/code.lux @@ -1,8 +1,8 @@ (.module: [library - [lux (#- nat int rev) + [lux {"-" [nat int rev]} [abstract - [equivalence (#+ Equivalence)]] + [equivalence {"+" [Equivalence]}]] [data ["." product] ["." bit] diff --git a/stdlib/source/library/lux/macro/local.lux b/stdlib/source/library/lux/macro/local.lux index edf8ca784..381dfc360 100644 --- a/stdlib/source/library/lux/macro/local.lux +++ b/stdlib/source/library/lux/macro/local.lux @@ -1,19 +1,19 @@ (.module: [library - [lux #* + [lux "*" ["." meta] [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control - ["." try (#+ Try)] - ["." exception (#+ exception:)]] + ["." try {"+" [Try]}] + ["." exception {"+" [exception:]}]] [data ["." product] ["." text] [collection ["." list ("#\." functor)] [dictionary - ["." plist (#+ PList)]]]]]] + ["." plist {"+" [PList]}]]]]]] ["." // ["#." code]]) diff --git a/stdlib/source/library/lux/macro/syntax.lux b/stdlib/source/library/lux/macro/syntax.lux index 106048f90..29ab5f49e 100644 --- a/stdlib/source/library/lux/macro/syntax.lux +++ b/stdlib/source/library/lux/macro/syntax.lux @@ -1,15 +1,15 @@ (.module: [library - [lux #* - ["." macro (#+ with_identifiers)] + [lux "*" + ["." macro {"+" [with_identifiers]}] ["." meta] [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control ["." maybe] ["." try] ["<>" parser - ["</>" code (#+ Parser)]]] + ["</>" code {"+" [Parser]}]]] [data ["." text ("#\." monoid)] [collection diff --git a/stdlib/source/library/lux/macro/syntax/annotations.lux b/stdlib/source/library/lux/macro/syntax/annotations.lux index acfaabd37..89a45ddf6 100644 --- a/stdlib/source/library/lux/macro/syntax/annotations.lux +++ b/stdlib/source/library/lux/macro/syntax/annotations.lux @@ -1,12 +1,12 @@ (.module: [library - [lux #* + [lux "*" [abstract - [equivalence (#+ Equivalence)]] + [equivalence {"+" [Equivalence]}]] [control ["." function] ["<>" parser - ["<.>" code (#+ Parser)]]] + ["<.>" code {"+" [Parser]}]]] [data ["." product] ["." name] diff --git a/stdlib/source/library/lux/macro/syntax/check.lux b/stdlib/source/library/lux/macro/syntax/check.lux index d6eb8215e..750ac56d2 100644 --- a/stdlib/source/library/lux/macro/syntax/check.lux +++ b/stdlib/source/library/lux/macro/syntax/check.lux @@ -1,14 +1,14 @@ (.module: [library - [lux #* + [lux "*" ["." meta] [abstract - [equivalence (#+ Equivalence)] - [monad (#+ do)]] + [equivalence {"+" [Equivalence]}] + [monad {"+" [do]}]] [control - ["." exception (#+ exception:)] + ["." exception {"+" [exception:]}] ["<>" parser - ["<.>" code (#+ Parser)]]] + ["<.>" code {"+" [Parser]}]]] [data ["." product]] [macro diff --git a/stdlib/source/library/lux/macro/syntax/declaration.lux b/stdlib/source/library/lux/macro/syntax/declaration.lux index 8713b35fc..b2d81ff4d 100644 --- a/stdlib/source/library/lux/macro/syntax/declaration.lux +++ b/stdlib/source/library/lux/macro/syntax/declaration.lux @@ -1,11 +1,11 @@ (.module: [library - [lux #* + [lux "*" [abstract - [equivalence (#+ Equivalence)]] + [equivalence {"+" [Equivalence]}]] [control ["<>" parser ("#\." monad) - ["<.>" code (#+ Parser)]]] + ["<.>" code {"+" [Parser]}]]] [data ["." product] ["." text] diff --git a/stdlib/source/library/lux/macro/syntax/definition.lux b/stdlib/source/library/lux/macro/syntax/definition.lux index 7b87eeba7..c342fd1fc 100644 --- a/stdlib/source/library/lux/macro/syntax/definition.lux +++ b/stdlib/source/library/lux/macro/syntax/definition.lux @@ -1,13 +1,13 @@ (.module: [library - [lux (#- Definition) + [lux {"-" [Definition]} [abstract - [equivalence (#+ Equivalence)] - [monad (#+ do)]] + [equivalence {"+" [Equivalence]}] + [monad {"+" [do]}]] [control - ["." exception (#+ exception:)] + ["." exception {"+" [exception:]}] ["<>" parser - ["<.>" code (#+ Parser)]]] + ["<.>" code {"+" [Parser]}]]] [data ["." sum] ["." product] @@ -22,8 +22,8 @@ ["." meta ["." location]]]] ["." // - ["#." annotations (#+ Annotations)] - ["#." check (#+ Check)]]) + ["#." annotations {"+" [Annotations]}] + ["#." check {"+" [Check]}]]) (type: .public Definition (Record diff --git a/stdlib/source/library/lux/macro/syntax/export.lux b/stdlib/source/library/lux/macro/syntax/export.lux index 445e8ae23..2ea86c378 100644 --- a/stdlib/source/library/lux/macro/syntax/export.lux +++ b/stdlib/source/library/lux/macro/syntax/export.lux @@ -1,9 +1,9 @@ (.module: [library - [lux #* + [lux "*" [control ["<>" parser ("#\." monad) - ["<.>" code (#+ Parser)]]]]]) + ["<.>" code {"+" [Parser]}]]]]]) (def: .public default_policy Code diff --git a/stdlib/source/library/lux/macro/syntax/input.lux b/stdlib/source/library/lux/macro/syntax/input.lux index c0f7066c6..81cd983d1 100644 --- a/stdlib/source/library/lux/macro/syntax/input.lux +++ b/stdlib/source/library/lux/macro/syntax/input.lux @@ -1,11 +1,11 @@ (.module: [library - [lux #* + [lux "*" [abstract - [equivalence (#+ Equivalence)]] + [equivalence {"+" [Equivalence]}]] [control ["<>" parser - ["<.>" code (#+ Parser)]]] + ["<.>" code {"+" [Parser]}]]] [data ["." product]] [macro diff --git a/stdlib/source/library/lux/macro/syntax/type/variable.lux b/stdlib/source/library/lux/macro/syntax/type/variable.lux index 7e66ca622..b079e3485 100644 --- a/stdlib/source/library/lux/macro/syntax/type/variable.lux +++ b/stdlib/source/library/lux/macro/syntax/type/variable.lux @@ -1,11 +1,11 @@ (.module: [library - [lux #* + [lux "*" [abstract - [equivalence (#+ Equivalence)]] + [equivalence {"+" [Equivalence]}]] [control [parser - ["<.>" code (#+ Parser)]]] + ["<.>" code {"+" [Parser]}]]] [data ["." text]] [macro diff --git a/stdlib/source/library/lux/macro/template.lux b/stdlib/source/library/lux/macro/template.lux index 256302d3c..d731c2810 100644 --- a/stdlib/source/library/lux/macro/template.lux +++ b/stdlib/source/library/lux/macro/template.lux @@ -1,20 +1,20 @@ (.module: [library - [lux (#- let local macro) + [lux {"-" [let local macro]} ["." meta] [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control - ["." try (#+ Try)] - ["." exception (#+ exception:)] + ["." try {"+" [Try]}] + ["." exception {"+" [exception:]}] ["<>" parser ("#\." functor) - ["<.>" code (#+ Parser)]]] + ["<.>" code {"+" [Parser]}]]] [data ["." bit ("#\." codec)] ["." text] [collection ["." list ("#\." monad)] - ["." dictionary (#+ Dictionary)]]] + ["." dictionary {"+" [Dictionary]}]]] [math [number ["." nat ("#\." decimal)] @@ -22,7 +22,7 @@ ["." rev ("#\." decimal)] ["." frac ("#\." decimal)]]]]] ["." // - [syntax (#+ syntax:)] + [syntax {"+" [syntax:]}] ["." code] ["." local]]) diff --git a/stdlib/source/library/lux/math.lux b/stdlib/source/library/lux/math.lux index c5fc005c6..b81ca5c50 100644 --- a/stdlib/source/library/lux/math.lux +++ b/stdlib/source/library/lux/math.lux @@ -1,6 +1,6 @@ (.module: [library - [lux #* + [lux "*" ["@" target] [math [number diff --git a/stdlib/source/library/lux/math/infix.lux b/stdlib/source/library/lux/math/infix.lux index fca3ed8ec..8e10d4ae0 100644 --- a/stdlib/source/library/lux/math/infix.lux +++ b/stdlib/source/library/lux/math/infix.lux @@ -1,17 +1,17 @@ (.module: [library - [lux #* + [lux "*" [abstract - [monad (#+ do)]] + [monad {"+" [do]}]] [control ["<>" parser ("#\." functor) - ["<.>" code (#+ Parser)]]] + ["<.>" code {"+" [Parser]}]]] [data ["." product] [collection ["." list ("#\." mix)]]] [macro - [syntax (#+ syntax:)] + [syntax {"+" [syntax:]}] ["." code]] [math [number diff --git a/stdlib/source/library/lux/math/logic/continuous.lux b/stdlib/source/library/lux/math/logic/continuous.lux index 57f3572b5..807cdba9c 100644 --- a/stdlib/source/library/lux/math/logic/continuous.lux +++ b/stdlib/source/library/lux/math/logic/continuous.lux @@ -1,9 +1,9 @@ ... https://en.wikipedia.org/wiki/Many-valued_logic (.module: [library - [lux (#- false true or and not) + [lux {"-" [false true or and not]} [abstract - [monoid (#+ Monoid)]] + [monoid {"+" [Monoid]}]] [math [number ["/" rev ("#\." interval)]]]]]) diff --git a/stdlib/source/library/lux/math/logic/fuzzy.lux b/stdlib/source/library/lux/math/logic/fuzzy.lux index 36277f723..a30c42d8c 100644 --- a/stdlib/source/library/lux/math/logic/fuzzy.lux +++ b/stdlib/source/library/lux/math/logic/fuzzy.lux @@ -1,19 +1,19 @@ ... https://en.wikipedia.org/wiki/Fuzzy_logic (.module: [library - [lux #* + [lux "*" [abstract - [predicate (#+ Predicate)] + [predicate {"+" [Predicate]}] [functor ["." contravariant]]] [data [collection ["." list] - ["." set (#+ Set)]]] + ["." set {"+" [Set]}]]] [math [number ["/" rev]]]]] - ["." // #_ + ["." // "_" ["#" continuous]]) (type: .public (Fuzzy a) diff --git a/stdlib/source/library/lux/math/modular.lux b/stdlib/source/library/lux/math/modular.lux index 35f92dc13..012af5c4b 100644 --- a/stdlib/source/library/lux/math/modular.lux +++ b/stdlib/source/library/lux/math/modular.lux @@ -1,31 +1,31 @@ (.module: [library - [lux #* + [lux "*" [abstract - [equivalence (#+ Equivalence)] - [order (#+ Order)] - [monoid (#+ Monoid)] - [codec (#+ Codec)] - [monad (#+ do)]] + [equivalence {"+" [Equivalence]}] + [order {"+" [Order]}] + [monoid {"+" [Monoid]}] + [codec {"+" [Codec]}] + [monad {"+" [do]}]] [control - ["." try (#+ Try)] - ["." exception (#+ exception:)] + ["." try {"+" [Try]}] + ["." exception {"+" [exception:]}] ["<>" parser - ["<.>" text (#+ Parser)] + ["<.>" text {"+" [Parser]}] ["<.>" code]]] [data ["." product] ["." text ("#\." monoid)]] [macro - [syntax (#+ syntax:)] + [syntax {"+" [syntax:]}] ["." code]] [math [number ["i" int ("#\." decimal)]]] [type abstract]]] - ["." // #_ - ["#" modulus (#+ Modulus)]]) + ["." // "_" + ["#" modulus {"+" [Modulus]}]]) (abstract: .public (Mod m) {} diff --git a/stdlib/source/library/lux/math/modulus.lux b/stdlib/source/library/lux/math/modulus.lux index 6ca5a9033..8fda89368 100644 --- a/stdlib/source/library/lux/math/modulus.lux +++ b/stdlib/source/library/lux/math/modulus.lux @@ -1,16 +1,16 @@ (.module: [library - [lux #* + [lux "*" ["." meta] [abstract - [monad (#+ do)]] + [monad {"+" [do]}]] [control - ["." try (#+ Try)] - ["." exception (#+ exception:)] + ["." try {"+" [Try]}] + ["." exception {"+" [exception:]}] [parser ["<.>" code]]] [macro - [syntax (#+ syntax:)] + [syntax {"+" [syntax:]}] ["." code]] [math [number diff --git a/stdlib/source/library/lux/math/number.lux b/stdlib/source/library/lux/math/number.lux index 03007c32e..6722c0329 100644 --- a/stdlib/source/library/lux/math/number.lux +++ b/stdlib/source/library/lux/math/number.lux @@ -1,13 +1,13 @@ (.module: [library - [lux #* + [lux "*" [abstract - [codec (#+ Codec)]] + [codec {"+" [Codec]}]] [control - ["." try (#+ Try)]] + ["." try {"+" [Try]}]] [data ["." text]]]] - ["." / #_ + ["." / "_" ["#." nat] ["#." int] ["#." rev] diff --git a/stdlib/source/library/lux/math/number/complex.lux b/stdlib/source/library/lux/math/number/complex.lux index 8d040123a..0846ed3a8 100644 --- a/stdlib/source/library/lux/math/number/complex.lux +++ b/stdlib/source/library/lux/math/number/complex.lux @@ -1,20 +1,20 @@ (.module: [library - [lux #* + [lux "*" ["." math] [abstract - [equivalence (#+ Equivalence)] - [codec (#+ Codec)] - ["M" monad (#+ Monad do)]] + [equivalence {"+" [Equivalence]}] + [codec {"+" [Codec]}] + ["M" monad {"+" [Monad do]}]] [control ["." maybe] ["<>" parser - ["<.>" code (#+ Parser)]]] + ["<.>" code {"+" [Parser]}]]] [data [collection ["." list ("#\." functor)]]] [macro - [syntax (#+ syntax:)] + [syntax {"+" [syntax:]}] ["." code]] [math [number diff --git a/stdlib/source/library/lux/math/number/frac.lux b/stdlib/source/library/lux/math/number/frac.lux index 5880650e3..4cc1857f1 100644 --- a/stdlib/source/library/lux/math/number/frac.lux +++ b/stdlib/source/library/lux/math/number/frac.lux @@ -1,21 +1,21 @@ (.module: [library - [lux (#- nat int rev) + [lux {"-" [nat int rev]} ["@" target] [abstract - [hash (#+ Hash)] - [monoid (#+ Monoid)] - [equivalence (#+ Equivalence)] - [codec (#+ Codec)] - [predicate (#+ Predicate)] - [order (#+ Order)] - [monad (#+ do)]] + [hash {"+" [Hash]}] + [monoid {"+" [Monoid]}] + [equivalence {"+" [Equivalence]}] + [codec {"+" [Codec]}] + [predicate {"+" [Predicate]}] + [order {"+" [Order]}] + [monad {"+" [do]}]] [control ["." maybe] - ["." try (#+ Try)]] + ["." try {"+" [Try]}]] [data ["." text]]]] - ["." // #_ + ["." // "_" ["#." i64] ["#." nat] ["#." int] diff --git a/stdlib/source/library/lux/math/number/i16.lux b/stdlib/source/library/lux/math/number/i16.lux index 9bbfc83a7..b3e97cb84 100644 --- a/stdlib/source/library/lux/math/number/i16.lux +++ b/stdlib/source/library/lux/math/number/i16.lux @@ -1,13 +1,13 @@ (.module: [library - [lux (#- i64) + [lux {"-" [i64]} [abstract - [equivalence (#+ Equivalence)]] + [equivalence {"+" [Equivalence]}]] [control ["." maybe]] - [type (#+ :by_example)]]] + [type {"+" [:by_example]}]]] [// - ["." i64 (#+ Sub)]]) + ["." i64 {"+" [Sub]}]]) (def: sub (maybe.trusted (i64.sub 16))) diff --git a/stdlib/source/library/lux/math/number/i32.lux b/stdlib/source/library/lux/math/number/i32.lux index 63edd2244..34174ddec 100644 --- a/stdlib/source/library/lux/math/number/i32.lux +++ b/stdlib/source/library/lux/math/number/i32.lux @@ -1,13 +1,13 @@ (.module: [library - [lux (#- i64) - [type (#+ :by_example)] + [lux {"-" [i64]} + [type {"+" [:by_example]}] [abstract - [equivalence (#+ Equivalence)]] + [equivalence {"+" [Equivalence]}]] [control ["." maybe]]]] [// - ["." i64 (#+ Sub)]]) + ["." i64 {"+" [Sub]}]]) (def: sub (maybe.trusted (i64.sub 32))) diff --git a/stdlib/source/library/lux/math/number/i64.lux b/stdlib/source/library/lux/math/number/i64.lux index 475ad82d6..673d99ab2 100644 --- a/stdlib/source/library/lux/math/number/i64.lux +++ b/stdlib/source/library/lux/math/number/i64.lux @@ -1,10 +1,10 @@ (.module: [library - [lux (#- and or not false true) + [lux {"-" [and or not false true]} [abstract - [equivalence (#+ Equivalence)] - [hash (#+ Hash)] - [monoid (#+ Monoid)]] + [equivalence {"+" [Equivalence]}] + [hash {"+" [Hash]}] + [monoid {"+" [Monoid]}]] [control ["." try]]]] [// diff --git a/stdlib/source/library/lux/math/number/i8.lux b/stdlib/source/library/lux/math/number/i8.lux index 7fb3e8e8b..a1d766e75 100644 --- a/stdlib/source/library/lux/math/number/i8.lux +++ b/stdlib/source/library/lux/math/number/i8.lux @@ -1,13 +1,13 @@ (.module: [library - [lux (#- i64) + [lux {"-" [i64]} [abstract - [equivalence (#+ Equivalence)]] + [equivalence {"+" [Equivalence]}]] [control ["." maybe]] - [type (#+ :by_example)]]] + [type {"+" [:by_example]}]]] [// - ["." i64 (#+ Sub)]]) + ["." i64 {"+" [Sub]}]]) (def: sub (maybe.trusted (i64.sub 8))) diff --git a/stdlib/source/library/lux/math/number/int.lux b/stdlib/source/library/lux/math/number/int.lux index 02430432b..53effd0c1 100644 --- a/stdlib/source/library/lux/math/number/int.lux +++ b/stdlib/source/library/lux/math/number/int.lux @@ -1,21 +1,21 @@ (.module: [library - [lux #* + [lux "*" [abstract - [hash (#+ Hash)] - [enum (#+ Enum)] - [interval (#+ Interval)] - [monoid (#+ Monoid)] - [equivalence (#+ Equivalence)] - [codec (#+ Codec)] - [predicate (#+ Predicate)] - ["." order (#+ Order)]] + [hash {"+" [Hash]}] + [enum {"+" [Enum]}] + [interval {"+" [Interval]}] + [monoid {"+" [Monoid]}] + [equivalence {"+" [Equivalence]}] + [codec {"+" [Codec]}] + [predicate {"+" [Predicate]}] + ["." order {"+" [Order]}]] [control ["." maybe] - ["." try (#+ Try)]] + ["." try {"+" [Try]}]] [data - [text (#+ Char)]]]] - ["." // #_ + [text {"+" [Char]}]]]] + ["." // "_" ["#." nat] ["#." i64]]) diff --git a/stdlib/source/library/lux/math/number/nat.lux b/stdlib/source/library/lux/math/number/nat.lux index 0794950b4..5de9ab23d 100644 --- a/stdlib/source/library/lux/math/number/nat.lux +++ b/stdlib/source/library/lux/math/number/nat.lux @@ -1,18 +1,18 @@ (.module: [library - [lux #* + [lux "*" [abstract - [hash (#+ Hash)] - [enum (#+ Enum)] - [interval (#+ Interval)] - [monoid (#+ Monoid)] - [equivalence (#+ Equivalence)] - [codec (#+ Codec)] - ["." order (#+ Order)]] + [hash {"+" [Hash]}] + [enum {"+" [Enum]}] + [interval {"+" [Interval]}] + [monoid {"+" [Monoid]}] + [equivalence {"+" [Equivalence]}] + [codec {"+" [Codec]}] + ["." order {"+" [Order]}]] [control ["." function] ["." maybe] - ["." try (#+ Try)]]]]) + ["." try {"+" [Try]}]]]]) (template [<extension> <output> <name>] [(def: .public (<name> parameter subject) diff --git a/stdlib/source/library/lux/math/number/ratio.lux b/stdlib/source/library/lux/math/number/ratio.lux index 52f826ae8..5d1ab4acf 100644 --- a/stdlib/source/library/lux/math/number/ratio.lux +++ b/stdlib/source/library/lux/math/number/ratio.lux @@ -1,23 +1,23 @@ (.module: [library - [lux (#- nat) + [lux {"-" [nat]} [abstract - [equivalence (#+ Equivalence)] - [order (#+ Order)] - [monoid (#+ Monoid)] - [codec (#+ Codec)] - [monad (#+ do)]] + [equivalence {"+" [Equivalence]}] + [order {"+" [Order]}] + [monoid {"+" [Monoid]}] + [codec {"+" [Codec]}] + [monad {"+" [do]}]] [control ["." function] ["." maybe] ["." try] ["<>" parser - ["<.>" code (#+ Parser)]]] + ["<.>" code {"+" [Parser]}]]] [data ["." product] ["." text ("#\." monoid)]] [macro - [syntax (#+ syntax:)] + [syntax {"+" [syntax:]}] ["." code]]]] [// ["n" nat ("#\." decimal)]]) diff --git a/stdlib/source/library/lux/math/number/rev.lux b/stdlib/source/library/lux/math/number/rev.lux index 06cc92053..e5975ffec 100644 --- a/stdlib/source/library/lux/math/number/rev.lux +++ b/stdlib/source/library/lux/math/number/rev.lux @@ -1,21 +1,21 @@ (.module: [library - [lux #* + [lux "*" [abstract - [hash (#+ Hash)] - [enum (#+ Enum)] - [interval (#+ Interval)] - [monoid (#+ Monoid)] - [equivalence (#+ Equivalence)] - [codec (#+ Codec)] - [order (#+ Order)]] + [hash {"+" [Hash]}] + [enum {"+" [Enum]}] + [interval {"+" [Interval]}] + [monoid {"+" [Monoid]}] + [equivalence {"+" [Equivalence]}] + [codec {"+" [Codec]}] + [order {"+" [Order]}]] [control ["." maybe] ["." try]] [data [collection - ["." array (#+ Array)]]]]] - ["." // #_ + ["." array {"+" [Array]}]]]]] + ["." // "_" ["#." i64] ["#." nat] ["#." int]]) diff --git a/stdlib/source/library/lux/math/random.lux b/stdlib/source/library/lux/math/random.lux index 8803ab037..4e62e6158 100644 --- a/stdlib/source/library/lux/math/random.lux +++ b/stdlib/source/library/lux/math/random.lux @@ -1,41 +1,41 @@ (.module: [library - [lux (#- or and list i64 nat int rev char) + [lux {"-" [or and list i64 nat int rev char]} [abstract - [hash (#+ Hash)] - [functor (#+ Functor)] - [apply (#+ Apply)] - ["." monad (#+ Monad do)]] + [hash {"+" [Hash]}] + [functor {"+" [Functor]}] + [apply {"+" [Apply]}] + ["." monad {"+" [Monad do]}]] [data - ["." text (#+ Char) ("#\." monoid) - ["." unicode #_ + ["." text {"+" [Char]} ("#\." monoid) + ["." unicode "_" ["#" set]]] [collection ["." list ("#\." mix)] - ["." array (#+ Array)] - ["." dictionary (#+ Dictionary)] - ["." queue (#+ Queue)] - ["." set (#+ Set)] - ["." stack (#+ Stack)] - ["." row (#+ Row)] + ["." array {"+" [Array]}] + ["." dictionary {"+" [Dictionary]}] + ["." queue {"+" [Queue]}] + ["." set {"+" [Set]}] + ["." stack {"+" [Stack]}] + ["." row {"+" [Row]}] [tree - ["." finger (#+ Tree)]]]] + ["." finger {"+" [Tree]}]]]] [math - [number (#+ hex) + [number {"+" [hex]} ["n" nat] ["i" int] ["f" frac] ["r" ratio] ["c" complex] ["." i64]]] - ["." time (#+ Time) - ["." instant (#+ Instant)] - ["." date (#+ Date)] - ["." duration (#+ Duration)] - ["." month (#+ Month)] - ["." day (#+ Day)]] + ["." time {"+" [Time]} + ["." instant {"+" [Instant]}] + ["." date {"+" [Date]}] + ["." duration {"+" [Duration]}] + ["." month {"+" [Month]}] + ["." day {"+" [Day]}]] [type - [refinement (#+ Refiner Refined)]]]]) + [refinement {"+" [Refiner Refined]}]]]]) (type: .public PRNG (Rec PRNG diff --git a/stdlib/source/library/lux/meta.lux b/stdlib/source/library/lux/meta.lux index 87ffc64be..ac26a08a4 100644 --- a/stdlib/source/library/lux/meta.lux +++ b/stdlib/source/library/lux/meta.lux @@ -1,13 +1,13 @@ (.module: [library - [lux (#- type macro try) + [lux {"-" [type macro try]} [abstract - [functor (#+ Functor)] - [apply (#+ Apply)] - ["." monad (#+ Monad do)]] + [functor {"+" [Functor]}] + [apply {"+" [Apply]}] + ["." monad {"+" [Monad do]}]] [control ["." maybe] - ["." try (#+ Try)]] + ["." try {"+" [Try]}]] [data ["." product] ["." text ("#\." monoid order)] diff --git a/stdlib/source/library/lux/meta/annotation.lux b/stdlib/source/library/lux/meta/annotation.lux index 5617cd88c..1b5c7f4f0 100644 --- a/stdlib/source/library/lux/meta/annotation.lux +++ b/stdlib/source/library/lux/meta/annotation.lux @@ -1,8 +1,8 @@ (.module: [library - [lux (#- nat int rev) + [lux {"-" [nat int rev]} [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control ["." maybe]] [data diff --git a/stdlib/source/library/lux/meta/location.lux b/stdlib/source/library/lux/meta/location.lux index 7282e9c1b..7f37b4d77 100644 --- a/stdlib/source/library/lux/meta/location.lux +++ b/stdlib/source/library/lux/meta/location.lux @@ -1,8 +1,8 @@ (.module: [library - [lux #* + [lux "*" [abstract - [equivalence (#+ Equivalence)]]]]) + [equivalence {"+" [Equivalence]}]]]]) (implementation: .public equivalence (Equivalence Location) diff --git a/stdlib/source/library/lux/program.lux b/stdlib/source/library/lux/program.lux index f53788682..ccd1633a6 100644 --- a/stdlib/source/library/lux/program.lux +++ b/stdlib/source/library/lux/program.lux @@ -1,9 +1,9 @@ (.module: [library - [lux #* + [lux "*" ["@" target] [abstract - [monad (#+ do)]] + [monad {"+" [do]}]] [control ["." io] [concurrency @@ -15,8 +15,8 @@ ["." text] [collection ["." list ("#\." monad)]]] - [macro (#+ with_identifiers) - [syntax (#+ syntax:)] + [macro {"+" [with_identifiers]} + [syntax {"+" [syntax:]}] ["." code]]]]) (type: Arguments diff --git a/stdlib/source/library/lux/static.lux b/stdlib/source/library/lux/static.lux index 668a23331..3f9d9caed 100644 --- a/stdlib/source/library/lux/static.lux +++ b/stdlib/source/library/lux/static.lux @@ -1,18 +1,18 @@ (.module: [library - [lux (#- nat int rev) + [lux {"-" [nat int rev]} ["." meta] [abstract - [monad (#+ do)]] + [monad {"+" [do]}]] [control ["<>" parser ["<.>" code]]] [macro - [syntax (#+ syntax:)] + [syntax {"+" [syntax:]}] ["." code]] [math - [number (#+ hex)] - ["." random (#+ Random)]]]]) + [number {"+" [hex]}] + ["." random {"+" [Random]}]]]]) (template [<name> <type> <format>] [(syntax: .public (<name> [expression <code>.any]) diff --git a/stdlib/source/library/lux/target.lux b/stdlib/source/library/lux/target.lux index fca7b2f6c..e909f5526 100644 --- a/stdlib/source/library/lux/target.lux +++ b/stdlib/source/library/lux/target.lux @@ -1,6 +1,6 @@ (.module: [library - [lux #*]]) + [lux "*"]]) (type: .public Target Text) diff --git a/stdlib/source/library/lux/target/common_lisp.lux b/stdlib/source/library/lux/target/common_lisp.lux index 9714e7743..d57cb51c9 100644 --- a/stdlib/source/library/lux/target/common_lisp.lux +++ b/stdlib/source/library/lux/target/common_lisp.lux @@ -1,11 +1,11 @@ (.module: [library - [lux (#- Code int if cond or and comment let) + [lux {"-" [Code int if cond or and comment let]} [control - [pipe (#+ case> cond> new>)]] + [pipe {"+" [case> cond> new>]}]] [data ["." text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." list ("#\." monad monoid)]]] [macro diff --git a/stdlib/source/library/lux/target/js.lux b/stdlib/source/library/lux/target/js.lux index 62ce204c5..fc1257fdc 100644 --- a/stdlib/source/library/lux/target/js.lux +++ b/stdlib/source/library/lux/target/js.lux @@ -1,11 +1,11 @@ (.module: [library - [lux (#- Location Code Label or and function if cond undefined for comment not int try ++ --) + [lux {"-" [Location Code Label or and function if cond undefined for comment not int try ++ --]} [control - [pipe (#+ case>)]] + [pipe {"+" [case>]}]] [data ["." text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." list ("#\." functor mix)]]] [macro diff --git a/stdlib/source/library/lux/target/jvm.lux b/stdlib/source/library/lux/target/jvm.lux index 50543961c..8da4679fc 100644 --- a/stdlib/source/library/lux/target/jvm.lux +++ b/stdlib/source/library/lux/target/jvm.lux @@ -1,13 +1,13 @@ (.module: [library - [lux (#- Type Label) + [lux {"-" [Type Label]} [data [collection - [row (#+ Row)]]] + [row {"+" [Row]}]]] [target [jvm - [type (#+ Type) - ["." category (#+ Primitive Class Value Method)]]]]]]) + [type {"+" [Type]} + ["." category {"+" [Primitive Class Value Method]}]]]]]]) (type: .public Literal (Variant diff --git a/stdlib/source/library/lux/target/jvm/attribute.lux b/stdlib/source/library/lux/target/jvm/attribute.lux index 45758f54f..053c59e3f 100644 --- a/stdlib/source/library/lux/target/jvm/attribute.lux +++ b/stdlib/source/library/lux/target/jvm/attribute.lux @@ -1,28 +1,28 @@ (.module: [library - [lux (#- Info Code) + [lux {"-" [Info Code]} [abstract - [monad (#+ do)] - ["." equivalence (#+ Equivalence)]] + [monad {"+" [do]}] + ["." equivalence {"+" [Equivalence]}]] [control ["." try] - ["." exception (#+ exception:)]] + ["." exception {"+" [exception:]}]] [data ["." sum] ["." product] [format - [".F" binary (#+ Writer)]]] + [".F" binary {"+" [Writer]}]]] [math [number ["n" nat]]]]] - ["." // #_ - ["#." index (#+ Index)] + ["." // "_" + ["#." index {"+" [Index]}] [encoding - ["#." unsigned (#+ U2 U4)]] - ["#." constant (#+ UTF8 Class Value) - ["#/." pool (#+ Pool Resource)]]] - ["." / #_ - ["#." constant (#+ Constant)] + ["#." unsigned {"+" [U2 U4]}]] + ["#." constant {"+" [UTF8 Class Value]} + ["#/." pool {"+" [Pool Resource]}]]] + ["." / "_" + ["#." constant {"+" [Constant]}] ["#." code]]) (type: .public (Info about) diff --git a/stdlib/source/library/lux/target/jvm/attribute/code.lux b/stdlib/source/library/lux/target/jvm/attribute/code.lux index 207ddf022..eec5e8233 100644 --- a/stdlib/source/library/lux/target/jvm/attribute/code.lux +++ b/stdlib/source/library/lux/target/jvm/attribute/code.lux @@ -1,26 +1,26 @@ (.module: [library - [lux (#- Code) + [lux {"-" [Code]} [abstract - [equivalence (#+ Equivalence)]] + [equivalence {"+" [Equivalence]}]] [data ["." product] - ["." binary (#+ Binary)] + ["." binary {"+" [Binary]}] [format - [".F" binary (#+ Writer) ("#\." monoid)]] + [".F" binary {"+" [Writer]} ("#\." monoid)]] [collection - ["." row (#+ Row) ("#\." functor mix)]]] + ["." row {"+" [Row]} ("#\." functor mix)]]] [math [number ["n" nat]]]]] - ["." /// #_ + ["." /// "_" [bytecode [environment - ["#." limit (#+ Limit)]]] + ["#." limit {"+" [Limit]}]]] [encoding - ["#." unsigned (#+ U2)]]] - ["." / #_ - ["#." exception (#+ Exception)]]) + ["#." unsigned {"+" [U2]}]]] + ["." / "_" + ["#." exception {"+" [Exception]}]]) (type: .public (Code Attribute) (Record diff --git a/stdlib/source/library/lux/target/jvm/attribute/code/exception.lux b/stdlib/source/library/lux/target/jvm/attribute/code/exception.lux index 6bdf8dfff..97cda5be3 100644 --- a/stdlib/source/library/lux/target/jvm/attribute/code/exception.lux +++ b/stdlib/source/library/lux/target/jvm/attribute/code/exception.lux @@ -1,23 +1,23 @@ (.module: [library - [lux #* + [lux "*" [abstract - [equivalence (#+ Equivalence)]] + [equivalence {"+" [Equivalence]}]] [data ["." product] - ["." format #_ - ["#" binary (#+ Writer)]]] + ["." format "_" + ["#" binary {"+" [Writer]}]]] [math [number ["n" nat]]]]] - ["." // #_ - ["//#" /// #_ - [constant (#+ Class)] - ["#." index (#+ Index)] + ["." // "_" + ["//#" /// "_" + [constant {"+" [Class]}] + ["#." index {"+" [Index]}] [bytecode - ["#." address (#+ Address)]] + ["#." address {"+" [Address]}]] [encoding - ["#." unsigned (#+ U2)]]]]) + ["#." unsigned {"+" [U2]}]]]]) (type: .public Exception (Record diff --git a/stdlib/source/library/lux/target/jvm/attribute/constant.lux b/stdlib/source/library/lux/target/jvm/attribute/constant.lux index d9242dc89..1f03b9162 100644 --- a/stdlib/source/library/lux/target/jvm/attribute/constant.lux +++ b/stdlib/source/library/lux/target/jvm/attribute/constant.lux @@ -1,16 +1,16 @@ (.module: [library - [lux #* + [lux "*" [abstract - [equivalence (#+ Equivalence)]] + [equivalence {"+" [Equivalence]}]] [data [format - [binary (#+ Writer)]]]]] - ["." /// #_ - [constant (#+ Value)] - ["#." index (#+ Index)] + [binary {"+" [Writer]}]]]]] + ["." /// "_" + [constant {"+" [Value]}] + ["#." index {"+" [Index]}] [encoding - ["#." unsigned (#+ U2 U4)]]]) + ["#." unsigned {"+" [U2 U4]}]]]) (type: .public (Constant a) (Index (Value a))) diff --git a/stdlib/source/library/lux/target/jvm/bytecode.lux b/stdlib/source/library/lux/target/jvm/bytecode.lux index 0cb111e13..bb0c14d64 100644 --- a/stdlib/source/library/lux/target/jvm/bytecode.lux +++ b/stdlib/source/library/lux/target/jvm/bytecode.lux @@ -1,53 +1,53 @@ (.module: [library - [lux (#- Type Label int try) - ["." ffi (#+ import:)] + [lux {"-" [Type Label int try]} + ["." ffi {"+" [import:]}] [abstract - [monoid (#+ Monoid)] - ["." monad (#+ Monad do)]] + [monoid {"+" [Monoid]}] + ["." monad {"+" [Monad do]}]] [control - ["." writer (#+ Writer)] - ["." state (#+ +State)] + ["." writer {"+" [Writer]}] + ["." state {"+" [+State]}] ["." function] ["." maybe] - ["." try (#+ Try)] - ["." exception (#+ exception:)]] + ["." try {"+" [Try]}] + ["." exception {"+" [exception:]}]] [data ["." product] [text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." list ("#\." functor mix)] - ["." dictionary (#+ Dictionary)] - ["." row (#+ Row)]]] + ["." dictionary {"+" [Dictionary]}] + ["." row {"+" [Row]}]]] [macro ["." template]] [math [number ["n" nat] ["i" int] - ["." i32 (#+ I32)]]]]] - ["." / #_ - ["#." address (#+ Address)] - ["#." jump (#+ Jump Big_Jump)] - ["_" instruction (#+ Primitive_Array_Type Instruction Estimator) ("#\." monoid)] - ["#." environment (#+ Environment) + ["." i32 {"+" [I32]}]]]]] + ["." / "_" + ["#." address {"+" [Address]}] + ["#." jump {"+" [Jump Big_Jump]}] + ["_" instruction {"+" [Primitive_Array_Type Instruction Estimator]} ("#\." monoid)] + ["#." environment {"+" [Environment]} [limit - ["/." registry (#+ Register Registry)] - ["/." stack (#+ Stack)]]] - ["/#" // #_ - ["#." index (#+ Index)] + ["/." registry {"+" [Register Registry]}] + ["/." stack {"+" [Stack]}]]] + ["/#" // "_" + ["#." index {"+" [Index]}] [encoding ["#." name] - ["#." unsigned (#+ U1 U2)] - ["#." signed (#+ S1 S2 S4)]] - ["#." constant (#+ UTF8) - ["#/." pool (#+ Pool Resource)]] + ["#." unsigned {"+" [U1 U2]}] + ["#." signed {"+" [S1 S2 S4]}]] + ["#." constant {"+" [UTF8]} + ["#/." pool {"+" [Pool Resource]}]] [attribute [code - ["#." exception (#+ Exception)]]] - ["." type (#+ Type) - [category (#+ Class Object Value' Value Return' Return Method)] + ["#." exception {"+" [Exception]}]]] + ["." type {"+" [Type]} + [category {"+" [Class Object Value' Value Return' Return Method]}] ["." reflection] ["." parser]]]]) diff --git a/stdlib/source/library/lux/target/jvm/bytecode/address.lux b/stdlib/source/library/lux/target/jvm/bytecode/address.lux index 51ab13080..302fbcc8e 100644 --- a/stdlib/source/library/lux/target/jvm/bytecode/address.lux +++ b/stdlib/source/library/lux/target/jvm/bytecode/address.lux @@ -1,27 +1,27 @@ (.module: [library - [lux #* + [lux "*" [abstract - [equivalence (#+ Equivalence)] - [monad (#+ do)]] + [equivalence {"+" [Equivalence]}] + [monad {"+" [do]}]] [control - ["." try (#+ Try)]] + ["." try {"+" [Try]}]] [data [format - [binary (#+ Writer)]] + [binary {"+" [Writer]}]] [text - ["%" format (#+ Format)]]] + ["%" format {"+" [Format]}]]] [math [number ["n" nat]]] [type abstract]]] - ["." // #_ - [jump (#+ Big_Jump)] - ["/#" // #_ + ["." // "_" + [jump {"+" [Big_Jump]}] + ["/#" // "_" [encoding - ["#." unsigned (#+ U2)] - ["#." signed (#+ S4)]]]]) + ["#." unsigned {"+" [U2]}] + ["#." signed {"+" [S4]}]]]]) (abstract: .public Address {} diff --git a/stdlib/source/library/lux/target/jvm/bytecode/environment.lux b/stdlib/source/library/lux/target/jvm/bytecode/environment.lux index 2bf2c5c31..ade32b3d4 100644 --- a/stdlib/source/library/lux/target/jvm/bytecode/environment.lux +++ b/stdlib/source/library/lux/target/jvm/bytecode/environment.lux @@ -1,21 +1,21 @@ (.module: [library - [lux (#- Type static) + [lux {"-" [Type static]} [abstract - [monad (#+ do)] - [monoid (#+ Monoid)]] + [monad {"+" [do]}] + [monoid {"+" [Monoid]}]] [control - ["." try (#+ Try)] - ["." exception (#+ exception:)]]]] + ["." try {"+" [Try]}] + ["." exception {"+" [exception:]}]]]] [/ - ["/." limit (#+ Limit) - ["/." stack (#+ Stack)] - ["/." registry (#+ Registry)]] + ["/." limit {"+" [Limit]} + ["/." stack {"+" [Stack]}] + ["/." registry {"+" [Registry]}]] [/// [encoding - [unsigned (#+ U2)]] - [type (#+ Type) - [category (#+ Method)]]]]) + [unsigned {"+" [U2]}]] + [type {"+" [Type]} + [category {"+" [Method]}]]]]) (type: .public Environment (Record diff --git a/stdlib/source/library/lux/target/jvm/bytecode/environment/limit.lux b/stdlib/source/library/lux/target/jvm/bytecode/environment/limit.lux index 4ab466ae4..faac0819b 100644 --- a/stdlib/source/library/lux/target/jvm/bytecode/environment/limit.lux +++ b/stdlib/source/library/lux/target/jvm/bytecode/environment/limit.lux @@ -1,24 +1,24 @@ (.module: [library - [lux (#- Type static) + [lux {"-" [Type static]} [abstract - [monad (#+ do)] - [equivalence (#+ Equivalence)]] + [monad {"+" [do]}] + [equivalence {"+" [Equivalence]}]] [control - ["." try (#+ Try)]] + ["." try {"+" [Try]}]] [data ["." product] - ["." format #_ - ["#" binary (#+ Writer) ("#\." monoid)]]] + ["." format "_" + ["#" binary {"+" [Writer]} ("#\." monoid)]]] [math [number ["n" nat]]]]] - ["." / #_ - ["#." stack (#+ Stack)] - ["#." registry (#+ Registry)] + ["." / "_" + ["#." stack {"+" [Stack]}] + ["#." registry {"+" [Registry]}] [//// - [type (#+ Type) - [category (#+ Method)]]]]) + [type {"+" [Type]} + [category {"+" [Method]}]]]]) (type: .public Limit (Record diff --git a/stdlib/source/library/lux/target/jvm/bytecode/environment/limit/registry.lux b/stdlib/source/library/lux/target/jvm/bytecode/environment/limit/registry.lux index 04bf00456..e2fa1461f 100644 --- a/stdlib/source/library/lux/target/jvm/bytecode/environment/limit/registry.lux +++ b/stdlib/source/library/lux/target/jvm/bytecode/environment/limit/registry.lux @@ -1,13 +1,13 @@ (.module: [library - [lux (#- Type for static) + [lux {"-" [Type for static]} [abstract - ["." equivalence (#+ Equivalence)]] + ["." equivalence {"+" [Equivalence]}]] [control - ["." try (#+ Try) ("#\." functor)]] + ["." try {"+" [Try]} ("#\." functor)]] [data [format - [binary (#+ Writer)]] + [binary {"+" [Writer]}]] [collection ["." list ("#\." functor mix)]]] [math @@ -15,11 +15,11 @@ ["n" nat]]] [type abstract]]] - ["." ///// #_ + ["." ///// "_" [encoding - ["#." unsigned (#+ U1 U2)]] - ["#." type (#+ Type) - [category (#+ Method)] + ["#." unsigned {"+" [U1 U2]}]] + ["#." type {"+" [Type]} + [category {"+" [Method]}] ["#/." parser]]]) (type: .public Register diff --git a/stdlib/source/library/lux/target/jvm/bytecode/environment/limit/stack.lux b/stdlib/source/library/lux/target/jvm/bytecode/environment/limit/stack.lux index 13d4b5137..396c972c5 100644 --- a/stdlib/source/library/lux/target/jvm/bytecode/environment/limit/stack.lux +++ b/stdlib/source/library/lux/target/jvm/bytecode/environment/limit/stack.lux @@ -1,21 +1,21 @@ (.module: [library - [lux #* + [lux "*" [abstract - ["." equivalence (#+ Equivalence)]] + ["." equivalence {"+" [Equivalence]}]] [control ["." maybe] - ["." try (#+ Try)]] + ["." try {"+" [Try]}]] [data [text - ["%" format (#+ Format)]] + ["%" format {"+" [Format]}]] [format - [binary (#+ Writer)]]] + [binary {"+" [Writer]}]]] [type abstract]]] - ["." ///// #_ + ["." ///// "_" [encoding - ["#." unsigned (#+ U2)]]]) + ["#." unsigned {"+" [U2]}]]]) (abstract: .public Stack {} diff --git a/stdlib/source/library/lux/target/jvm/bytecode/instruction.lux b/stdlib/source/library/lux/target/jvm/bytecode/instruction.lux index bba0c67da..effbdda4a 100644 --- a/stdlib/source/library/lux/target/jvm/bytecode/instruction.lux +++ b/stdlib/source/library/lux/target/jvm/bytecode/instruction.lux @@ -1,40 +1,40 @@ (.module: [library - [lux #* + [lux "*" [abstract - [monad (#+ do)] - [monoid (#+ Monoid)]] + [monad {"+" [do]}] + [monoid {"+" [Monoid]}]] [control ["." function] ["." try]] [data ["." product] ["." binary] - ["." format #_ - ["#" binary (#+ Mutation Specification)]] + ["." format "_" + ["#" binary {"+" [Mutation Specification]}]] [collection ["." list]]] [macro ["." template]] [math - [number (#+ hex) + [number {"+" [hex]} ["n" nat]]] [type abstract]]] - ["." // #_ - ["#." address (#+ Address)] - ["#." jump (#+ Jump Big_Jump)] + ["." // "_" + ["#." address {"+" [Address]}] + ["#." jump {"+" [Jump Big_Jump]}] [environment [limit - [registry (#+ Register)]]] - ["/#" // #_ - ["#." index (#+ Index)] - ["#." constant (#+ Class Reference)] + [registry {"+" [Register]}]]] + ["/#" // "_" + ["#." index {"+" [Index]}] + ["#." constant {"+" [Class Reference]}] [encoding - ["#." unsigned (#+ U1 U2 U4)] - ["#." signed (#+ S1 S2 S4)]] + ["#." unsigned {"+" [U1 U2 U4]}] + ["#." signed {"+" [S1 S2 S4]}]] [type - [category (#+ Value Method)]]]]) + [category {"+" [Value Method]}]]]]) (type: .public Size U2) diff --git a/stdlib/source/library/lux/target/jvm/bytecode/jump.lux b/stdlib/source/library/lux/target/jvm/bytecode/jump.lux index 4b908d990..615b7f9ac 100644 --- a/stdlib/source/library/lux/target/jvm/bytecode/jump.lux +++ b/stdlib/source/library/lux/target/jvm/bytecode/jump.lux @@ -1,14 +1,14 @@ (.module: [library - [lux #* + [lux "*" [abstract - [equivalence (#+ Equivalence)]] + [equivalence {"+" [Equivalence]}]] [data - ["." format #_ - ["#" binary (#+ Writer)]]]]] - ["." /// #_ + ["." format "_" + ["#" binary {"+" [Writer]}]]]]] + ["." /// "_" [encoding - ["#." signed (#+ S2 S4)]]]) + ["#." signed {"+" [S2 S4]}]]]) (type: .public Jump S2) diff --git a/stdlib/source/library/lux/target/jvm/class.lux b/stdlib/source/library/lux/target/jvm/class.lux index 1dae89e90..72bdce14e 100644 --- a/stdlib/source/library/lux/target/jvm/class.lux +++ b/stdlib/source/library/lux/target/jvm/class.lux @@ -1,31 +1,31 @@ (.module: [library - [lux (#- public private) + [lux {"-" [public private]} [abstract - [equivalence (#+ Equivalence)] - ["." monad (#+ do)]] + [equivalence {"+" [Equivalence]}] + ["." monad {"+" [do]}]] [control ["." state] - ["." try (#+ Try)]] + ["." try {"+" [Try]}]] [data ["." product] [format - [".F" binary (#+ Writer) ("#\." monoid)]] + [".F" binary {"+" [Writer]} ("#\." monoid)]] [collection - ["." row (#+ Row)]]]]] - ["." // #_ - ["#." modifier (#+ Modifier modifiers:)] - ["#." version (#+ Version Minor Major)] - ["#." magic (#+ Magic)] - ["#." index (#+ Index)] - ["#." attribute (#+ Attribute)] - ["#." field (#+ Field)] - ["#." method (#+ Method)] + ["." row {"+" [Row]}]]]]] + ["." // "_" + ["#." modifier {"+" [Modifier modifiers:]}] + ["#." version {"+" [Version Minor Major]}] + ["#." magic {"+" [Magic]}] + ["#." index {"+" [Index]}] + ["#." attribute {"+" [Attribute]}] + ["#." field {"+" [Field]}] + ["#." method {"+" [Method]}] [encoding ["#." unsigned] - ["#." name (#+ Internal)]] - ["#." constant (#+ Constant) - ["#/." pool (#+ Pool Resource)]]]) + ["#." name {"+" [Internal]}]] + ["#." constant {"+" [Constant]} + ["#/." pool {"+" [Pool Resource]}]]]) (type: .public Class (Rec Class diff --git a/stdlib/source/library/lux/target/jvm/constant.lux b/stdlib/source/library/lux/target/jvm/constant.lux index 780816d70..82e4c49e1 100644 --- a/stdlib/source/library/lux/target/jvm/constant.lux +++ b/stdlib/source/library/lux/target/jvm/constant.lux @@ -1,36 +1,36 @@ (.module: [library - [lux #* - ["." ffi (#+ import:)] + [lux "*" + ["." ffi {"+" [import:]}] ["@" target] [abstract - [monad (#+ do)] - ["." equivalence (#+ Equivalence)]] + [monad {"+" [do]}] + ["." equivalence {"+" [Equivalence]}]] [data ["." sum] ["." product] ["." text] [format - [".F" binary (#+ Writer) ("#\." monoid)]] + [".F" binary {"+" [Writer]} ("#\." monoid)]] [collection - ["." row (#+ Row)]]] + ["." row {"+" [Row]}]]] [macro ["." template]] [math [number - ["." i32 (#+ I32)] + ["." i32 {"+" [I32]}] ["." i64] ["." int] ["." frac]]] [type abstract]]] - ["." / #_ + ["." / "_" ["#." tag] - ["/#" // #_ - ["#." index (#+ Index)] + ["/#" // "_" + ["#." index {"+" [Index]}] [type ["#." category] - ["#." descriptor (#+ Descriptor)]] + ["#." descriptor {"+" [Descriptor]}]] [encoding ["#." unsigned]]]]) diff --git a/stdlib/source/library/lux/target/jvm/constant/pool.lux b/stdlib/source/library/lux/target/jvm/constant/pool.lux index a680980ef..7bdb7d977 100644 --- a/stdlib/source/library/lux/target/jvm/constant/pool.lux +++ b/stdlib/source/library/lux/target/jvm/constant/pool.lux @@ -1,20 +1,20 @@ (.module: [library - [lux #* + [lux "*" ["." ffi] [abstract - [equivalence (#+ Equivalence)] - [monad (#+ Monad do)]] + [equivalence {"+" [Equivalence]}] + [monad {"+" [Monad do]}]] [control - ["." state (#+ +State)] - ["." try (#+ Try)]] + ["." state {"+" [+State]}] + ["." try {"+" [Try]}]] [data ["." product] ["." text] - ["." format #_ - ["#" binary (#+ Writer) ("specification\." monoid)]] + ["." format "_" + ["#" binary {"+" [Writer]} ("specification\." monoid)]] [collection - ["." row (#+ Row) ("#\." mix)]]] + ["." row {"+" [Row]} ("#\." mix)]]] [macro ["." template]] [math @@ -25,15 +25,15 @@ ["." frac]]] [type abstract]]] - ["." // (#+ UTF8 String Class Integer Float Long Double Constant Name_And_Type Reference) + ["." // {"+" [UTF8 String Class Integer Float Long Double Constant Name_And_Type Reference]} [// [encoding - ["#." name (#+ Internal External)] + ["#." name {"+" [Internal External]}] ["#." unsigned]] - ["#." index (#+ Index)] + ["#." index {"+" [Index]}] [type - [category (#+ Value Method)] - ["#." descriptor (#+ Descriptor)]]]]) + [category {"+" [Value Method]}] + ["#." descriptor {"+" [Descriptor]}]]]]) (type: .public Pool [Index (Row [Index Constant])]) diff --git a/stdlib/source/library/lux/target/jvm/constant/tag.lux b/stdlib/source/library/lux/target/jvm/constant/tag.lux index 54b4dbba1..75afcd52c 100644 --- a/stdlib/source/library/lux/target/jvm/constant/tag.lux +++ b/stdlib/source/library/lux/target/jvm/constant/tag.lux @@ -1,18 +1,18 @@ (.module: [library - [lux #* + [lux "*" [abstract - [equivalence (#+ Equivalence)]] + [equivalence {"+" [Equivalence]}]] [control ["." try]] [data [format - [binary (#+ Writer)]]] + [binary {"+" [Writer]}]]] [type abstract]]] - ["." /// #_ + ["." /// "_" [encoding - ["#." unsigned (#+ U1) ("u1//." equivalence)]]]) + ["#." unsigned {"+" [U1]} ("u1//." equivalence)]]]) (abstract: .public Tag {} diff --git a/stdlib/source/library/lux/target/jvm/encoding/name.lux b/stdlib/source/library/lux/target/jvm/encoding/name.lux index eb232aaba..b515e1d6b 100644 --- a/stdlib/source/library/lux/target/jvm/encoding/name.lux +++ b/stdlib/source/library/lux/target/jvm/encoding/name.lux @@ -1,9 +1,9 @@ (.module: [library - [lux #* + [lux "*" [data ["." text - ["%" format (#+ format)]]] + ["%" format {"+" [format]}]]] [type abstract]]]) diff --git a/stdlib/source/library/lux/target/jvm/encoding/signed.lux b/stdlib/source/library/lux/target/jvm/encoding/signed.lux index 5a687eaba..abd02e3d8 100644 --- a/stdlib/source/library/lux/target/jvm/encoding/signed.lux +++ b/stdlib/source/library/lux/target/jvm/encoding/signed.lux @@ -1,17 +1,17 @@ (.module: [library - [lux (#- int) + [lux {"-" [int]} [abstract - [equivalence (#+ Equivalence)] - [order (#+ Order)]] + [equivalence {"+" [Equivalence]}] + [order {"+" [Order]}]] [control - ["." try (#+ Try)] - ["." exception (#+ exception:)]] + ["." try {"+" [Try]}] + ["." exception {"+" [exception:]}]] [data [text - ["%" format (#+ format)]] - ["." format #_ - ["#" binary (#+ Writer)]]] + ["%" format {"+" [format]}]] + ["." format "_" + ["#" binary {"+" [Writer]}]]] [macro ["." template]] [math diff --git a/stdlib/source/library/lux/target/jvm/encoding/unsigned.lux b/stdlib/source/library/lux/target/jvm/encoding/unsigned.lux index 2b38774f5..6d0f259cb 100644 --- a/stdlib/source/library/lux/target/jvm/encoding/unsigned.lux +++ b/stdlib/source/library/lux/target/jvm/encoding/unsigned.lux @@ -1,17 +1,17 @@ (.module: [library - [lux (#- nat) + [lux {"-" [nat]} [abstract - [equivalence (#+ Equivalence)] - [order (#+ Order)]] + [equivalence {"+" [Equivalence]}] + [order {"+" [Order]}]] [control - ["." try (#+ Try)] - ["." exception (#+ exception:)]] + ["." try {"+" [Try]}] + ["." exception {"+" [exception:]}]] [data [text - ["%" format (#+ format)]] - ["." format #_ - ["#" binary (#+ Writer)]]] + ["%" format {"+" [format]}]] + ["." format "_" + ["#" binary {"+" [Writer]}]]] [macro ["." template]] [math diff --git a/stdlib/source/library/lux/target/jvm/field.lux b/stdlib/source/library/lux/target/jvm/field.lux index a709da105..b3f41c3f1 100644 --- a/stdlib/source/library/lux/target/jvm/field.lux +++ b/stdlib/source/library/lux/target/jvm/field.lux @@ -1,24 +1,24 @@ (.module: [library - [lux (#- Type static public private) + [lux {"-" [Type static public private]} [abstract - [equivalence (#+ Equivalence)] - ["." monad (#+ do)]] + [equivalence {"+" [Equivalence]}] + ["." monad {"+" [do]}]] [data ["." product] [format - [".F" binary (#+ Writer) ("#\." monoid)]] + [".F" binary {"+" [Writer]} ("#\." monoid)]] [collection - ["." row (#+ Row)]]]]] - ["." // #_ - ["." modifier (#+ Modifier modifiers:)] - ["#." constant (#+ UTF8) - ["#/." pool (#+ Pool Resource)]] - ["#." index (#+ Index)] - ["#." attribute (#+ Attribute)] - ["#." type (#+ Type) - [category (#+ Value)] - [descriptor (#+ Descriptor)]]]) + ["." row {"+" [Row]}]]]]] + ["." // "_" + ["." modifier {"+" [Modifier modifiers:]}] + ["#." constant {"+" [UTF8]} + ["#/." pool {"+" [Pool Resource]}]] + ["#." index {"+" [Index]}] + ["#." attribute {"+" [Attribute]}] + ["#." type {"+" [Type]} + [category {"+" [Value]}] + [descriptor {"+" [Descriptor]}]]]) (type: .public Field (Rec Field diff --git a/stdlib/source/library/lux/target/jvm/index.lux b/stdlib/source/library/lux/target/jvm/index.lux index 5651ac589..178586d44 100644 --- a/stdlib/source/library/lux/target/jvm/index.lux +++ b/stdlib/source/library/lux/target/jvm/index.lux @@ -1,16 +1,16 @@ (.module: [library - [lux #* + [lux "*" [abstract - ["." equivalence (#+ Equivalence)]] + ["." equivalence {"+" [Equivalence]}]] [data [format - [binary (#+ Writer)]]] + [binary {"+" [Writer]}]]] [type abstract]]] - ["." // #_ + ["." // "_" [encoding - ["#." unsigned (#+ U2)]]]) + ["#." unsigned {"+" [U2]}]]]) (def: .public length //unsigned.bytes/2) diff --git a/stdlib/source/library/lux/target/jvm/loader.lux b/stdlib/source/library/lux/target/jvm/loader.lux index daae8ca9a..511dd9c39 100644 --- a/stdlib/source/library/lux/target/jvm/loader.lux +++ b/stdlib/source/library/lux/target/jvm/loader.lux @@ -1,23 +1,23 @@ (.module: [library - [lux #* + [lux "*" ["@" target] - ["." ffi (#+ import: object do_to)] + ["." ffi {"+" [import: object do_to]}] [abstract - [monad (#+ do)]] + [monad {"+" [do]}]] [control - ["." try (#+ Try)] - ["." exception (#+ exception:)] - ["." io (#+ IO)] + ["." try {"+" [Try]}] + ["." exception {"+" [exception:]}] + ["." io {"+" [IO]}] [concurrency - ["." atom (#+ Atom)]]] + ["." atom {"+" [Atom]}]]] [data - ["." binary (#+ Binary)] + ["." binary {"+" [Binary]}] ["." text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." array] - ["." dictionary (#+ Dictionary)]]]]]) + ["." dictionary {"+" [Dictionary]}]]]]]) (type: .public Library (Atom (Dictionary Text Binary))) diff --git a/stdlib/source/library/lux/target/jvm/magic.lux b/stdlib/source/library/lux/target/jvm/magic.lux index b2b547fcf..a29a6a73b 100644 --- a/stdlib/source/library/lux/target/jvm/magic.lux +++ b/stdlib/source/library/lux/target/jvm/magic.lux @@ -1,13 +1,13 @@ (.module: [library - [lux #* + [lux "*" [control ["." try]] [math - [number (#+ hex)]]]] - ["." // #_ + [number {"+" [hex]}]]]] + ["." // "_" [encoding - ["#." unsigned (#+ U4)]]]) + ["#." unsigned {"+" [U4]}]]]) (type: .public Magic U4) diff --git a/stdlib/source/library/lux/target/jvm/method.lux b/stdlib/source/library/lux/target/jvm/method.lux index 638d4091f..b3a4a811c 100644 --- a/stdlib/source/library/lux/target/jvm/method.lux +++ b/stdlib/source/library/lux/target/jvm/method.lux @@ -1,30 +1,30 @@ (.module: [library - [lux (#- Type static public private) + [lux {"-" [Type static public private]} [abstract - [equivalence (#+ Equivalence)] - ["." monad (#+ do)]] + [equivalence {"+" [Equivalence]}] + ["." monad {"+" [do]}]] [control ["." try]] [data ["." product] - ["." format #_ - ["#" binary (#+ Writer) ("#\." monoid)]] + ["." format "_" + ["#" binary {"+" [Writer]} ("#\." monoid)]] [collection - ["." row (#+ Row)]]]]] - ["." // #_ - ["#." modifier (#+ Modifier modifiers:)] - ["#." index (#+ Index)] - ["#." attribute (#+ Attribute) + ["." row {"+" [Row]}]]]]] + ["." // "_" + ["#." modifier {"+" [Modifier modifiers:]}] + ["#." index {"+" [Index]}] + ["#." attribute {"+" [Attribute]} ["#/." code]] - ["#." constant (#+ UTF8) - ["#/." pool (#+ Pool Resource)]] - ["#." bytecode (#+ Bytecode) - ["#/." environment (#+ Environment)] + ["#." constant {"+" [UTF8]} + ["#/." pool {"+" [Pool Resource]}]] + ["#." bytecode {"+" [Bytecode]} + ["#/." environment {"+" [Environment]}] ["#/." instruction]] - ["#." type (#+ Type) + ["#." type {"+" [Type]} ["#/." category] - ["#." descriptor (#+ Descriptor)]]]) + ["#." descriptor {"+" [Descriptor]}]]]) (type: .public Method (Rec Method diff --git a/stdlib/source/library/lux/target/jvm/modifier.lux b/stdlib/source/library/lux/target/jvm/modifier.lux index b50127bc2..86a63b6fe 100644 --- a/stdlib/source/library/lux/target/jvm/modifier.lux +++ b/stdlib/source/library/lux/target/jvm/modifier.lux @@ -1,25 +1,25 @@ (.module: [library - [lux #* + [lux "*" [abstract - ["." equivalence (#+ Equivalence)] - ["." monoid (#+ Monoid)]] + ["." equivalence {"+" [Equivalence]}] + ["." monoid {"+" [Monoid]}]] [control ["." try] ["<>" parser ["<.>" code]]] [data [format - [".F" binary (#+ Writer)]]] - [macro (#+ with_identifiers) - [syntax (#+ syntax:)] + [".F" binary {"+" [Writer]}]]] + [macro {"+" [with_identifiers]} + [syntax {"+" [syntax:]}] ["." code]] [math - ["." number (#+ hex) + ["." number {"+" [hex]} ["." i64]]] [type abstract]]] - ["." // #_ + ["." // "_" [encoding ["#." unsigned]]]) diff --git a/stdlib/source/library/lux/target/jvm/modifier/inner.lux b/stdlib/source/library/lux/target/jvm/modifier/inner.lux index 6a7e9ae7c..a3777c380 100644 --- a/stdlib/source/library/lux/target/jvm/modifier/inner.lux +++ b/stdlib/source/library/lux/target/jvm/modifier/inner.lux @@ -1,9 +1,9 @@ (.module: [library - [lux (#- static) + [lux {"-" [static]} [type abstract]]] - [// (#+ modifiers:)]) + [// {"+" [modifiers:]}]) (abstract: .public Inner {} Any) diff --git a/stdlib/source/library/lux/target/jvm/reflection.lux b/stdlib/source/library/lux/target/jvm/reflection.lux index dfb2ff5d1..d6b899aab 100644 --- a/stdlib/source/library/lux/target/jvm/reflection.lux +++ b/stdlib/source/library/lux/target/jvm/reflection.lux @@ -1,18 +1,18 @@ (.module: [library - [lux (#- type) - ["." ffi (#+ import:)] + [lux {"-" [type]} + ["." ffi {"+" [import:]}] ["." type] [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control - ["." try (#+ Try)] - ["." exception (#+ exception:)] + ["." try {"+" [Try]}] + ["." exception {"+" [exception:]}] [parser ["<t>" text]]] [data ["." text ("#\." equivalence) - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." list ("#\." mix functor)] ["." array] @@ -20,12 +20,12 @@ [math [number ["n" nat]]]]] - ["." // #_ + ["." // "_" [encoding - ["#." name (#+ External)]] + ["#." name {"+" [External]}]] ["/" type - [category (#+ Void Value Return Method Primitive Object Class Array Parameter)] - ["#." lux (#+ Mapping)] + [category {"+" [Void Value Return Method Primitive Object Class Array Parameter]}] + ["#." lux {"+" [Mapping]}] ["#." descriptor] ["#." reflection] ["#." parser]]]) diff --git a/stdlib/source/library/lux/target/jvm/type.lux b/stdlib/source/library/lux/target/jvm/type.lux index 55c6bd921..eb3bece00 100644 --- a/stdlib/source/library/lux/target/jvm/type.lux +++ b/stdlib/source/library/lux/target/jvm/type.lux @@ -1,14 +1,14 @@ (.module: [library - [lux (#- Type int char) + [lux {"-" [Type int char]} [abstract - [equivalence (#+ Equivalence)] - [hash (#+ Hash)]] + [equivalence {"+" [Equivalence]}] + [hash {"+" [Hash]}]] [control ["." maybe]] [data ["." text - ["%" format (#+ Format)]] + ["%" format {"+" [Format]}]] [collection ["." list ("#\." functor)]]] [math @@ -16,14 +16,14 @@ ["n" nat]]] [type abstract]]] - ["." // #_ + ["." // "_" [encoding - ["#." name (#+ External)]]] - ["." / #_ - [category (#+ Void Value' Value Return' Return Method Primitive Object Class Array Var Parameter Declaration)] - ["#." signature (#+ Signature)] - ["#." descriptor (#+ Descriptor)] - ["#." reflection (#+ Reflection)]]) + ["#." name {"+" [External]}]]] + ["." / "_" + [category {"+" [Void Value' Value Return' Return Method Primitive Object Class Array Var Parameter Declaration]}] + ["#." signature {"+" [Signature]}] + ["#." descriptor {"+" [Descriptor]}] + ["#." reflection {"+" [Reflection]}]]) (abstract: .public (Type category) {} diff --git a/stdlib/source/library/lux/target/jvm/type/alias.lux b/stdlib/source/library/lux/target/jvm/type/alias.lux index 20f0b2921..cff9f623c 100644 --- a/stdlib/source/library/lux/target/jvm/type/alias.lux +++ b/stdlib/source/library/lux/target/jvm/type/alias.lux @@ -1,26 +1,26 @@ (.module: [library - [lux (#- Type int char type primitive) + [lux {"-" [Type int char type primitive]} [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control ["." maybe] ["." try] - ["." exception (#+ exception:)] + ["." exception {"+" [exception:]}] ["<>" parser - ["<.>" text (#+ Parser)]]] + ["<.>" text {"+" [Parser]}]]] [data ["." text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection - ["." dictionary (#+ Dictionary)]]]]] - ["." // (#+ Type) - [category (#+ Void Value Return Method Primitive Object Class Array Var Parameter)] + ["." dictionary {"+" [Dictionary]}]]]]] + ["." // {"+" [Type]} + [category {"+" [Void Value Return Method Primitive Object Class Array Var Parameter]}] ["#." descriptor] - ["#." signature (#+ Signature)] + ["#." signature {"+" [Signature]}] ["#." reflection] ["#." parser] - ["/#" // #_ + ["/#" // "_" [encoding ["#." name]]]]) diff --git a/stdlib/source/library/lux/target/jvm/type/box.lux b/stdlib/source/library/lux/target/jvm/type/box.lux index 44ab2a6ee..4029aaa28 100644 --- a/stdlib/source/library/lux/target/jvm/type/box.lux +++ b/stdlib/source/library/lux/target/jvm/type/box.lux @@ -1,9 +1,9 @@ (.module: [library - [lux (#- int char)]] + [lux {"-" [int char]}]] [/// [encoding - [name (#+ External)]]]) + [name {"+" [External]}]]]) (template [<name> <box>] [(def: .public <name> External <box>)] diff --git a/stdlib/source/library/lux/target/jvm/type/category.lux b/stdlib/source/library/lux/target/jvm/type/category.lux index c42a007f2..d4ddd056f 100644 --- a/stdlib/source/library/lux/target/jvm/type/category.lux +++ b/stdlib/source/library/lux/target/jvm/type/category.lux @@ -1,6 +1,6 @@ (.module: [library - [lux #* + [lux "*" [macro ["." template]] [type diff --git a/stdlib/source/library/lux/target/jvm/type/descriptor.lux b/stdlib/source/library/lux/target/jvm/type/descriptor.lux index 851213003..9d0cc7813 100644 --- a/stdlib/source/library/lux/target/jvm/type/descriptor.lux +++ b/stdlib/source/library/lux/target/jvm/type/descriptor.lux @@ -1,13 +1,13 @@ (.module: [library - [lux (#- int char) + [lux {"-" [int char]} [abstract - [equivalence (#+ Equivalence)]] + [equivalence {"+" [Equivalence]}]] [control ["." maybe]] [data ["." text ("#\." equivalence) - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." list ("#\." functor)]]] [math @@ -15,11 +15,11 @@ ["n" nat]]] [type abstract]]] - ["." // #_ - [category (#+ Void Value Return Method Primitive Object Class Array Var Parameter Declaration)] - ["/#" // #_ + ["." // "_" + [category {"+" [Void Value Return Method Primitive Object Class Array Var Parameter Declaration]}] + ["/#" // "_" [encoding - ["#." name (#+ Internal External)]]]]) + ["#." name {"+" [Internal External]}]]]]) (abstract: .public (Descriptor category) {} diff --git a/stdlib/source/library/lux/target/jvm/type/lux.lux b/stdlib/source/library/lux/target/jvm/type/lux.lux index 1e44c7a25..eacb25024 100644 --- a/stdlib/source/library/lux/target/jvm/type/lux.lux +++ b/stdlib/source/library/lux/target/jvm/type/lux.lux @@ -1,31 +1,31 @@ (.module: [library - [lux (#- int char type primitive) + [lux {"-" [int char type primitive]} [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control ["." try] - ["." exception (#+ exception:)] + ["." exception {"+" [exception:]}] ["<>" parser ("#\." monad) - ["<.>" text (#+ Parser)]]] + ["<.>" text {"+" [Parser]}]]] [data ["." product] ["." text ("#\." equivalence) - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." array] - ["." dictionary (#+ Dictionary)]]] + ["." dictionary {"+" [Dictionary]}]]] [type abstract - ["." check (#+ Check) ("#\." monad)]]]] + ["." check {"+" [Check]} ("#\." monad)]]]] ["." // - [category (#+ Void Value Return Method Primitive Object Class Array Var Parameter)] + [category {"+" [Void Value Return Method Primitive Object Class Array Var Parameter]}] ["#." descriptor] ["#." signature] ["#." reflection] ["#." parser] ["#." box] - ["/#" // #_ + ["/#" // "_" [encoding ["#." name]]]]) diff --git a/stdlib/source/library/lux/target/jvm/type/parser.lux b/stdlib/source/library/lux/target/jvm/type/parser.lux index cf0064195..3d68ddb85 100644 --- a/stdlib/source/library/lux/target/jvm/type/parser.lux +++ b/stdlib/source/library/lux/target/jvm/type/parser.lux @@ -1,26 +1,26 @@ (.module: [library - [lux (#- Type int char primitive) + [lux {"-" [Type int char primitive]} [abstract - [monad (#+ do)]] + [monad {"+" [do]}]] [control ["." try] ["." function] ["<>" parser ("#\." monad) - ["<.>" text (#+ Parser)]]] + ["<.>" text {"+" [Parser]}]]] [data ["." product] [text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." list]]]]] - ["." // (#+ Type) - [category (#+ Void Value Return Method Primitive Object Class Array Var Parameter Declaration)] + ["." // {"+" [Type]} + [category {"+" [Void Value Return Method Primitive Object Class Array Var Parameter Declaration]}] ["#." signature] ["#." descriptor] - ["." // #_ + ["." // "_" [encoding - ["#." name (#+ External)]]]]) + ["#." name {"+" [External]}]]]]) (template [<category> <name> <signature> <type>] [(def: .public <name> diff --git a/stdlib/source/library/lux/target/jvm/type/reflection.lux b/stdlib/source/library/lux/target/jvm/type/reflection.lux index 936e7347e..576fb0abc 100644 --- a/stdlib/source/library/lux/target/jvm/type/reflection.lux +++ b/stdlib/source/library/lux/target/jvm/type/reflection.lux @@ -1,19 +1,19 @@ (.module: [library - [lux (#- int char) + [lux {"-" [int char]} [abstract - [equivalence (#+ Equivalence)]] + [equivalence {"+" [Equivalence]}]] [data ["." text ("#\." equivalence) - ["%" format (#+ format)]]] + ["%" format {"+" [format]}]]] [type abstract]]] - ["." // #_ - [category (#+ Void Value Return Method Primitive Object Class Array Var Parameter Declaration)] + ["." // "_" + [category {"+" [Void Value Return Method Primitive Object Class Array Var Parameter Declaration]}] ["#." descriptor] [// [encoding - ["#." name (#+ External)]]]]) + ["#." name {"+" [External]}]]]]) (abstract: .public (Reflection category) {} diff --git a/stdlib/source/library/lux/target/jvm/type/signature.lux b/stdlib/source/library/lux/target/jvm/type/signature.lux index 957926021..667457d61 100644 --- a/stdlib/source/library/lux/target/jvm/type/signature.lux +++ b/stdlib/source/library/lux/target/jvm/type/signature.lux @@ -1,22 +1,22 @@ (.module: [library - [lux (#- int char) + [lux {"-" [int char]} [abstract - [equivalence (#+ Equivalence)] - [hash (#+ Hash)]] + [equivalence {"+" [Equivalence]}] + [hash {"+" [Hash]}]] [data ["." text ("#\." hash) - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." list ("#\." functor)]]] [type abstract]]] - ["." // #_ - [category (#+ Void Value Return Method Primitive Object Class Array Var Parameter Declaration)] + ["." // "_" + [category {"+" [Void Value Return Method Primitive Object Class Array Var Parameter Declaration]}] ["#." descriptor] - ["/#" // #_ + ["/#" // "_" [encoding - ["#." name (#+ External)]]]]) + ["#." name {"+" [External]}]]]]) (abstract: .public (Signature category) {} diff --git a/stdlib/source/library/lux/target/jvm/version.lux b/stdlib/source/library/lux/target/jvm/version.lux index 7fbf55c35..79e839977 100644 --- a/stdlib/source/library/lux/target/jvm/version.lux +++ b/stdlib/source/library/lux/target/jvm/version.lux @@ -1,11 +1,11 @@ (.module: [library - [lux #* + [lux "*" [control ["." try]]]] - ["." // #_ + ["." // "_" [encoding - ["#." unsigned (#+ U2)]]]) + ["#." unsigned {"+" [U2]}]]]) (type: .public Version U2) (type: .public Minor Version) diff --git a/stdlib/source/library/lux/target/lua.lux b/stdlib/source/library/lux/target/lua.lux index faac1b184..540b8e7a0 100644 --- a/stdlib/source/library/lux/target/lua.lux +++ b/stdlib/source/library/lux/target/lua.lux @@ -1,22 +1,22 @@ (.module: [library - [lux (#- Location Code Label int if cond function or and not let ^ local) + [lux {"-" [Location Code Label int if cond function or and not let ^ local]} ["@" target] [abstract - [equivalence (#+ Equivalence)] - [hash (#+ Hash)] + [equivalence {"+" [Equivalence]}] + [hash {"+" [Hash]}] ["." enum]] [control - [pipe (#+ case> cond> new>)] + [pipe {"+" [case> cond> new>]}] [parser ["<.>" code]]] [data ["." text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." list ("#\." functor mix)]]] [macro - [syntax (#+ syntax:)] + [syntax {"+" [syntax:]}] ["." template] ["." code]] [math diff --git a/stdlib/source/library/lux/target/php.lux b/stdlib/source/library/lux/target/php.lux index 57fca8e65..5bc937489 100644 --- a/stdlib/source/library/lux/target/php.lux +++ b/stdlib/source/library/lux/target/php.lux @@ -1,22 +1,22 @@ (.module: [library - [lux (#- Location Code Global Label static int if cond or and not comment for try global) + [lux {"-" [Location Code Global Label static int if cond or and not comment for try global]} ["@" target] [abstract - [equivalence (#+ Equivalence)] - [hash (#+ Hash)] + [equivalence {"+" [Equivalence]}] + [hash {"+" [Hash]}] ["." enum]] [control - [pipe (#+ case> cond> new>)] + [pipe {"+" [case> cond> new>]}] [parser ["<.>" code]]] [data ["." text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." list ("#\." functor mix)]]] [macro - [syntax (#+ syntax:)] + [syntax {"+" [syntax:]}] ["." template] ["." code]] [math diff --git a/stdlib/source/library/lux/target/python.lux b/stdlib/source/library/lux/target/python.lux index f0d4e23f2..21aa9291f 100644 --- a/stdlib/source/library/lux/target/python.lux +++ b/stdlib/source/library/lux/target/python.lux @@ -1,23 +1,23 @@ (.module: [library - [lux (#- Location Code Label not or and list if cond int comment exec try) + [lux {"-" [Location Code Label not or and list if cond int comment exec try]} ["@" target] ["." ffi] [abstract - [equivalence (#+ Equivalence)] - [hash (#+ Hash)] + [equivalence {"+" [Equivalence]}] + [hash {"+" [Hash]}] ["." enum]] [control - [pipe (#+ new> case> cond>)] + [pipe {"+" [new> case> cond>]}] [parser ["<.>" code]]] [data ["." text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." list ("#\." functor mix)]]] [macro - [syntax (#+ syntax:)] + [syntax {"+" [syntax:]}] ["." template] ["." code]] [math diff --git a/stdlib/source/library/lux/target/r.lux b/stdlib/source/library/lux/target/r.lux index 5b7b9bb47..e6b4bb611 100644 --- a/stdlib/source/library/lux/target/r.lux +++ b/stdlib/source/library/lux/target/r.lux @@ -1,19 +1,19 @@ (.module: [library - [lux (#- Code or and list if function cond not int) + [lux {"-" [Code or and list if function cond not int]} [control - [pipe (#+ case> cond> new>)] + [pipe {"+" [case> cond> new>]}] ["." function] ["." maybe ("#\." functor)] [parser ["<.>" code]]] [data ["." text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." list ("#\." functor mix)]]] [macro - [syntax (#+ syntax:)] + [syntax {"+" [syntax:]}] ["." template] ["." code]] [math diff --git a/stdlib/source/library/lux/target/ruby.lux b/stdlib/source/library/lux/target/ruby.lux index 501c4d1e7..22ca238d8 100644 --- a/stdlib/source/library/lux/target/ruby.lux +++ b/stdlib/source/library/lux/target/ruby.lux @@ -1,22 +1,22 @@ (.module: [library - [lux (#- Location Code static int if cond function or and not comment local global) + [lux {"-" [Location Code static int if cond function or and not comment local global]} ["@" target] [abstract - [equivalence (#+ Equivalence)] - [hash (#+ Hash)] + [equivalence {"+" [Equivalence]}] + [hash {"+" [Hash]}] ["." enum]] [control - [pipe (#+ case> cond> new>)] + [pipe {"+" [case> cond> new>]}] [parser ["<.>" code]]] [data ["." text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." list ("#\." functor mix)]]] [macro - [syntax (#+ syntax:)] + [syntax {"+" [syntax:]}] ["." template] ["." code]] [math diff --git a/stdlib/source/library/lux/target/scheme.lux b/stdlib/source/library/lux/target/scheme.lux index 5bce310fc..fcf575658 100644 --- a/stdlib/source/library/lux/target/scheme.lux +++ b/stdlib/source/library/lux/target/scheme.lux @@ -1,15 +1,15 @@ (.module: [library - [lux (#- Code int or and if cond let) + [lux {"-" [Code int or and if cond let]} ["@" target] [abstract - [equivalence (#+ Equivalence)] - [hash (#+ Hash)]] + [equivalence {"+" [Equivalence]}] + [hash {"+" [Hash]}]] [control - [pipe (#+ new> cond> case>)]] + [pipe {"+" [new> cond> case>]}]] [data ["." text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." list ("#\." functor monoid)]]] [macro diff --git a/stdlib/source/library/lux/test.lux b/stdlib/source/library/lux/test.lux index feab6c2f6..4467d12c6 100644 --- a/stdlib/source/library/lux/test.lux +++ b/stdlib/source/library/lux/test.lux @@ -1,41 +1,41 @@ (.module: [library - [lux (#- and for) + [lux {"-" [and for]} ["." meta] ["." debug] [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control - [pipe (#+ case>)] + [pipe {"+" [case>]}] ["." maybe] ["." try] - ["." exception (#+ exception:)] + ["." exception {"+" [exception:]}] ["." io] [concurrency - ["." atom (#+ Atom)] - ["." async (#+ Async) ("#\." monad)]] + ["." atom {"+" [Atom]}] + ["." async {"+" [Async]} ("#\." monad)]] ["<>" parser ["<.>" code]]] [data ["." product] ["." name] ["." text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." list ("#\." functor mix)] - ["." set (#+ Set)] - ["." dictionary #_ - ["#" ordered (#+ Dictionary)]]]] + ["." set {"+" [Set]}] + ["." dictionary "_" + ["#" ordered {"+" [Dictionary]}]]]] [time ["." instant] - ["." duration (#+ Duration)]] + ["." duration {"+" [Duration]}]] [math - ["." random (#+ Random) ("#\." monad)] - [number (#+ hex) + ["." random {"+" [Random]} ("#\." monad)] + [number {"+" [hex]} ["n" nat] ["f" frac]]] [macro - [syntax (#+ syntax:)] + [syntax {"+" [syntax:]}] ["." code]] [world ["." program]]]]) diff --git a/stdlib/source/library/lux/time.lux b/stdlib/source/library/lux/time.lux index 87556b1a8..b179416ea 100644 --- a/stdlib/source/library/lux/time.lux +++ b/stdlib/source/library/lux/time.lux @@ -1,18 +1,18 @@ (.module: [library - [lux #* + [lux "*" [abstract - [equivalence (#+ Equivalence)] - [order (#+ Order)] - [enum (#+ Enum)] - [codec (#+ Codec)] - [monad (#+ Monad do)]] + [equivalence {"+" [Equivalence]}] + [order {"+" [Order]}] + [enum {"+" [Enum]}] + [codec {"+" [Codec]}] + [monad {"+" [Monad do]}]] [control - [pipe (#+ case>)] - ["." try (#+ Try)] - ["." exception (#+ exception:)] + [pipe {"+" [case>]}] + ["." try {"+" [Try]}] + ["." exception {"+" [exception:]}] ["<>" parser - ["<.>" text (#+ Parser)]]] + ["<.>" text {"+" [Parser]}]]] [data ["." text ("#\." monoid)]] [math @@ -21,7 +21,7 @@ [type abstract]]] [/ - ["." duration (#+ Duration)]]) + ["." duration {"+" [Duration]}]]) (template [<name> <singular> <plural>] [(def: .public <name> diff --git a/stdlib/source/library/lux/time/date.lux b/stdlib/source/library/lux/time/date.lux index d606449c5..be4742376 100644 --- a/stdlib/source/library/lux/time/date.lux +++ b/stdlib/source/library/lux/time/date.lux @@ -1,32 +1,32 @@ (.module: [library - [lux #* + [lux "*" [abstract - [equivalence (#+ Equivalence)] - [order (#+ Order)] - [enum (#+ Enum)] - [codec (#+ Codec)] - [monad (#+ do)]] + [equivalence {"+" [Equivalence]}] + [order {"+" [Order]}] + [enum {"+" [Enum]}] + [codec {"+" [Codec]}] + [monad {"+" [do]}]] [control ["." maybe] - ["." try (#+ Try)] - ["." exception (#+ exception:)] + ["." try {"+" [Try]}] + ["." exception {"+" [exception:]}] ["<>" parser - ["<.>" text (#+ Parser)]]] + ["<.>" text {"+" [Parser]}]]] [data ["." text ("#\." monoid)] [collection ["." list ("#\." mix)] - ["." dictionary (#+ Dictionary)]]] + ["." dictionary {"+" [Dictionary]}]]] [math [number ["n" nat ("#\." decimal)] ["i" int]]] [type abstract]]] - ["." // #_ - ["#." year (#+ Year)] - ["#." month (#+ Month)]]) + ["." // "_" + ["#." year {"+" [Year]}] + ["#." month {"+" [Month]}]]) (def: month_by_number (Dictionary Nat Month) diff --git a/stdlib/source/library/lux/time/day.lux b/stdlib/source/library/lux/time/day.lux index 3286062ea..ebc24879c 100644 --- a/stdlib/source/library/lux/time/day.lux +++ b/stdlib/source/library/lux/time/day.lux @@ -1,15 +1,15 @@ (.module: [library - [lux (#- nat) + [lux {"-" [nat]} [abstract - [equivalence (#+ Equivalence)] - [hash (#+ Hash)] - [order (#+ Order)] - [enum (#+ Enum)] - [codec (#+ Codec)]] + [equivalence {"+" [Equivalence]}] + [hash {"+" [Hash]}] + [order {"+" [Order]}] + [enum {"+" [Enum]}] + [codec {"+" [Codec]}]] [control - ["." try (#+ Try)] - ["." exception (#+ exception:)]] + ["." try {"+" [Try]}] + ["." exception {"+" [exception:]}]] [data ["." text]] [macro diff --git a/stdlib/source/library/lux/time/duration.lux b/stdlib/source/library/lux/time/duration.lux index 7b2c8e289..3e8063563 100644 --- a/stdlib/source/library/lux/time/duration.lux +++ b/stdlib/source/library/lux/time/duration.lux @@ -1,17 +1,17 @@ (.module: [library - [lux #* + [lux "*" [abstract - [equivalence (#+ Equivalence)] - [order (#+ Order)] - [enum (#+ Enum)] - [codec (#+ Codec)] - [monoid (#+ Monoid)] - [monad (#+ do)]] + [equivalence {"+" [Equivalence]}] + [order {"+" [Order]}] + [enum {"+" [Enum]}] + [codec {"+" [Codec]}] + [monoid {"+" [Monoid]}] + [monad {"+" [do]}]] [control ["." try] ["<>" parser - ["<.>" text (#+ Parser)]]] + ["<.>" text {"+" [Parser]}]]] [data ["." text ("#\." monoid)]] [math @@ -20,7 +20,7 @@ ["." nat ("#\." decimal)]]] [type abstract]]] - ["." // #_ + ["." // "_" ["#." year]]) (abstract: .public Duration diff --git a/stdlib/source/library/lux/time/instant.lux b/stdlib/source/library/lux/time/instant.lux index d8a1d0bff..9ef644274 100644 --- a/stdlib/source/library/lux/time/instant.lux +++ b/stdlib/source/library/lux/time/instant.lux @@ -1,20 +1,20 @@ (.module: [library - [lux #* + [lux "*" ["@" target] [abstract - [equivalence (#+ Equivalence)] - [order (#+ Order)] - [enum (#+ Enum)] - [codec (#+ Codec)] - [monad (#+ Monad do)]] + [equivalence {"+" [Equivalence]}] + [order {"+" [Order]}] + [enum {"+" [Enum]}] + [codec {"+" [Codec]}] + [monad {"+" [Monad do]}]] [control - [io (#+ IO io)] + [io {"+" [IO io]}] ["." maybe] ["." try] - ["." exception (#+ exception:)] + ["." exception {"+" [exception:]}] ["<>" parser - ["<.>" text (#+ Parser)]]] + ["<.>" text {"+" [Parser]}]]] [data ["." text ("#\." monoid)] [collection @@ -25,12 +25,12 @@ ["f" frac]]] [type abstract]]] - ["." // (#+ Time) - ["." duration (#+ Duration)] - ["." year (#+ Year)] - ["." month (#+ Month)] - ["." day (#+ Day)] - ["." date (#+ Date)]]) + ["." // {"+" [Time]} + ["." duration {"+" [Duration]}] + ["." year {"+" [Year]}] + ["." month {"+" [Month]}] + ["." day {"+" [Day]}] + ["." date {"+" [Date]}]]) (abstract: .public Instant {} diff --git a/stdlib/source/library/lux/time/month.lux b/stdlib/source/library/lux/time/month.lux index c7e4af9e9..772b58c0b 100644 --- a/stdlib/source/library/lux/time/month.lux +++ b/stdlib/source/library/lux/time/month.lux @@ -1,15 +1,15 @@ (.module: [library - [lux #* + [lux "*" [abstract - [equivalence (#+ Equivalence)] - [hash (#+ Hash)] - [order (#+ Order)] - [enum (#+ Enum)] - [codec (#+ Codec)]] + [equivalence {"+" [Equivalence]}] + [hash {"+" [Hash]}] + [order {"+" [Order]}] + [enum {"+" [Enum]}] + [codec {"+" [Codec]}]] [control - ["." try (#+ Try)] - ["." exception (#+ exception:)]] + ["." try {"+" [Try]}] + ["." exception {"+" [exception:]}]] [data ["." text]] [macro diff --git a/stdlib/source/library/lux/time/year.lux b/stdlib/source/library/lux/time/year.lux index e47b0d465..cf1aa6945 100644 --- a/stdlib/source/library/lux/time/year.lux +++ b/stdlib/source/library/lux/time/year.lux @@ -1,16 +1,16 @@ (.module: [library - [lux #* + [lux "*" [abstract - [monad (#+ do)] - [codec (#+ Codec)] - [equivalence (#+ Equivalence)] - [order (#+ Order)]] + [monad {"+" [do]}] + [codec {"+" [Codec]}] + [equivalence {"+" [Equivalence]}] + [order {"+" [Order]}]] [control - ["." try (#+ Try)] - ["." exception (#+ exception:)] + ["." try {"+" [Try]}] + ["." exception {"+" [exception:]}] ["<>" parser - ["<.>" text (#+ Parser)]]] + ["<.>" text {"+" [Parser]}]]] [data ["." text ("#\." monoid)]] [math diff --git a/stdlib/source/library/lux/tool/compiler.lux b/stdlib/source/library/lux/tool/compiler.lux index 5bb3c0fd2..5f9f7e4dd 100644 --- a/stdlib/source/library/lux/tool/compiler.lux +++ b/stdlib/source/library/lux/tool/compiler.lux @@ -1,22 +1,22 @@ (.module: [library - [lux (#- Module Code) + [lux {"-" [Module Code]} [control - ["." try (#+ Try)] - ["." exception (#+ exception:)]] + ["." try {"+" [Try]}] + ["." exception {"+" [exception:]}]] [data - [binary (#+ Binary)] + [binary {"+" [Binary]}] ["." text] [collection - ["." row (#+ Row)]]] + ["." row {"+" [Row]}]]] [world - ["." file (#+ Path)]]]] + ["." file {"+" [Path]}]]]] [/ [meta - ["." archive (#+ Output Archive) - [key (#+ Key)] - [descriptor (#+ Descriptor Module)] - [document (#+ Document)]]]]) + ["." archive {"+" [Output Archive]} + [key {"+" [Key]}] + [descriptor {"+" [Descriptor Module]}] + [document {"+" [Document]}]]]]) (type: .public Code Text) diff --git a/stdlib/source/library/lux/tool/compiler/arity.lux b/stdlib/source/library/lux/tool/compiler/arity.lux index 5d20220c3..cf985c1fe 100644 --- a/stdlib/source/library/lux/tool/compiler/arity.lux +++ b/stdlib/source/library/lux/tool/compiler/arity.lux @@ -1,6 +1,6 @@ (.module: [library - [lux #* + [lux "*" [math [number ["n" nat]]]]]) diff --git a/stdlib/source/library/lux/tool/compiler/default/init.lux b/stdlib/source/library/lux/tool/compiler/default/init.lux index 7748186b2..d704b8c44 100644 --- a/stdlib/source/library/lux/tool/compiler/default/init.lux +++ b/stdlib/source/library/lux/tool/compiler/default/init.lux @@ -1,17 +1,17 @@ (.module: [library - [lux (#- Module) - ["@" target (#+ Target)] + [lux {"-" [Module]} + ["@" target {"+" [Target]}] [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control - ["." try (#+ Try)] - ["." exception (#+ exception:)]] + ["." try {"+" [Try]}] + ["." exception {"+" [exception:]}]] [data - [binary (#+ Binary)] + [binary {"+" [Binary]}] ["." product] ["." text ("#\." hash) - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." list ("#\." functor)] ["." dictionary] @@ -20,33 +20,33 @@ ["." meta] [world ["." file]]]] - ["." // #_ - ["/#" // (#+ Instancer) + ["." // "_" + ["/#" // {"+" [Instancer]} ["#." phase] [language [lux - [program (#+ Program)] + [program {"+" [Program]}] ["#." version] - ["#." syntax (#+ Aliases)] + ["#." syntax {"+" [Aliases]}] ["#." synthesis] - ["#." directive (#+ Requirements)] + ["#." directive {"+" [Requirements]}] ["#." generation] ["#." analysis - [macro (#+ Expander)] + [macro {"+" [Expander]}] ["#/." evaluation]] [phase [".P" synthesis] [".P" directive] [".P" analysis ["." module]] - ["." extension (#+ Extender) + ["." extension {"+" [Extender]} [".E" analysis] [".E" synthesis] [directive [".D" lux]]]]]] [meta - ["." archive (#+ Archive) - ["." descriptor (#+ Module)] + ["." archive {"+" [Archive]} + ["." descriptor {"+" [Module]}] ["." artifact] ["." document]]]] ]) diff --git a/stdlib/source/library/lux/tool/compiler/default/platform.lux b/stdlib/source/library/lux/tool/compiler/default/platform.lux index 0452ef5b6..8ee88204a 100644 --- a/stdlib/source/library/lux/tool/compiler/default/platform.lux +++ b/stdlib/source/library/lux/tool/compiler/default/platform.lux @@ -1,66 +1,66 @@ (.module: [library - [lux (#- Module) - [type (#+ :sharing)] + [lux {"-" [Module]} + [type {"+" [:sharing]}] ["@" target] ["." debug] [abstract - ["." monad (#+ Monad do)]] + ["." monad {"+" [Monad do]}]] [control ["." function] ["." maybe] - ["." try (#+ Try) ("#\." monad)] - ["." exception (#+ exception:)] + ["." try {"+" [Try]} ("#\." monad)] + ["." exception {"+" [exception:]}] [concurrency - ["." async (#+ Async Resolver) ("#\." monad)] - ["." stm (#+ Var STM)]]] + ["." async {"+" [Async Resolver]} ("#\." monad)] + ["." stm {"+" [Var STM]}]]] [data - ["." binary (#+ Binary)] + ["." binary {"+" [Binary]}] ["." bit] ["." product] ["." text ("#\." equivalence) - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection - ["." dictionary (#+ Dictionary)] - ["." row (#+ Row) ("#\." mix)] - ["." set (#+ Set)] + ["." dictionary {"+" [Dictionary]}] + ["." row {"+" [Row]} ("#\." mix)] + ["." set {"+" [Set]}] ["." list ("#\." monoid functor mix)]] [format - ["_" binary (#+ Writer)]]] + ["_" binary {"+" [Writer]}]]] [world - ["." file (#+ Path)]]]] - ["." // #_ + ["." file {"+" [Path]}]]]] + ["." // "_" ["#." init] ["/#" // - ["#." phase (#+ Phase)] + ["#." phase {"+" [Phase]}] [language [lux - [program (#+ Program)] + [program {"+" [Program]}] ["$" /] ["#." version] ["." syntax] ["#." analysis - [macro (#+ Expander)]] + [macro {"+" [Expander]}]] ["#." synthesis] - ["#." generation (#+ Buffer)] + ["#." generation {"+" [Buffer]}] ["#." directive] [phase - ["." extension (#+ Extender)] + ["." extension {"+" [Extender]}] [analysis ["." module]]]]] [meta - ["." archive (#+ Output Archive) - ["." artifact (#+ Registry)] - ["." descriptor (#+ Descriptor Module)] - ["." document (#+ Document)]] - [io (#+ Context) + ["." archive {"+" [Output Archive]} + ["." artifact {"+" [Registry]}] + ["." descriptor {"+" [Descriptor Module]}] + ["." document {"+" [Document]}]] + [io {"+" [Context]} ["." context] ["ioW" archive]]]]] [program [compositor - [cli (#+ Compilation Library)] - [import (#+ Import)] - ["." static (#+ Static)]]]) + [cli {"+" [Compilation Library]}] + [import {"+" [Import]}] + ["." static {"+" [Static]}]]]) (with_expansions [<type_vars> (as_is anchor expression directive) <Operation> (as_is ///generation.Operation <type_vars>)] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux.lux b/stdlib/source/library/lux/tool/compiler/language/lux.lux index 5ad1e959e..30465ca7d 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux.lux @@ -1,13 +1,13 @@ (.module: [library - [lux #* + [lux "*" [control ["<>" parser - ["<b>" binary (#+ Parser)]]] + ["<b>" binary {"+" [Parser]}]]] [data [format - ["_" binary (#+ Writer)]]]]] - ["." / #_ + ["_" binary {"+" [Writer]}]]]]] + ["." / "_" ["#." version] [phase [analysis @@ -16,7 +16,7 @@ [meta [archive ["." signature] - ["." key (#+ Key)]]]]]) + ["." key {"+" [Key]}]]]]]) ... TODO: Remove #module_hash, #imports & #module_state ASAP. ... TODO: Not just from this parser, but from the lux.Module type. diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux b/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux index bdc195879..772b0b04d 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux @@ -1,20 +1,20 @@ (.module: [library - [lux (#- Tuple Variant nat int rev) + [lux {"-" [Tuple Variant nat int rev]} [abstract - [equivalence (#+ Equivalence)] - [hash (#+ Hash)] - [monad (#+ do)]] + [equivalence {"+" [Equivalence]}] + [hash {"+" [Hash]}] + [monad {"+" [do]}]] [control ["." function] ["." maybe] ["." try] - ["." exception (#+ Exception)]] + ["." exception {"+" [Exception]}]] [data ["." product] ["." bit ("#\." equivalence)] ["." text ("#\." equivalence) - ["%" format (#+ Format format)]] + ["%" format {"+" [Format format]}]] [collection ["." list ("#\." functor mix)]]] [math @@ -27,13 +27,13 @@ ["." location]]]] [// [phase - ["." extension (#+ Extension)]] + ["." extension {"+" [Extension]}]] [/// - [arity (#+ Arity)] - [version (#+ Version)] + [arity {"+" [Arity]}] + [version {"+" [Version]}] ["." phase] - ["." reference (#+ Reference) - ["." variable (#+ Register Variable)]]]]) + ["." reference {"+" [Reference]} + ["." variable {"+" [Register Variable]}]]]]) (type: .public Primitive (.Variant diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/evaluation.lux b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/evaluation.lux index 723f61d29..a770d7798 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/evaluation.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/evaluation.lux @@ -1,16 +1,16 @@ (.module: [library - [lux (#- Module) + [lux {"-" [Module]} ["." meta] [abstract - [monad (#+ do)]] + [monad {"+" [do]}]] [control ["." try]] [math [number ["n" nat]]]]] - [// (#+ Operation) - [macro (#+ Expander)] + [// {"+" [Operation]} + [macro {"+" [Expander]}] [// [phase [".P" extension] @@ -19,12 +19,12 @@ ["." type]] [// ["." synthesis] - ["." generation (#+ Context)] + ["." generation {"+" [Context]}] [/// ["." phase] [meta - [archive (#+ Archive) - [descriptor (#+ Module)]]]]]]]]) + [archive {"+" [Archive]} + [descriptor {"+" [Module]}]]]]]]]]) (type: .public Eval (-> Archive Type Code (Operation Any))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/macro.lux b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/macro.lux index 800d3091e..f6b4d0c3b 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/macro.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/macro.lux @@ -1,14 +1,14 @@ (.module: [library - [lux #* + [lux "*" [abstract - [monad (#+ do)]] + [monad {"+" [do]}]] [control - ["." try (#+ Try)] - ["." exception (#+ exception:)]] + ["." try {"+" [Try]}] + ["." exception {"+" [exception:]}]] [data ["." text - ["%" format (#+ format)]]] + ["%" format {"+" [format]}]]] ["." meta]]] [///// ["." phase]]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/directive.lux b/stdlib/source/library/lux/tool/compiler/language/lux/directive.lux index ea9d244af..e2c1899de 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/directive.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/directive.lux @@ -1,8 +1,8 @@ (.module: [library - [lux (#- Module) + [lux {"-" [Module]} [abstract - [monad (#+ do)]] + [monad {"+" [do]}]] [control ["." try]] [data @@ -18,7 +18,7 @@ ["." phase] [meta [archive - [descriptor (#+ Module)]]]]]) + [descriptor {"+" [Module]}]]]]]) (type: .public (Component state phase) (Record diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/generation.lux b/stdlib/source/library/lux/tool/compiler/language/lux/generation.lux index 91b758c78..22e3708ec 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/generation.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/generation.lux @@ -1,33 +1,33 @@ (.module: [library - [lux (#- Module) + [lux {"-" [Module]} [abstract - [monad (#+ do)]] + [monad {"+" [do]}]] [control - ["." try (#+ Try)] - ["." exception (#+ exception:)] + ["." try {"+" [Try]}] + ["." exception {"+" [exception:]}] ["." function]] [data - [binary (#+ Binary)] + [binary {"+" [Binary]}] ["." product] ["." name] ["." text ("#\." equivalence) - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection - ["." row (#+ Row)] + ["." row {"+" [Row]}] ["." list ("#\." functor)]]] [math [number ["n" nat]]]]] [// - [synthesis (#+ Synthesis)] + [synthesis {"+" [Synthesis]}] [phase ["." extension]] [/// ["." phase] [meta - ["." archive (#+ Archive) - ["." descriptor (#+ Module)] + ["." archive {"+" [Archive]} + ["." descriptor {"+" [Module]}] ["." artifact]]]]]) (type: .public Context diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis.lux index 9f5e6d12a..ff4db62e6 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis.lux @@ -1,32 +1,32 @@ (.module: [library - [lux #* + [lux "*" [abstract - [monad (#+ do)]] + [monad {"+" [do]}]] [control - ["." exception (#+ exception:)]] + ["." exception {"+" [exception:]}]] [data [text - ["%" format (#+ format)]]] + ["%" format {"+" [format]}]]] ["." meta ["." location]]]] - ["." / #_ + ["." / "_" ["#." type] ["#." primitive] ["#." structure] ["#." reference] ["#." case] ["#." function] - ["/#" // #_ + ["/#" // "_" ["#." extension] - ["/#" // #_ - ["/" analysis (#+ Analysis Operation Phase) - ["#." macro (#+ Expander)]] + ["/#" // "_" + ["/" analysis {"+" [Analysis Operation Phase]} + ["#." macro {"+" [Expander]}]] [/// ["//" phase] ["." reference] [meta - [archive (#+ Archive)]]]]]]) + [archive {"+" [Archive]}]]]]]]) (exception: .public (unrecognized_syntax {code Code}) (exception.report ["Code" (%.code code)])) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux index 9777b1a31..0d029264e 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux @@ -1,17 +1,17 @@ (.module: [library - [lux (#- case) + [lux {"-" [case]} ["." meta] [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control ["." maybe] ["." try] - ["." exception (#+ exception:)]] + ["." exception {"+" [exception:]}]] [data ["." product] [text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." list ("#\." mix monoid functor)]]] [math @@ -21,16 +21,16 @@ ["." code]] ["." type ["." check]]]] - ["." / #_ - ["#." coverage (#+ Coverage)] - ["/#" // #_ + ["." / "_" + ["#." coverage {"+" [Coverage]}] + ["/#" // "_" ["#." scope] ["#." type] ["#." structure] - ["/#" // #_ + ["/#" // "_" ["#." extension] [// - ["/" analysis (#+ Pattern Analysis Operation Phase)] + ["/" analysis {"+" [Pattern Analysis Operation Phase]}] [/// ["#" phase]]]]]]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case/coverage.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case/coverage.lux index d9b47d757..e1ac7bdf4 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case/coverage.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case/coverage.lux @@ -1,26 +1,26 @@ (.module: [library - [lux (#- Variant) + [lux {"-" [Variant]} [abstract equivalence - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control ["." maybe] - ["." try (#+ Try) ("#\." monad)] - ["." exception (#+ exception:)]] + ["." try {"+" [Try]} ("#\." monad)] + ["." exception {"+" [exception:]}]] [data ["." bit ("#\." equivalence)] ["." text - ["%" format (#+ Format format)]] + ["%" format {"+" [Format format]}]] [collection ["." list ("#\." functor mix)] - ["." dictionary (#+ Dictionary)]]] + ["." dictionary {"+" [Dictionary]}]]] [math [number ["n" nat]]]]] - ["." //// #_ + ["." //// "_" [// - ["/" analysis (#+ Pattern Variant Operation)] + ["/" analysis {"+" [Pattern Variant Operation]}] [/// ["#" phase ("#\." monad)]]]]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/function.lux index a499b5df4..c1341eaf7 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/function.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/function.lux @@ -1,31 +1,31 @@ (.module: [library - [lux (#- function) + [lux {"-" [function]} [abstract monad] [control ["." maybe] - ["ex" exception (#+ exception:)]] + ["ex" exception {"+" [exception:]}]] [data ["." text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." list ("#\." monoid monad)]]] ["." type ["." check]] ["." meta]]] - ["." // #_ + ["." // "_" ["#." scope] ["#." type] ["#." inference] - ["/#" // #_ + ["/#" // "_" ["#." extension] [// - ["/" analysis (#+ Analysis Operation Phase)] + ["/" analysis {"+" [Analysis Operation Phase]}] [/// ["#" phase] - [reference (#+) - [variable (#+)]]]]]]) + [reference {"+" []} + [variable {"+" []}]]]]]]) (exception: .public (cannot_analyse {expected Type} {function Text} {argument Text} {body Code}) (ex.report ["Type" (%.type expected)] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/inference.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/inference.lux index 366a92cad..4972f71dc 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/inference.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/inference.lux @@ -1,14 +1,14 @@ (.module: [library - [lux #* + [lux "*" [abstract - [monad (#+ do)]] + [monad {"+" [do]}]] [control ["." maybe] - ["." exception (#+ exception:)]] + ["." exception {"+" [exception:]}]] [data ["." text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." list ("#\." functor monoid)]]] [math @@ -17,16 +17,16 @@ ["." type ["." check]] ["." meta]]] - ["." // #_ + ["." // "_" ["#." type] - ["/#" // #_ + ["/#" // "_" ["#." extension] [// - ["/" analysis (#+ Tag Analysis Operation Phase)] + ["/" analysis {"+" [Tag Analysis Operation Phase]}] [/// ["#" phase ("#\." monad)] [meta - [archive (#+ Archive)]]]]]]) + [archive {"+" [Archive]}]]]]]]) (exception: .public (variant_tag_out_of_bounds {size Nat} {tag Tag} {type Type}) (exception.report diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/module.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/module.lux index 0499c2d8a..3304e0331 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/module.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/module.lux @@ -1,24 +1,24 @@ (.module: [library - [lux #* + [lux "*" [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control pipe ["." try] - ["." exception (#+ exception:)]] + ["." exception {"+" [exception:]}]] [data ["." text ("#\." equivalence) - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." list ("#\." mix functor)] [dictionary ["." plist]]]] ["." meta]]] - ["." /// #_ + ["." /// "_" ["#." extension] [// - ["/" analysis (#+ Operation)] + ["/" analysis {"+" [Operation]}] [/// ["#" phase]]]]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/primitive.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/primitive.lux index 2b82d55a4..d3351fdf8 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/primitive.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/primitive.lux @@ -1,13 +1,13 @@ (.module: [library - [lux (#- nat int rev) + [lux {"-" [nat int rev]} [abstract monad]]] - ["." // #_ + ["." // "_" ["#." type] - ["/#" // #_ + ["/#" // "_" [// - ["/" analysis (#+ Analysis Operation)] + ["/" analysis {"+" [Analysis Operation]}] [/// ["#" phase]]]]]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/reference.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/reference.lux index d7d19e802..dcb211af4 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/reference.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/reference.lux @@ -1,21 +1,21 @@ (.module: [library - [lux #* + [lux "*" [abstract monad] [control - ["." exception (#+ exception:)]] + ["." exception {"+" [exception:]}]] ["." meta] [data ["." text ("#\." equivalence) - ["%" format (#+ format)]]]]] - ["." // #_ + ["%" format {"+" [format]}]]]]] + ["." // "_" ["#." scope] ["#." type] - ["/#" // #_ + ["/#" // "_" ["#." extension] [// - ["/" analysis (#+ Analysis Operation)] + ["/" analysis {"+" [Analysis Operation]}] [/// ["#." reference] ["#" phase]]]]]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/scope.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/scope.lux index 17423da65..4f99341c0 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/scope.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/scope.lux @@ -1,12 +1,12 @@ (.module: [library - [lux (#- local) + [lux {"-" [local]} [abstract monad] [control ["." maybe ("#\." monad)] ["." try] - ["." exception (#+ exception:)]] + ["." exception {"+" [exception:]}]] [data ["." text ("#\." equivalence)] ["." product] @@ -14,13 +14,13 @@ ["." list ("#\." functor mix monoid)] [dictionary ["." plist]]]]]] - ["." /// #_ + ["." /// "_" ["#." extension] [// - ["/" analysis (#+ Operation Phase)] + ["/" analysis {"+" [Operation Phase]}] [/// [reference - ["." variable (#+ Register Variable)]] + ["." variable {"+" [Register Variable]}]] ["#" phase]]]]) (type: Local diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/structure.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/structure.lux index 2d6d3140c..4dbaa2a4a 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/structure.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/structure.lux @@ -1,22 +1,22 @@ (.module: [library - [lux #* + [lux "*" ["." meta] [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control ["." maybe] ["." try] - ["." exception (#+ exception:)] + ["." exception {"+" [exception:]}] ["." state]] [data ["." name] ["." product] [text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." list ("#\." functor)] - ["." dictionary (#+ Dictionary)]]] + ["." dictionary {"+" [Dictionary]}]]] [macro ["." code]] [math @@ -24,18 +24,18 @@ ["n" nat]]] ["." type ["." check]]]] - ["." // #_ + ["." // "_" ["#." type] ["#." primitive] ["#." inference] - ["/#" // #_ + ["/#" // "_" ["#." extension] [// - ["/" analysis (#+ Tag Analysis Operation Phase)] + ["/" analysis {"+" [Tag Analysis Operation Phase]}] [/// ["#" phase] [meta - [archive (#+ Archive)]]]]]]) + [archive {"+" [Archive]}]]]]]]) (exception: .public (invalid_variant_type {type Type} {tag Tag} {code Code}) (exception.report diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/type.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/type.lux index 5b837152b..33c58b397 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/type.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/type.lux @@ -1,18 +1,18 @@ (.module: [library - [lux #* + [lux "*" [abstract - [monad (#+ do)]] + [monad {"+" [do]}]] [control ["." function] ["." try]] [type - ["." check (#+ Check)]] + ["." check {"+" [Check]}]] ["." meta]]] - ["." /// #_ + ["." /// "_" ["#." extension] [// - ["/" analysis (#+ Operation)] + ["/" analysis {"+" [Operation]}] [/// ["#" phase]]]]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/directive.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/directive.lux index 8db59f655..256725c5c 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/directive.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/directive.lux @@ -1,32 +1,32 @@ (.module: [library - [lux #* + [lux "*" ["." meta] [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control ["." try] - ["." exception (#+ exception:)]] + ["." exception {"+" [exception:]}]] [data [text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." list ("#\." mix monoid)]]]]] - ["." // #_ + ["." // "_" ["#." extension] ["#." analysis ["#/." type]] - ["/#" // #_ - ["/" directive (#+ Phase)] + ["/#" // "_" + ["/" directive {"+" [Phase]}] ["#." analysis ["." evaluation] - ["#/." macro (#+ Expander)]] + ["#/." macro {"+" [Expander]}]] [/// ["//" phase] - [reference (#+) - [variable (#+)]] + [reference {"+" []} + [variable {"+" []}]] [meta - [archive (#+ Archive)]]]]]) + [archive {"+" [Archive]}]]]]]) (exception: .public (not_a_directive {code Code}) (exception.report diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension.lux index e89d68ac8..4812e38e3 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension.lux @@ -1,25 +1,25 @@ (.module: [library - [lux (#- Name) + [lux {"-" [Name]} [abstract - [equivalence (#+ Equivalence)] - [hash (#+ Hash)] - ["." monad (#+ do)]] + [equivalence {"+" [Equivalence]}] + [hash {"+" [Hash]}] + ["." monad {"+" [do]}]] [control ["." function] - ["." try (#+ Try)] - ["." exception (#+ exception:)]] + ["." try {"+" [Try]}] + ["." exception {"+" [exception:]}]] [data ["." product] ["." text ("#\." order) - ["%" format (#+ Format format)]] + ["%" format {"+" [Format format]}]] [collection ["." list] - ["." dictionary (#+ Dictionary)]]]]] + ["." dictionary {"+" [Dictionary]}]]]]] [///// ["//" phase] [meta - [archive (#+ Archive)]]]) + [archive {"+" [Archive]}]]]) (type: .public Name Text) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis.lux index 096b659a2..1cba7387f 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis.lux @@ -1,13 +1,13 @@ (.module: [library - [lux #* + [lux "*" [data [collection ["." dictionary]]]]] [//// - [analysis (#+ Bundle) - [evaluation (#+ Eval)]]] - ["." / #_ + [analysis {"+" [Bundle]} + [evaluation {"+" [Eval]}]]] + ["." / "_" ["#." lux]]) (def: .public (bundle eval host_specific) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/common_lisp.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/common_lisp.lux index ea770d3a9..7f013b821 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/common_lisp.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/common_lisp.lux @@ -1,15 +1,15 @@ (.module: [library - [lux #* + [lux "*" ["." ffi] [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control ["<>" parser - ["<c>" code (#+ Parser)]]] + ["<c>" code {"+" [Parser]}]]] [data [collection - ["." array (#+ Array)] + ["." array {"+" [Array]}] ["." dictionary] ["." list]]] ["." type @@ -17,14 +17,14 @@ ["@" target ["_" common_lisp]]]] [// - ["/" lux (#+ custom)] + ["/" lux {"+" [custom]}] [// ["." bundle] [// - ["." analysis #_ + ["." analysis "_" ["#/." type]] [// - ["." analysis (#+ Analysis Operation Phase Handler Bundle)] + ["." analysis {"+" [Analysis Operation Phase Handler Bundle]}] [/// ["." phase]]]]]]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/js.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/js.lux index 22c663250..3d18a03b4 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/js.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/js.lux @@ -1,15 +1,15 @@ (.module: [library - [lux #* + [lux "*" ["." ffi] [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control ["<>" parser - ["<c>" code (#+ Parser)]]] + ["<c>" code {"+" [Parser]}]]] [data [collection - ["." array (#+ Array)] + ["." array {"+" [Array]}] ["." dictionary] ["." list]]] ["." type @@ -17,14 +17,14 @@ ["@" target ["_" js]]]] [// - ["/" lux (#+ custom)] + ["/" lux {"+" [custom]}] [// ["." bundle] [// - ["." analysis #_ + ["." analysis "_" ["#/." type]] [// - ["." analysis (#+ Analysis Operation Phase Handler Bundle)] + ["." analysis {"+" [Analysis Operation Phase Handler Bundle]}] [/// ["." phase]]]]]]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux index 7efd44bcd..953a9aaa4 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux @@ -1,62 +1,62 @@ (.module: [library - [lux (#- Type Module primitive type char int) - ["." ffi (#+ import:)] + [lux {"-" [Type Module primitive type char int]} + ["." ffi {"+" [import:]}] ["." meta] [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control pipe ["." maybe] - ["." try (#+ Try) ("#\." monad)] - ["." exception (#+ exception:)] + ["." try {"+" [Try]} ("#\." monad)] + ["." exception {"+" [exception:]}] ["<>" parser - ["<.>" code (#+ Parser)] + ["<.>" code {"+" [Parser]}] ["<.>" text]]] [data ["." product] ["." text ("#\." equivalence) - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." list ("#\." mix monad monoid)] ["." array] - ["." dictionary (#+ Dictionary)]]] + ["." dictionary {"+" [Dictionary]}]]] [math [number ["n" nat]]] [target - ["." jvm #_ + ["." jvm "_" [".!" reflection] [encoding - [name (#+ External)]] - ["#" type (#+ Type Argument Typed) ("#\." equivalence) - ["." category (#+ Void Value' Value Return' Return Primitive Object Class Array Var Parameter Method)] + [name {"+" [External]}]] + ["#" type {"+" [Type Argument Typed]} ("#\." equivalence) + ["." category {"+" [Void Value' Value Return' Return Primitive Object Class Array Var Parameter Method]}] ["." box] ["." reflection] ["." descriptor] ["." signature] ["#_." parser] - ["#_." alias (#+ Aliasing)] - [".T" lux (#+ Mapping)]]]] + ["#_." alias {"+" [Aliasing]}] + [".T" lux {"+" [Mapping]}]]]] ["." type - ["." check (#+ Check) ("#\." monad)]]]] - ["." // #_ - ["#." lux (#+ custom)] + ["." check {"+" [Check]} ("#\." monad)]]]] + ["." // "_" + ["#." lux {"+" [custom]}] ["/#" // ["#." bundle] - ["/#" // #_ + ["/#" // "_" [analysis [".A" type] [".A" inference] ["." scope]] - ["/#" // #_ - ["#." analysis (#+ Analysis Operation Phase Handler Bundle)] + ["/#" // "_" + ["#." analysis {"+" [Analysis Operation Phase Handler Bundle]}] ["#." synthesis] [/// ["." phase ("#\." monad)] [meta - [archive (#+ Archive) - [descriptor (#+ Module)]]]]]]]]) + [archive {"+" [Archive]} + [descriptor {"+" [Module]}]]]]]]]]) (import: java/lang/ClassLoader) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/lua.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/lua.lux index 7cfd9eed6..fcdd55439 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/lua.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/lua.lux @@ -1,15 +1,15 @@ (.module: [library - [lux #* + [lux "*" ["." ffi] [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control ["<>" parser - ["<.>" code (#+ Parser)]]] + ["<.>" code {"+" [Parser]}]]] [data [collection - ["." array (#+ Array)] + ["." array {"+" [Array]}] ["." dictionary] ["." list]]] ["." type @@ -17,14 +17,14 @@ ["@" target ["_" lua]]]] [// - ["/" lux (#+ custom)] + ["/" lux {"+" [custom]}] [// ["." bundle] [// - ["." analysis #_ + ["." analysis "_" ["#/." type]] [// - ["." analysis (#+ Analysis Operation Phase Handler Bundle)] + ["." analysis {"+" [Analysis Operation Phase Handler Bundle]}] [/// ["." phase]]]]]]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/lux.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/lux.lux index 278447d11..cc3f13b0a 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/lux.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/lux.lux @@ -1,20 +1,20 @@ (.module: [library - [lux #* + [lux "*" [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control ["." maybe] ["." try] - ["." exception (#+ exception:)] + ["." exception {"+" [exception:]}] ["<>" parser - ["<.>" code (#+ Parser)]]] + ["<.>" code {"+" [Parser]}]]] [data ["." text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." list ("#\." functor)] - ["." dictionary (#+ Dictionary)]]] + ["." dictionary {"+" [Dictionary]}]]] [math [number ["n" nat]]] @@ -23,16 +23,16 @@ ["." meta]]] ["." /// ["#." bundle] - ["/#" // #_ + ["/#" // "_" [analysis [".A" type]] [// - ["#." analysis (#+ Analysis Operation Phase Handler Bundle) - [evaluation (#+ Eval)]] + ["#." analysis {"+" [Analysis Operation Phase Handler Bundle]} + [evaluation {"+" [Eval]}]] [/// ["#" phase] [meta - [archive (#+ Archive)]]]]]]) + [archive {"+" [Archive]}]]]]]]) (def: .public (custom [syntax handler]) (All (_ s) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/php.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/php.lux index 02cb8bbb7..5edc50baa 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/php.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/php.lux @@ -1,15 +1,15 @@ (.module: [library - [lux #* + [lux "*" ["." ffi] [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control ["<>" parser - ["<c>" code (#+ Parser)]]] + ["<c>" code {"+" [Parser]}]]] [data [collection - ["." array (#+ Array)] + ["." array {"+" [Array]}] ["." dictionary] ["." list]]] ["." type @@ -17,14 +17,14 @@ ["@" target ["_" php]]]] [// - ["/" lux (#+ custom)] + ["/" lux {"+" [custom]}] [// ["." bundle] [// - ["." analysis #_ + ["." analysis "_" ["#/." type]] [// - ["." analysis (#+ Analysis Operation Phase Handler Bundle)] + ["." analysis {"+" [Analysis Operation Phase Handler Bundle]}] [/// ["." phase]]]]]]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/python.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/python.lux index 85b9124ce..5bbaa5947 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/python.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/python.lux @@ -1,15 +1,15 @@ (.module: [library - [lux #* + [lux "*" ["." ffi] [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control ["<>" parser - ["<.>" code (#+ Parser)]]] + ["<.>" code {"+" [Parser]}]]] [data [collection - ["." array (#+ Array)] + ["." array {"+" [Array]}] ["." dictionary] ["." list]]] ["." type @@ -17,14 +17,14 @@ ["@" target ["_" python]]]] [// - ["/" lux (#+ custom)] + ["/" lux {"+" [custom]}] [// ["." bundle] [// - ["." analysis #_ + ["." analysis "_" ["#/." type]] [// - ["." analysis (#+ Analysis Operation Phase Handler Bundle)] + ["." analysis {"+" [Analysis Operation Phase Handler Bundle]}] [/// ["." phase]]]]]]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/r.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/r.lux index 00e210a54..b9a92f5fe 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/r.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/r.lux @@ -1,15 +1,15 @@ (.module: [library - [lux #* + [lux "*" ["." ffi] [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control ["<>" parser - ["<c>" code (#+ Parser)]]] + ["<c>" code {"+" [Parser]}]]] [data [collection - ["." array (#+ Array)] + ["." array {"+" [Array]}] ["." dictionary] ["." list]]] ["." type @@ -17,14 +17,14 @@ ["@" target ["_" r]]]] [// - ["/" lux (#+ custom)] + ["/" lux {"+" [custom]}] [// ["." bundle] [// - ["." analysis #_ + ["." analysis "_" ["#/." type]] [// - ["." analysis (#+ Analysis Operation Phase Handler Bundle)] + ["." analysis {"+" [Analysis Operation Phase Handler Bundle]}] [/// ["." phase]]]]]]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/ruby.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/ruby.lux index 2f5ef9cbb..e5e7c98a5 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/ruby.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/ruby.lux @@ -1,15 +1,15 @@ (.module: [library - [lux #* + [lux "*" ["." ffi] [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control ["<>" parser - ["<c>" code (#+ Parser)]]] + ["<c>" code {"+" [Parser]}]]] [data [collection - ["." array (#+ Array)] + ["." array {"+" [Array]}] ["." dictionary] ["." list]]] ["." type @@ -17,14 +17,14 @@ ["@" target ["_" ruby]]]] [// - ["/" lux (#+ custom)] + ["/" lux {"+" [custom]}] [// ["." bundle] [// - ["." analysis #_ + ["." analysis "_" ["#/." type]] [// - ["." analysis (#+ Analysis Operation Phase Handler Bundle)] + ["." analysis {"+" [Analysis Operation Phase Handler Bundle]}] [/// ["." phase]]]]]]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/scheme.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/scheme.lux index e29c99177..179af70bc 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/scheme.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/scheme.lux @@ -1,15 +1,15 @@ (.module: [library - [lux #* + [lux "*" ["." ffi] [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control ["<>" parser - ["<c>" code (#+ Parser)]]] + ["<c>" code {"+" [Parser]}]]] [data [collection - ["." array (#+ Array)] + ["." array {"+" [Array]}] ["." dictionary] ["." list]]] ["." type @@ -17,14 +17,14 @@ ["@" target ["_" scheme]]]] [// - ["/" lux (#+ custom)] + ["/" lux {"+" [custom]}] [// ["." bundle] [// - ["." analysis #_ + ["." analysis "_" ["#/." type]] [// - ["." analysis (#+ Analysis Operation Phase Handler Bundle)] + ["." analysis {"+" [Analysis Operation Phase Handler Bundle]}] [/// ["." phase]]]]]]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/bundle.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/bundle.lux index c3b9b9a9e..07efebff3 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/bundle.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/bundle.lux @@ -1,15 +1,15 @@ (.module: [library - [lux #* + [lux "*" [abstract - [monad (#+ do)]] + [monad {"+" [do]}]] [data ["." text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." list ("#\." functor)] - ["." dictionary (#+ Dictionary)]]]]] - [// (#+ Handler Bundle)]) + ["." dictionary {"+" [Dictionary]}]]]]] + [// {"+" [Handler Bundle]}]) (def: .public empty Bundle diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/jvm.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/jvm.lux index c7e17a992..b07a693e4 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/jvm.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/jvm.lux @@ -1,18 +1,18 @@ (.module: [library - [lux (#- Type Definition) + [lux {"-" [Type Definition]} ["." host] [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control - [pipe (#+ case>)] + [pipe {"+" [case>]}] ["<>" parser ("#\." monad) - ["<c>" code (#+ Parser)] + ["<c>" code {"+" [Parser]}] ["<t>" text]]] [data ["." product] [text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." list ("#\." functor mix)] ["." dictionary] @@ -24,34 +24,34 @@ ["." i32]]] [target [jvm - ["_" bytecode (#+ Bytecode)] - ["." modifier (#+ Modifier) ("#\." monoid)] + ["_" bytecode {"+" [Bytecode]}] + ["." modifier {"+" [Modifier]} ("#\." monoid)] ["." attribute] ["." field] ["." version] ["." class] ["." constant - ["." pool (#+ Resource)]] + ["." pool {"+" [Resource]}]] [encoding ["." name]] - ["." type (#+ Type Constraint Argument Typed) - [category (#+ Void Value Return Method Primitive Object Class Array Var Parameter)] - [".T" lux (#+ Mapping)] + ["." type {"+" [Type Constraint Argument Typed]} + [category {"+" [Void Value Return Method Primitive Object Class Array Var Parameter]}] + [".T" lux {"+" [Mapping]}] ["." signature] - ["." descriptor (#+ Descriptor)] + ["." descriptor {"+" [Descriptor]}] ["." parser]]]] [tool [compiler ["." analysis] ["." synthesis] ["." generation] - ["." directive (#+ Handler Bundle)] + ["." directive {"+" [Handler Bundle]}] ["." phase [analysis [".A" type]] ["." generation [jvm - [runtime (#+ Anchor Definition)]]] + [runtime {"+" [Anchor Definition]}]]] ["." extension ["." bundle] [analysis @@ -59,7 +59,7 @@ [directive ["/" lux]]]]]] [type - ["." check (#+ Check)]]]]) + ["." check {"+" [Check]}]]]]) (type: Operation (directive.Operation Anchor (Bytecode Any) Definition)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux index 46dd5d709..72b5692ed 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux @@ -1,19 +1,19 @@ (.module: [library - [lux #* + [lux "*" ["." meta] [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control - [io (#+ IO)] + [io {"+" [IO]}] ["." try] - ["." exception (#+ exception:)] + ["." exception {"+" [exception:]}] ["<>" parser - ["<.>" code (#+ Parser)]]] + ["<.>" code {"+" [Parser]}]]] [data ["." product] ["." text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." dictionary]]] [macro @@ -21,27 +21,27 @@ [math [number ["n" nat]]] - ["." type (#+ :sharing) + ["." type {"+" [:sharing]} ["." check]]]] - ["." /// (#+ Extender) + ["." /// {"+" [Extender]} ["#." bundle] ["#." analysis] - ["/#" // #_ + ["/#" // "_" [analysis ["." module] [".A" type]] - ["/#" // #_ + ["/#" // "_" ["#." analysis - [macro (#+ Expander)] + [macro {"+" [Expander]}] ["#/." evaluation]] - ["#." synthesis (#+ Synthesis)] - ["#." generation (#+ Context)] - ["#." directive (#+ Import Requirements Phase Operation Handler Bundle)] - ["#." program (#+ Program)] + ["#." synthesis {"+" [Synthesis]}] + ["#." generation {"+" [Context]}] + ["#." directive {"+" [Import Requirements Phase Operation Handler Bundle]}] + ["#." program {"+" [Program]}] [/// ["." phase] [meta - ["." archive (#+ Archive)]]]]]]) + ["." archive {"+" [Archive]}]]]]]]) (def: .public (custom [syntax handler]) (All (_ anchor expression directive s) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/common_lisp.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/common_lisp.lux index 6d5995330..0992cd220 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/common_lisp.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/common_lisp.lux @@ -1,16 +1,16 @@ (.module: [library - [lux #* + [lux "*" [data [collection ["." dictionary]]]]] - ["." / #_ + ["." / "_" ["#." common] ["#." host] [//// [generation [common_lisp - [runtime (#+ Bundle)]]]]]) + [runtime {"+" [Bundle]}]]]]]) (def: .public bundle Bundle diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/common_lisp/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/common_lisp/common.lux index 3f63dbcd9..713343997 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/common_lisp/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/common_lisp/common.lux @@ -1,17 +1,17 @@ (.module: [library - [lux #* + [lux "*" [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control ["." function] ["." try] ["<>" parser - ["<s>" synthesis (#+ Parser)]]] + ["<s>" synthesis {"+" [Parser]}]]] [data ["." product] ["." text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." dictionary] ["." set] @@ -20,20 +20,20 @@ [number ["f" frac]]] ["@" target - ["_" common_lisp (#+ Expression)]]]] - ["." //// #_ + ["_" common_lisp {"+" [Expression]}]]]] + ["." //// "_" ["/" bundle] - ["/#" // #_ + ["/#" // "_" ["." extension] [generation - [extension (#+ Nullary Unary Binary Trinary - nullary unary binary trinary)] + [extension {"+" [Nullary Unary Binary Trinary + nullary unary binary trinary]}] ["." reference] - ["//" common_lisp #_ - ["#." runtime (#+ Operation Phase Handler Bundle Generator)] + ["//" common_lisp "_" + ["#." runtime {"+" [Operation Phase Handler Bundle Generator]}] ["#." case]]] [// - ["." synthesis (#+ %synthesis)] + ["." synthesis {"+" [%synthesis]}] ["." generation] [/// ["#" phase]]]]]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/common_lisp/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/common_lisp/host.lux index a4aa3e5e8..5a3e8bc9a 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/common_lisp/host.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/common_lisp/host.lux @@ -1,36 +1,36 @@ (.module: [library - [lux #* + [lux "*" [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control ["." function] ["<>" parser - ["<s>" synthesis (#+ Parser)]]] + ["<s>" synthesis {"+" [Parser]}]]] [data [collection ["." dictionary] ["." list]] [text - ["%" format (#+ format)]]] + ["%" format {"+" [format]}]]] [target - ["_" common_lisp (#+ Var Expression)]]]] - ["." // #_ - ["#." common (#+ custom)] - ["//#" /// #_ + ["_" common_lisp {"+" [Var Expression]}]]]] + ["." // "_" + ["#." common {"+" [custom]}] + ["//#" /// "_" ["/" bundle] - ["/#" // #_ + ["/#" // "_" ["." extension] [generation - [extension (#+ Nullary Unary Binary Trinary - nullary unary binary trinary)] + [extension {"+" [Nullary Unary Binary Trinary + nullary unary binary trinary]}] ["." reference] - ["//" common_lisp #_ - ["#." runtime (#+ Operation Phase Handler Bundle - with_vars)]]] - ["/#" // #_ + ["//" common_lisp "_" + ["#." runtime {"+" [Operation Phase Handler Bundle + with_vars]}]]] + ["/#" // "_" ["." generation] - ["//#" /// #_ + ["//#" /// "_" ["#." phase]]]]]]) (def: .public bundle diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js.lux index d4580215f..4f4bb191f 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js.lux @@ -1,16 +1,16 @@ (.module: [library - [lux #* + [lux "*" [data [collection ["." dictionary]]]]] - ["." / #_ + ["." / "_" ["#." common] ["#." host] [//// [generation [js - [runtime (#+ Bundle)]]]]]) + [runtime {"+" [Bundle]}]]]]]) (def: .public bundle Bundle diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/common.lux index be57d4c55..c86f34dc9 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/common.lux @@ -1,12 +1,12 @@ (.module: [library - [lux #* + [lux "*" [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control ["." try] ["<>" parser - ["<s>" synthesis (#+ Parser)]]] + ["<s>" synthesis {"+" [Parser]}]]] [data ["." product] [collection @@ -16,16 +16,16 @@ [number ["f" frac]]] ["@" target - ["_" js (#+ Literal Expression Statement)]]]] - ["." //// #_ + ["_" js {"+" [Literal Expression Statement]}]]]] + ["." //// "_" ["/" bundle] - ["/#" // #_ + ["/#" // "_" ["." extension] [generation - [extension (#+ Nullary Unary Binary Trinary - nullary unary binary trinary)] - ["//" js #_ - ["#." runtime (#+ Operation Phase Phase! Handler Bundle Generator)] + [extension {"+" [Nullary Unary Binary Trinary + nullary unary binary trinary]}] + ["//" js "_" + ["#." runtime {"+" [Operation Phase Phase! Handler Bundle Generator]}] ["#." primitive] ["#." structure] ["#." reference] @@ -33,8 +33,8 @@ ["#." loop] ["#." function]]] [// - [analysis (#+)] - ["." synthesis (#+ %synthesis)] + [analysis {"+" []}] + ["." synthesis {"+" [%synthesis]}] [/// ["#" phase ("#\." monad)]]]]]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/host.lux index 546085ce4..e37c2abf3 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/host.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/host.lux @@ -1,33 +1,33 @@ (.module: [library - [lux #* + [lux "*" [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control ["." function] ["<>" parser - ["<s>" synthesis (#+ Parser)]]] + ["<s>" synthesis {"+" [Parser]}]]] [data [collection ["." dictionary] ["." list]]] [target - ["_" js (#+ Var Expression)]]]] - ["." // #_ - ["#." common (#+ custom)] - ["//#" /// #_ + ["_" js {"+" [Var Expression]}]]]] + ["." // "_" + ["#." common {"+" [custom]}] + ["//#" /// "_" ["/" bundle] - ["/#" // #_ + ["/#" // "_" ["." extension] [generation - [extension (#+ Nullary Unary Binary Trinary - nullary unary binary trinary)] - ["//" js #_ - ["#." runtime (#+ Operation Phase Handler Bundle - with_vars)]]] - ["/#" // #_ + [extension {"+" [Nullary Unary Binary Trinary + nullary unary binary trinary]}] + ["//" js "_" + ["#." runtime {"+" [Operation Phase Handler Bundle + with_vars]}]]] + ["/#" // "_" ["." generation] - ["//#" /// #_ + ["//#" /// "_" ["#." phase]]]]]]) (def: array::new diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm.lux index 43bc68142..cbd03e12b 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm.lux @@ -1,16 +1,16 @@ (.module: [library - [lux #* + [lux "*" [data [collection ["." dictionary]]]]] - ["." / #_ + ["." / "_" ["#." common] ["#." host] [//// [generation [jvm - [runtime (#+ Bundle)]]]]]) + [runtime {"+" [Bundle]}]]]]]) (def: .public bundle Bundle diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/common.lux index ce860dbf9..ce8ecb7fb 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/common.lux @@ -1,13 +1,13 @@ (.module: [library - [lux (#- Type) + [lux {"-" [Type]} [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control ["." try] - ["." exception (#+ exception:)] + ["." exception {"+" [exception:]}] ["<>" parser - ["<s>" synthesis (#+ Parser)]]] + ["<s>" synthesis {"+" [Parser]}]]] [data ["." product] [number @@ -18,29 +18,29 @@ ["." dictionary]]] [target [jvm - ["_" bytecode (#+ Label Bytecode) ("#\." monad)] + ["_" bytecode {"+" [Label Bytecode]} ("#\." monad)] [encoding - ["." signed (#+ S4)]] - ["." type (#+ Type) - [category (#+ Primitive Class)]]]]]] - ["." ///// #_ + ["." signed {"+" [S4]}]] + ["." type {"+" [Type]} + [category {"+" [Primitive Class]}]]]]]] + ["." ///// "_" [generation - [extension (#+ Nullary Unary Binary Trinary Variadic - nullary unary binary trinary variadic)] - ["///" jvm #_ + [extension {"+" [Nullary Unary Binary Trinary Variadic + nullary unary binary trinary variadic]}] + ["///" jvm "_" ["#." value] - ["#." runtime (#+ Operation Phase Bundle Handler)] - ["#." function #_ + ["#." runtime {"+" [Operation Phase Bundle Handler]}] + ["#." function "_" ["#" abstract]]]] [extension ["#extension" /] ["#." bundle]] [// - ["/#." synthesis (#+ Synthesis %synthesis)] + ["/#." synthesis {"+" [Synthesis %synthesis]}] [/// ["#" phase] [meta - [archive (#+ Archive)]]]]]) + [archive {"+" [Archive]}]]]]]) (def: .public (custom [parser handler]) (All (_ s) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux index cf9f14c00..b112ee9a3 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux @@ -1,54 +1,54 @@ (.module: [library - [lux (#- Type) + [lux {"-" [Type]} [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control ["." maybe] ["." try] - ["." exception (#+ exception:)] + ["." exception {"+" [exception:]}] ["<>" parser ["<t>" text] - ["<s>" synthesis (#+ Parser)]]] + ["<s>" synthesis {"+" [Parser]}]]] [data ["." product] ["." text ("#\." equivalence) - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [number ["." i32]] [collection ["." list ("#\." monad)] - ["." dictionary (#+ Dictionary)] + ["." dictionary {"+" [Dictionary]}] ["." set] ["." row]] - ["." format #_ + ["." format "_" ["#" binary]]] [target [jvm ["." version] ["." modifier ("#\." monoid)] - ["." method (#+ Method)] - ["." class (#+ Class)] + ["." method {"+" [Method]}] + ["." class {"+" [Class]}] [constant - [pool (#+ Resource)]] + [pool {"+" [Resource]}]] [encoding ["." name]] - ["_" bytecode (#+ Label Bytecode) ("#\." monad) - ["__" instruction (#+ Primitive_Array_Type)]] - ["." type (#+ Type Typed Argument) - ["." category (#+ Void Value' Value Return' Return Primitive Object Array Var Parameter)] + ["_" bytecode {"+" [Label Bytecode]} ("#\." monad) + ["__" instruction {"+" [Primitive_Array_Type]}]] + ["." type {"+" [Type Typed Argument]} + ["." category {"+" [Void Value' Value Return' Return Primitive Object Array Var Parameter]}] ["." box] ["." reflection] ["." signature] ["." parser]]]]]] - ["." // #_ - [common (#+ custom)] - ["///#" //// #_ + ["." // "_" + [common {"+" [custom]}] + ["///#" //// "_" [generation - [extension (#+ Nullary Unary Binary Trinary Variadic - nullary unary binary trinary variadic)] + [extension {"+" [Nullary Unary Binary Trinary Variadic + nullary unary binary trinary variadic]}] ["///" jvm - ["#." runtime (#+ Operation Bundle Phase Handler)] + ["#." runtime {"+" [Operation Bundle Phase Handler]}] ["#." reference] [function [field @@ -58,16 +58,16 @@ ["#." bundle] [analysis ["/" jvm]]] - ["/#" // #_ - [analysis (#+ Environment)] - ["#." synthesis (#+ Synthesis Path %synthesis)] + ["/#" // "_" + [analysis {"+" [Environment]}] + ["#." synthesis {"+" [Synthesis Path %synthesis]}] ["#." generation] [/// ["#" phase] [reference - ["#." variable (#+ Variable)]] + ["#." variable {"+" [Variable]}]] [meta - ["." archive (#+ Archive)]]]]]]) + ["." archive {"+" [Archive]}]]]]]]) (template [<name> <0> <1>] [(def: <name> diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua.lux index 93062f68c..55320a5dd 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua.lux @@ -1,16 +1,16 @@ (.module: [library - [lux #* + [lux "*" [data [collection ["." dictionary]]]]] - ["." / #_ + ["." / "_" ["#." common] ["#." host] [//// [generation [lua - [runtime (#+ Bundle)]]]]]) + [runtime {"+" [Bundle]}]]]]]) (def: .public bundle Bundle diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/common.lux index 4cfaa6335..c6401872e 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/common.lux @@ -1,17 +1,17 @@ (.module: [library - [lux #* + [lux "*" [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control ["." function] ["." try] ["<>" parser - ["<s>" synthesis (#+ Parser)]]] + ["<s>" synthesis {"+" [Parser]}]]] [data ["." product] ["." text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." dictionary] ["." list ("#\." functor mix)]]] @@ -19,16 +19,16 @@ [number ["f" frac]]] ["@" target - ["_" lua (#+ Expression Statement)]]]] - ["." //// #_ + ["_" lua {"+" [Expression Statement]}]]]] + ["." //// "_" ["/" bundle] - ["/#" // #_ + ["/#" // "_" ["." extension] [generation - [extension (#+ Nullary Unary Binary Trinary - nullary unary binary trinary)] - ["//" lua #_ - ["#." runtime (#+ Operation Phase Phase! Handler Bundle Generator)] + [extension {"+" [Nullary Unary Binary Trinary + nullary unary binary trinary]}] + ["//" lua "_" + ["#." runtime {"+" [Operation Phase Phase! Handler Bundle Generator]}] ["#." primitive] ["#." structure] ["#." reference] @@ -36,7 +36,7 @@ ["#." loop] ["#." function]]] [// - ["." synthesis (#+ %synthesis)] + ["." synthesis {"+" [%synthesis]}] ["." generation] [/// ["#" phase ("#\." monad)]]]]]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/host.lux index a1bffe3cf..1a041a49e 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/host.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/host.lux @@ -1,36 +1,36 @@ (.module: [library - [lux #* + [lux "*" [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control ["." function] ["<>" parser - ["<s>" synthesis (#+ Parser)]]] + ["<s>" synthesis {"+" [Parser]}]]] [data [collection ["." dictionary] ["." list]] [text - ["%" format (#+ format)]]] + ["%" format {"+" [format]}]]] [target - ["_" lua (#+ Var Expression)]]]] - ["." // #_ - ["#." common (#+ custom)] - ["//#" /// #_ + ["_" lua {"+" [Var Expression]}]]]] + ["." // "_" + ["#." common {"+" [custom]}] + ["//#" /// "_" ["/" bundle] - ["/#" // #_ + ["/#" // "_" ["." extension] [generation - [extension (#+ Nullary Unary Binary Trinary - nullary unary binary trinary)] + [extension {"+" [Nullary Unary Binary Trinary + nullary unary binary trinary]}] ["." reference] - ["//" lua #_ - ["#." runtime (#+ Operation Phase Handler Bundle - with_vars)]]] - ["/#" // #_ + ["//" lua "_" + ["#." runtime {"+" [Operation Phase Handler Bundle + with_vars]}]]] + ["/#" // "_" ["." generation] - ["//#" /// #_ + ["//#" /// "_" ["#." phase]]]]]]) (def: array::new diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php.lux index 552a0756c..1815d08fa 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php.lux @@ -1,16 +1,16 @@ (.module: [library - [lux #* + [lux "*" [data [collection ["." dictionary]]]]] - ["." / #_ + ["." / "_" ["#." common] ["#." host] [//// [generation [php - [runtime (#+ Bundle)]]]]]) + [runtime {"+" [Bundle]}]]]]]) (def: .public bundle Bundle diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php/common.lux index 0ba08dfd9..b176ca30d 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php/common.lux @@ -1,17 +1,17 @@ (.module: [library - [lux #* + [lux "*" [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control ["." function] ["." try] ["<>" parser - ["<s>" synthesis (#+ Parser)]]] + ["<s>" synthesis {"+" [Parser]}]]] [data ["." product] ["." text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." dictionary] ["." set] @@ -20,20 +20,20 @@ [number ["f" frac]]] ["@" target - ["_" php (#+ Expression)]]]] - ["." //// #_ + ["_" php {"+" [Expression]}]]]] + ["." //// "_" ["/" bundle] - ["/#" // #_ + ["/#" // "_" ["." extension] [generation - [extension (#+ Nullary Unary Binary Trinary - nullary unary binary trinary)] + [extension {"+" [Nullary Unary Binary Trinary + nullary unary binary trinary]}] ["." reference] - ["//" php #_ - ["#." runtime (#+ Operation Phase Handler Bundle Generator)] + ["//" php "_" + ["#." runtime {"+" [Operation Phase Handler Bundle Generator]}] ["#." case]]] [// - ["." synthesis (#+ %synthesis)] + ["." synthesis {"+" [%synthesis]}] ["." generation] [/// ["#" phase]]]]]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php/host.lux index e391dba46..c577f36c1 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php/host.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php/host.lux @@ -1,36 +1,36 @@ (.module: [library - [lux #* + [lux "*" [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control ["." function] ["<>" parser - ["<s>" synthesis (#+ Parser)]]] + ["<s>" synthesis {"+" [Parser]}]]] [data [collection ["." dictionary] ["." list]] [text - ["%" format (#+ format)]]] + ["%" format {"+" [format]}]]] [target - ["_" php (#+ Var Expression)]]]] - ["." // #_ - ["#." common (#+ custom)] - ["//#" /// #_ + ["_" php {"+" [Var Expression]}]]]] + ["." // "_" + ["#." common {"+" [custom]}] + ["//#" /// "_" ["/" bundle] - ["/#" // #_ + ["/#" // "_" ["." extension] [generation - [extension (#+ Nullary Unary Binary Trinary - nullary unary binary trinary)] + [extension {"+" [Nullary Unary Binary Trinary + nullary unary binary trinary]}] ["." reference] - ["//" php #_ - ["#." runtime (#+ Operation Phase Handler Bundle - with_vars)]]] - ["/#" // #_ + ["//" php "_" + ["#." runtime {"+" [Operation Phase Handler Bundle + with_vars]}]]] + ["/#" // "_" ["." generation] - ["//#" /// #_ + ["//#" /// "_" ["#." phase]]]]]]) (def: (array::new size) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python.lux index b0bab688a..17c4e2402 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python.lux @@ -1,16 +1,16 @@ (.module: [library - [lux #* + [lux "*" [data [collection ["." dictionary]]]]] - ["." / #_ + ["." / "_" ["#." common] ["#." host] [//// [generation [python - [runtime (#+ Bundle)]]]]]) + [runtime {"+" [Bundle]}]]]]]) (def: .public bundle Bundle diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/common.lux index fcf5e8b2d..7f4cf2e80 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/common.lux @@ -1,17 +1,17 @@ (.module: [library - [lux #* + [lux "*" [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control ["." function] ["." try] ["<>" parser - ["<.>" synthesis (#+ Parser)]]] + ["<.>" synthesis {"+" [Parser]}]]] [data ["." product] ["." text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." dictionary] ["." list ("#\." functor mix)]]] @@ -19,17 +19,17 @@ [number ["f" frac]]] [target - ["_" python (#+ Expression Statement)]]]] - ["." //// #_ + ["_" python {"+" [Expression Statement]}]]]] + ["." //// "_" ["/" bundle] - ["/#" // #_ + ["/#" // "_" ["." extension] [generation ["." reference] - [extension (#+ Nullary Unary Binary Trinary - nullary unary binary trinary)] - ["//" python #_ - ["#." runtime (#+ Operation Phase Phase! Handler Bundle Generator)] + [extension {"+" [Nullary Unary Binary Trinary + nullary unary binary trinary]}] + ["//" python "_" + ["#." runtime {"+" [Operation Phase Phase! Handler Bundle Generator]}] ["#." primitive] ["#." structure] ["#." reference] @@ -37,8 +37,8 @@ ["#." case] ["#." loop]]] [// - [analysis (#+)] - ["." synthesis (#+ %synthesis)] + [analysis {"+" []}] + ["." synthesis {"+" [%synthesis]}] ["." generation] [/// ["#" phase ("#\." monad)]]]]]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/host.lux index c5b2d8abf..276edc180 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/host.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/host.lux @@ -1,33 +1,33 @@ (.module: [library - [lux #* + [lux "*" [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control ["." function] ["<>" parser - ["<s>" synthesis (#+ Parser)]]] + ["<s>" synthesis {"+" [Parser]}]]] [data [collection ["." dictionary] ["." list]]] [target - ["_" python (#+ Expression SVar)]]]] - ["." // #_ - ["#." common (#+ custom)] - ["//#" /// #_ + ["_" python {"+" [Expression SVar]}]]]] + ["." // "_" + ["#." common {"+" [custom]}] + ["//#" /// "_" ["/" bundle] - ["/#" // #_ + ["/#" // "_" ["." extension] [generation - [extension (#+ Nullary Unary Binary Trinary - nullary unary binary trinary)] - ["//" python #_ - ["#." runtime (#+ Operation Phase Handler Bundle - with_vars)]]] - ["/#" // #_ + [extension {"+" [Nullary Unary Binary Trinary + nullary unary binary trinary]}] + ["//" python "_" + ["#." runtime {"+" [Operation Phase Handler Bundle + with_vars]}]]] + ["/#" // "_" ["." generation] - ["//#" /// #_ + ["//#" /// "_" ["#." phase]]]]]]) (def: (array::new size) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/r.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/r.lux index 504e5d5e9..256bca1b1 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/r.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/r.lux @@ -1,16 +1,16 @@ (.module: [library - [lux #* + [lux "*" [data [collection ["." dictionary]]]]] - ["." / #_ + ["." / "_" ["#." common] ["#." host] [//// [generation [r - [runtime (#+ Bundle)]]]]]) + [runtime {"+" [Bundle]}]]]]]) (def: .public bundle Bundle diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/r/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/r/common.lux index a07c72c74..4a736b151 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/r/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/r/common.lux @@ -1,17 +1,17 @@ (.module: [library - [lux #* + [lux "*" [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control ["." function] ["." try] ["<>" parser - ["<s>" synthesis (#+ Parser)]]] + ["<s>" synthesis {"+" [Parser]}]]] [data ["." product] ["." text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." dictionary] ["." set] @@ -20,20 +20,20 @@ [number ["f" frac]]] ["@" target - ["_" r (#+ Expression)]]]] - ["." //// #_ + ["_" r {"+" [Expression]}]]]] + ["." //// "_" ["/" bundle] - ["/#" // #_ + ["/#" // "_" ["." extension] [generation - [extension (#+ Nullary Unary Binary Trinary - nullary unary binary trinary)] + [extension {"+" [Nullary Unary Binary Trinary + nullary unary binary trinary]}] ["." reference] - ["//" r #_ - ["#." runtime (#+ Operation Phase Handler Bundle Generator)] + ["//" r "_" + ["#." runtime {"+" [Operation Phase Handler Bundle Generator]}] ["#." case]]] [// - ["." synthesis (#+ %synthesis)] + ["." synthesis {"+" [%synthesis]}] ["." generation] [/// ["#" phase]]]]]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/r/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/r/host.lux index f36b10e83..38613dbe3 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/r/host.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/r/host.lux @@ -1,36 +1,36 @@ (.module: [library - [lux #* + [lux "*" [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control ["." function] ["<>" parser - ["<s>" synthesis (#+ Parser)]]] + ["<s>" synthesis {"+" [Parser]}]]] [data [collection ["." dictionary] ["." list]] [text - ["%" format (#+ format)]]] + ["%" format {"+" [format]}]]] [target - ["_" r (#+ Var Expression)]]]] - ["." // #_ - ["#." common (#+ custom)] - ["//#" /// #_ + ["_" r {"+" [Var Expression]}]]]] + ["." // "_" + ["#." common {"+" [custom]}] + ["//#" /// "_" ["/" bundle] - ["/#" // #_ + ["/#" // "_" ["." extension] [generation - [extension (#+ Nullary Unary Binary Trinary - nullary unary binary trinary)] + [extension {"+" [Nullary Unary Binary Trinary + nullary unary binary trinary]}] ["." reference] - ["//" r #_ - ["#." runtime (#+ Operation Phase Handler Bundle - with_vars)]]] - ["/#" // #_ + ["//" r "_" + ["#." runtime {"+" [Operation Phase Handler Bundle + with_vars]}]]] + ["/#" // "_" ["." generation] - ["//#" /// #_ + ["//#" /// "_" ["#." phase]]]]]]) (def: .public bundle diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby.lux index 42518bd79..e638baf9e 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby.lux @@ -1,16 +1,16 @@ (.module: [library - [lux #* + [lux "*" [data [collection ["." dictionary]]]]] - ["." / #_ + ["." / "_" ["#." common] ["#." host] [//// [generation [ruby - [runtime (#+ Bundle)]]]]]) + [runtime {"+" [Bundle]}]]]]]) (def: .public bundle Bundle diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby/common.lux index d55550954..1fe6627fa 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby/common.lux @@ -1,17 +1,17 @@ (.module: [library - [lux #* + [lux "*" [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control ["." function] ["." try] ["<>" parser - ["<s>" synthesis (#+ Parser)]]] + ["<s>" synthesis {"+" [Parser]}]]] [data ["." product] ["." text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." dictionary] ["." list ("#\." functor mix)]]] @@ -19,16 +19,16 @@ [number ["f" frac]]] [target - ["_" ruby (#+ Expression Statement)]]]] - ["." //// #_ + ["_" ruby {"+" [Expression Statement]}]]]] + ["." //// "_" ["/" bundle] - ["/#" // #_ + ["/#" // "_" ["." extension] [generation - [extension (#+ Nullary Unary Binary Trinary - nullary unary binary trinary)] - ["//" ruby #_ - ["#." runtime (#+ Operation Phase Phase! Handler Bundle Generator)] + [extension {"+" [Nullary Unary Binary Trinary + nullary unary binary trinary]}] + ["//" ruby "_" + ["#." runtime {"+" [Operation Phase Phase! Handler Bundle Generator]}] ["#." primitive] ["#." structure] ["#." reference] @@ -36,7 +36,7 @@ ["#." case] ["#." loop]]] [// - ["." synthesis (#+ %synthesis)] + ["." synthesis {"+" [%synthesis]}] ["." generation] [/// ["#" phase ("#\." monad)]]]]]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby/host.lux index 98edb6d30..db6864e97 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby/host.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby/host.lux @@ -1,36 +1,36 @@ (.module: [library - [lux #* + [lux "*" [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control ["." function] ["<>" parser - ["<s>" synthesis (#+ Parser)]]] + ["<s>" synthesis {"+" [Parser]}]]] [data [collection ["." dictionary] ["." list]] [text - ["%" format (#+ format)]]] + ["%" format {"+" [format]}]]] [target - ["_" ruby (#+ Var Expression)]]]] - ["." // #_ - ["#." common (#+ custom)] - ["//#" /// #_ + ["_" ruby {"+" [Var Expression]}]]]] + ["." // "_" + ["#." common {"+" [custom]}] + ["//#" /// "_" ["/" bundle] - ["/#" // #_ + ["/#" // "_" ["." extension] [generation - [extension (#+ Nullary Unary Binary Trinary - nullary unary binary trinary)] + [extension {"+" [Nullary Unary Binary Trinary + nullary unary binary trinary]}] ["." reference] - ["//" ruby #_ - ["#." runtime (#+ Operation Phase Handler Bundle - with_vars)]]] - ["/#" // #_ + ["//" ruby "_" + ["#." runtime {"+" [Operation Phase Handler Bundle + with_vars]}]]] + ["/#" // "_" ["." generation] - ["//#" /// #_ + ["//#" /// "_" ["#." phase]]]]]]) (def: (array::new [size]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme.lux index 2fd37b5d7..83b5f4a56 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme.lux @@ -1,16 +1,16 @@ (.module: [library - [lux #* + [lux "*" [data [collection ["." dictionary]]]]] - ["." / #_ + ["." / "_" ["#." common] ["#." host] [//// [generation [scheme - [runtime (#+ Bundle)]]]]]) + [runtime {"+" [Bundle]}]]]]]) (def: .public bundle Bundle diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme/common.lux index e51c2b542..228c6e4f1 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme/common.lux @@ -1,17 +1,17 @@ (.module: [library - [lux #* + [lux "*" [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control ["." function] ["." try] ["<>" parser - ["<s>" synthesis (#+ Parser)]]] + ["<s>" synthesis {"+" [Parser]}]]] [data ["." product] ["." text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." dictionary] ["." set] @@ -20,20 +20,20 @@ [number ["f" frac]]] ["@" target - ["_" scheme (#+ Expression)]]]] - ["." //// #_ + ["_" scheme {"+" [Expression]}]]]] + ["." //// "_" ["/" bundle] - ["/#" // #_ + ["/#" // "_" ["." extension] [generation - [extension (#+ Nullary Unary Binary Trinary - nullary unary binary trinary)] + [extension {"+" [Nullary Unary Binary Trinary + nullary unary binary trinary]}] ["." reference] - ["//" scheme #_ - ["#." runtime (#+ Operation Phase Handler Bundle Generator)] + ["//" scheme "_" + ["#." runtime {"+" [Operation Phase Handler Bundle Generator]}] ["#." case]]] [// - ["." synthesis (#+ %synthesis)] + ["." synthesis {"+" [%synthesis]}] ["." generation] [/// ["#" phase]]]]]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme/host.lux index cd2b46e13..dc7215b53 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme/host.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme/host.lux @@ -1,36 +1,36 @@ (.module: [library - [lux #* + [lux "*" [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control ["." function] ["<>" parser - ["<s>" synthesis (#+ Parser)]]] + ["<s>" synthesis {"+" [Parser]}]]] [data [collection ["." dictionary] ["." list]] [text - ["%" format (#+ format)]]] + ["%" format {"+" [format]}]]] [target - ["_" scheme (#+ Var Expression)]]]] - ["." // #_ - ["#." common (#+ custom)] - ["//#" /// #_ + ["_" scheme {"+" [Var Expression]}]]]] + ["." // "_" + ["#." common {"+" [custom]}] + ["//#" /// "_" ["/" bundle] - ["/#" // #_ + ["/#" // "_" ["." extension] [generation - [extension (#+ Nullary Unary Binary Trinary - nullary unary binary trinary)] + [extension {"+" [Nullary Unary Binary Trinary + nullary unary binary trinary]}] ["." reference] - ["//" scheme #_ - ["#." runtime (#+ Operation Phase Handler Bundle - with_vars)]]] - ["/#" // #_ + ["//" scheme "_" + ["#." runtime {"+" [Operation Phase Handler Bundle + with_vars]}]]] + ["/#" // "_" ["." generation] - ["//#" /// #_ + ["//#" /// "_" ["#." phase]]]]]]) (def: (array::new size) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/synthesis.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/synthesis.lux index 557dac7ac..69be9bd6e 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/synthesis.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/synthesis.lux @@ -1,10 +1,10 @@ (.module: [library - [lux #*]] + [lux "*"]] [// ["." bundle] [/// - [synthesis (#+ Bundle)]]]) + [synthesis {"+" [Bundle]}]]]) (def: .public bundle Bundle diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp.lux index 3a0578db1..00f493422 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp.lux @@ -1,27 +1,27 @@ (.module: [library - [lux #* + [lux "*" [abstract - [monad (#+ do)]]]] - ["." / #_ - [runtime (#+ Phase)] + [monad {"+" [do]}]]]] + ["." / "_" + [runtime {"+" [Phase]}] ["#." primitive] ["#." structure] ["#." reference] ["#." case] ["#." loop] ["#." function] - ["/#" // #_ + ["/#" // "_" ["#." reference] - ["/#" // #_ + ["/#" // "_" ["#." extension] - ["/#" // #_ - [analysis (#+)] + ["/#" // "_" + [analysis {"+" []}] ["#." synthesis] - ["//#" /// #_ + ["//#" /// "_" ["#." phase ("#\." monad)] - [reference (#+) - [variable (#+)]]]]]]]) + [reference {"+" []} + [variable {"+" []}]]]]]]]) (def: .public (generate archive synthesis) Phase diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/case.lux index 8577bb82a..67b9060ad 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/case.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/case.lux @@ -1,13 +1,13 @@ (.module: [library - [lux (#- case let if) + [lux {"-" [case let if]} [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control - ["." exception (#+ exception:)]] + ["." exception {"+" [exception:]}]] [data ["." text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." list ("#\." functor mix monoid)] ["." set]]] @@ -15,25 +15,25 @@ [number ["n" nat]]] [target - ["_" common_lisp (#+ Expression Var/1)]]]] - ["." // #_ - ["#." runtime (#+ Operation Phase Generator)] + ["_" common_lisp {"+" [Expression Var/1]}]]]] + ["." // "_" + ["#." runtime {"+" [Operation Phase Generator]}] ["#." reference] ["#." primitive] - ["/#" // #_ + ["/#" // "_" ["#." reference] - ["/#" // #_ - ["#." synthesis #_ + ["/#" // "_" + ["#." synthesis "_" ["#/." case]] - ["/#" // #_ - ["#." synthesis (#+ Member Synthesis Path)] + ["/#" // "_" + ["#." synthesis {"+" [Member Synthesis Path]}] ["#." generation] - ["//#" /// #_ + ["//#" /// "_" [reference - ["#." variable (#+ Register)]] + ["#." variable {"+" [Register]}]] ["#." phase ("#\." monad)] [meta - [archive (#+ Archive)]]]]]]]) + [archive {"+" [Archive]}]]]]]]]) (def: .public register (-> Register Var/1) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/extension.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/extension.lux index 17052fb88..6e255664b 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/extension.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/extension.lux @@ -1,11 +1,11 @@ (.module: [library - [lux #* + [lux "*" [data [collection ["." dictionary]]]]] [// - [runtime (#+ Bundle)]] + [runtime {"+" [Bundle]}]] [/ ["." common]]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/extension/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/extension/common.lux index c4b5b3764..ec5baaf7f 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/extension/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/extension/common.lux @@ -1,8 +1,8 @@ (.module: [library - [lux #* + [lux "*" [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control ["." function]] [data @@ -12,13 +12,13 @@ [collection ["." dictionary]]] [target - ["_" common_lisp (#+ Expression)]]]] - ["." /// #_ - ["#." runtime (#+ Operation Phase Handler Bundle)] + ["_" common_lisp {"+" [Expression]}]]]] + ["." /// "_" + ["#." runtime {"+" [Operation Phase Handler Bundle]}] ["#." primitive] [// - [extension (#+ Nullary Unary Binary Trinary - nullary unary binary trinary)] + [extension {"+" [Nullary Unary Binary Trinary + nullary unary binary trinary]}] [// [extension ["." bundle]]]]]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/function.lux index 9a2b543d9..b1be4e914 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/function.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/function.lux @@ -1,33 +1,33 @@ (.module: [library - [lux (#- function) + [lux {"-" [function]} [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control pipe] [data ["." product] [text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." list ("#\." functor)]]] [target - ["_" common_lisp (#+ Expression Var/1)]]]] - ["." // #_ - ["#." runtime (#+ Operation Phase Generator)] + ["_" common_lisp {"+" [Expression Var/1]}]]]] + ["." // "_" + ["#." runtime {"+" [Operation Phase Generator]}] ["#." reference] ["#." case] - ["/#" // #_ + ["/#" // "_" ["#." reference] - ["//#" /// #_ - [analysis (#+ Variant Tuple Abstraction Application Analysis)] - [synthesis (#+ Synthesis)] - ["#." generation (#+ Context)] - ["//#" /// #_ - [arity (#+ Arity)] + ["//#" /// "_" + [analysis {"+" [Variant Tuple Abstraction Application Analysis]}] + [synthesis {"+" [Synthesis]}] + ["#." generation {"+" [Context]}] + ["//#" /// "_" + [arity {"+" [Arity]}] ["#." phase ("#\." monad)] [reference - [variable (#+ Register Variable)]]]]]]) + [variable {"+" [Register Variable]}]]]]]]) (def: .public (apply expression archive [functionS argsS+]) (Generator (Application Synthesis)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/loop.lux index 592733e5e..9d1a27f7a 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/loop.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/loop.lux @@ -1,36 +1,36 @@ (.module: [library - [lux (#- Scope) + [lux {"-" [Scope]} [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [data ["." product] [text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." list ("#\." functor)]]] [math [number ["n" nat]]] [target - ["_" common_lisp (#+ Expression)]]]] - ["." // #_ - [runtime (#+ Operation Phase Generator)] + ["_" common_lisp {"+" [Expression]}]]]] + ["." // "_" + [runtime {"+" [Operation Phase Generator]}] ["#." case] - ["/#" // #_ + ["/#" // "_" ["#." reference] - ["/#" // #_ + ["/#" // "_" [synthesis ["." case]] - ["/#" // #_ - ["."synthesis (#+ Scope Synthesis)] + ["/#" // "_" + ["."synthesis {"+" [Scope Synthesis]}] ["#." generation] - ["//#" /// #_ + ["//#" /// "_" ["#." phase] [meta - [archive (#+ Archive)]] + [archive {"+" [Archive]}]] [reference - [variable (#+ Register)]]]]]]]) + [variable {"+" [Register]}]]]]]]]) (def: .public (scope expression archive [start initsS+ bodyS]) (Generator (Scope Synthesis)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/primitive.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/primitive.lux index c3417e461..33c46df80 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/primitive.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/primitive.lux @@ -1,8 +1,8 @@ (.module: [library - [lux (#- i64) + [lux {"-" [i64]} [target - ["_" common_lisp (#+ Expression)]]]]) + ["_" common_lisp {"+" [Expression]}]]]]) (def: .public bit (-> Bit (Expression Any)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/reference.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/reference.lux index a12a8c590..d7ecb7abd 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/reference.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/reference.lux @@ -1,10 +1,10 @@ (.module: [library - [lux #* + [lux "*" [target - ["_" common_lisp (#+ Expression)]]]] + ["_" common_lisp {"+" [Expression]}]]]] [/// - [reference (#+ System)]]) + [reference {"+" [System]}]]) (implementation: .public system (System (Expression Any)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/runtime.lux index c478118de..c891ba166 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/runtime.lux @@ -1,9 +1,9 @@ (.module: [library - [lux (#- Location) + [lux {"-" [Location]} ["." meta] [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control ["." function] ["<>" parser @@ -11,32 +11,32 @@ [data ["." product] ["." text ("#\." hash) - ["%" format (#+ format)] + ["%" format {"+" [format]}] ["." encoding]] [collection ["." list ("#\." functor monoid)] ["." row]]] ["." macro - [syntax (#+ syntax:)] + [syntax {"+" [syntax:]}] ["." code]] [math - [number (#+ hex) + [number {"+" [hex]} ["." i64]]] ["@" target - ["_" common_lisp (#+ Expression Computation Literal)]]]] - ["." /// #_ + ["_" common_lisp {"+" [Expression Computation Literal]}]]]] + ["." /// "_" ["#." reference] - ["//#" /// #_ - [analysis (#+ Variant)] - ["#." synthesis (#+ Synthesis)] + ["//#" /// "_" + [analysis {"+" [Variant]}] + ["#." synthesis {"+" [Synthesis]}] ["#." generation] ["//#" /// ["#." phase] [reference - [variable (#+ Register)]] + [variable {"+" [Register]}]] [meta - [archive (#+ Output Archive) - ["." artifact (#+ Registry)]]]]]]) + [archive {"+" [Output Archive]} + ["." artifact {"+" [Registry]}]]]]]]) (def: module_id 0) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/structure.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/structure.lux index c8f9230a3..d370aca6a 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/structure.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/structure.lux @@ -1,17 +1,17 @@ (.module: [library - [lux #* + [lux "*" [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [target - ["_" common_lisp (#+ Expression)]]]] - ["." // #_ - ["#." runtime (#+ Operation Phase Generator)] + ["_" common_lisp {"+" [Expression]}]]]] + ["." // "_" + ["#." runtime {"+" [Operation Phase Generator]}] ["#." primitive] - ["///#" //// #_ - [analysis (#+ Variant Tuple)] - ["#." synthesis (#+ Synthesis)] - ["//#" /// #_ + ["///#" //// "_" + [analysis {"+" [Variant Tuple]}] + ["#." synthesis {"+" [Synthesis]}] + ["//#" /// "_" ["#." phase ("#\." monad)]]]]) (def: .public (tuple expression archive elemsS+) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/extension.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/extension.lux index 5c5e43e8b..434c0836a 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/extension.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/extension.lux @@ -1,8 +1,8 @@ (.module: [library - [lux #* + [lux "*" [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control [parser ["<.>" code]]] @@ -10,13 +10,13 @@ [collection ["." list ("#\." functor)]]] ["." meta] - ["." macro (#+ with_identifiers) + ["." macro {"+" [with_identifiers]} ["." code] - [syntax (#+ syntax:)]]]] - ["." /// #_ + [syntax {"+" [syntax:]}]]]] + ["." /// "_" ["#." extension] [// - [synthesis (#+ Synthesis)] + [synthesis {"+" [Synthesis]}] ["." generation] [/// ["#" phase]]]]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js.lux index c240161ee..c37946c77 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js.lux @@ -1,34 +1,34 @@ (.module: [library - [lux #* + [lux "*" [abstract - [monad (#+ do)]] + [monad {"+" [do]}]] [control - ["." exception (#+ exception:)]] + ["." exception {"+" [exception:]}]] [target ["_" js]]]] - ["." / #_ - [runtime (#+ Phase Phase!)] + ["." / "_" + [runtime {"+" [Phase Phase!]}] ["#." primitive] ["#." structure] ["#." reference] ["#." case] ["#." loop] ["#." function] - ["/#" // #_ + ["/#" // "_" ["#." reference] - ["/#" // #_ + ["/#" // "_" ["#." extension [generation [js ["#/." common]]]] - ["/#" // #_ - [analysis (#+)] + ["/#" // "_" + [analysis {"+" []}] ["." synthesis] - ["//#" /// #_ + ["//#" /// "_" ["#." phase ("#\." monad)] - [reference (#+) - [variable (#+)]]]]]]]) + [reference {"+" []} + [variable {"+" []}]]]]]]]) (exception: .public cannot_recur_as_an_expression) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/case.lux index 2b80bcc35..7194bb0e6 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/case.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/case.lux @@ -1,8 +1,8 @@ (.module: [library - [lux (#- case let if) + [lux {"-" [case let if]} [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control ["." maybe]] [data @@ -13,24 +13,24 @@ [number ["n" nat]]] [target - ["_" js (#+ Expression Computation Var Statement)]]]] - ["." // #_ - ["#." runtime (#+ Operation Phase Phase! Generator Generator!)] + ["_" js {"+" [Expression Computation Var Statement]}]]]] + ["." // "_" + ["#." runtime {"+" [Operation Phase Phase! Generator Generator!]}] ["#." reference] ["#." primitive] - ["/#" // #_ + ["/#" // "_" ["#." reference] - ["/#" // #_ - ["#." synthesis #_ + ["/#" // "_" + ["#." synthesis "_" ["#/." case]] - ["/#" // #_ - ["#." synthesis (#+ Member Synthesis Path)] - ["//#" /// #_ + ["/#" // "_" + ["#." synthesis {"+" [Member Synthesis Path]}] + ["//#" /// "_" [reference - [variable (#+ Register)]] + [variable {"+" [Register]}]] ["#." phase ("#\." monad)] [meta - [archive (#+ Archive)]]]]]]]) + [archive {"+" [Archive]}]]]]]]]) (def: .public register (-> Register Var) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/function.lux index 11a0b5640..819cb2769 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/function.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/function.lux @@ -1,31 +1,31 @@ (.module: [library - [lux (#- Variant Tuple function) + [lux {"-" [Variant Tuple function]} [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [data ["." product] [text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." list ("#\." functor mix)]]] [target - ["_" js (#+ Expression Computation Var Statement)]]]] - ["." // #_ - ["#." runtime (#+ Operation Phase Phase! Generator)] + ["_" js {"+" [Expression Computation Var Statement]}]]]] + ["." // "_" + ["#." runtime {"+" [Operation Phase Phase! Generator]}] ["#." reference] ["#." case] - ["/#" // #_ + ["/#" // "_" ["#." reference] - ["//#" /// #_ - [analysis (#+ Variant Tuple Abstraction Application Analysis)] - [synthesis (#+ Synthesis)] - ["#." generation (#+ Context)] - ["//#" /// #_ - [arity (#+ Arity)] + ["//#" /// "_" + [analysis {"+" [Variant Tuple Abstraction Application Analysis]}] + [synthesis {"+" [Synthesis]}] + ["#." generation {"+" [Context]}] + ["//#" /// "_" + [arity {"+" [Arity]}] ["#." phase ("#\." monad)] [reference - [variable (#+ Register Variable)]]]]]]) + [variable {"+" [Register Variable]}]]]]]]) (def: .public (apply expression archive [functionS argsS+]) (Generator (Application Synthesis)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/loop.lux index 7946e7b12..2e2e21522 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/loop.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/loop.lux @@ -1,29 +1,29 @@ (.module: [library - [lux (#- Scope) + [lux {"-" [Scope]} [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [data ["." product] ["." text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." list ("#\." functor mix)]]] [math [number ["n" nat]]] [target - ["_" js (#+ Computation Var Expression Statement)]]]] - ["." // #_ - [runtime (#+ Operation Phase Phase! Generator Generator!)] + ["_" js {"+" [Computation Var Expression Statement]}]]]] + ["." // "_" + [runtime {"+" [Operation Phase Phase! Generator Generator!]}] ["#." case] - ["///#" //// #_ - [synthesis (#+ Scope Synthesis)] + ["///#" //// "_" + [synthesis {"+" [Scope Synthesis]}] ["#." generation] - ["//#" /// #_ + ["//#" /// "_" ["#." phase] [reference - [variable (#+ Register)]]]]]) + [variable {"+" [Register]}]]]]]) (def: @scope (-> Nat Text) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/primitive.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/primitive.lux index 711a72275..ba2d683f0 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/primitive.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/primitive.lux @@ -1,9 +1,9 @@ (.module: [library - [lux (#- i64) + [lux {"-" [i64]} [target - ["_" js (#+ Computation)]]]] - ["." // #_ + ["_" js {"+" [Computation]}]]]] + ["." // "_" ["#." runtime]]) (def: .public bit diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/reference.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/reference.lux index 646852129..c2bf71750 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/reference.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/reference.lux @@ -1,10 +1,10 @@ (.module: [library - [lux #* + [lux "*" [target - ["_" js (#+ Expression)]]]] + ["_" js {"+" [Expression]}]]]] [/// - [reference (#+ System)]]) + [reference {"+" [System]}]]) (implementation: .public system (System Expression) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux index b76af26be..0263cb579 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux @@ -1,9 +1,9 @@ (.module: [library - [lux (#- i64) + [lux {"-" [i64]} ["." meta] [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control ["." function] ["<>" parser @@ -11,37 +11,37 @@ [data ["." product] ["." text ("#\." hash) - ["%" format (#+ format)] + ["%" format {"+" [format]}] [encoding ["." utf8]]] [collection ["." list ("#\." functor)] ["." row]]] ["." macro - [syntax (#+ syntax:)] + [syntax {"+" [syntax:]}] ["." code]] [math - [number (#+ hex) + [number {"+" [hex]} ["." i64]]] [target - ["_" js (#+ Expression Var Computation Statement)]] + ["_" js {"+" [Expression Var Computation Statement]}]] [tool [compiler [language [lux ["$" version]]]]]]] - ["." /// #_ + ["." /// "_" ["#." reference] - ["//#" /// #_ - ["#." synthesis (#+ Synthesis)] + ["//#" /// "_" + ["#." synthesis {"+" [Synthesis]}] ["#." generation] ["//#" /// ["#." phase] [reference - [variable (#+ Register)]] + [variable {"+" [Register]}]] [meta - [archive (#+ Output Archive) - ["." artifact (#+ Registry)]]]]]]) + [archive {"+" [Output Archive]} + ["." artifact {"+" [Registry]}]]]]]]) (template [<name> <base>] [(type: .public <name> diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/structure.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/structure.lux index 8b91f6d95..c92df3024 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/structure.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/structure.lux @@ -1,16 +1,16 @@ (.module: [library - [lux (#- Variant Tuple) + [lux {"-" [Variant Tuple]} [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [target - ["_" js (#+ Expression)]]]] - ["." // #_ - ["#." runtime (#+ Operation Phase Generator)] + ["_" js {"+" [Expression]}]]]] + ["." // "_" + ["#." runtime {"+" [Operation Phase Generator]}] ["#." primitive] - ["///#" //// #_ - [analysis (#+ Variant Tuple)] - ["#." synthesis (#+ Synthesis)] + ["///#" //// "_" + [analysis {"+" [Variant Tuple]}] + ["#." synthesis {"+" [Synthesis]}] ["//#" /// ["#." phase ("#\." monad)]]]]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm.lux index bece6d582..07045ccdd 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm.lux @@ -1,17 +1,17 @@ (.module: [library - [lux #* + [lux "*" [abstract - [monad (#+ do)]]]] - ["." / #_ - [runtime (#+ Phase)] + [monad {"+" [do]}]]]] + ["." / "_" + [runtime {"+" [Phase]}] ["#." primitive] ["#." structure] ["#." reference] ["#." function] ["#." case] ["#." loop] - ["//#" /// #_ + ["//#" /// "_" ["#." extension] [// ["." synthesis] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/case.lux index 928fbb101..61f9ce83b 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/case.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/case.lux @@ -1,8 +1,8 @@ (.module: [library - [lux (#- Type if let case int) + [lux {"-" [Type if let case int]} [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control ["." function]] [data @@ -13,21 +13,21 @@ ["." list ("#\." mix)]]] [target [jvm - ["_" bytecode (#+ Label Bytecode) ("#\." monad)] - ["." type (#+ Type) - [category (#+ Method)]]]]]] - ["." // #_ + ["_" bytecode {"+" [Label Bytecode]} ("#\." monad)] + ["." type {"+" [Type]} + [category {"+" [Method]}]]]]]] + ["." // "_" ["#." type] - ["#." runtime (#+ Operation Phase Generator)] + ["#." runtime {"+" [Operation Phase Generator]}] ["#." value] ["#." structure] [//// - ["." synthesis (#+ Path Synthesis)] + ["." synthesis {"+" [Path Synthesis]}] ["." generation] [/// ["." phase ("operation\." monad)] [reference - [variable (#+ Register)]]]]]) + [variable {"+" [Register]}]]]]]) (def: equals_name "equals") diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/debug.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/debug.lux index d830d478f..d4a2c34f4 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/debug.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/debug.lux @@ -1,17 +1,17 @@ (.module: [library - [lux #* + [lux "*" [abstract - [monad (#+ do)]] + [monad {"+" [do]}]] [control - ["." io (#+ IO)] - ["." try (#+ Try)]] + ["." io {"+" [IO]}] + ["." try {"+" [Try]}]] [data - [binary (#+ Binary)] + [binary {"+" [Binary]}] [text - ["%" format (#+ format)]]] + ["%" format {"+" [format]}]]] [world - ["." file (#+ File)]]]]) + ["." file {"+" [File]}]]]]) (def: extension ".class") diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function.lux index f43a360d2..961291c53 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function.lux @@ -1,8 +1,8 @@ (.module: [library - [lux (#- Type) + [lux {"-" [Type]} [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [data [number ["." i32] @@ -10,29 +10,29 @@ [collection ["." list ("#\." monoid functor)] ["." row]] - ["." format #_ + ["." format "_" ["#" binary]]] [target [jvm ["." version] - ["." modifier (#+ Modifier) ("#\." monoid)] - ["." field (#+ Field)] - ["." method (#+ Method)] - ["_" bytecode (#+ Label Bytecode) ("#\." monad)] - ["." class (#+ Class)] - ["." type (#+ Type) - [category (#+ Return' Value')] + ["." modifier {"+" [Modifier]} ("#\." monoid)] + ["." field {"+" [Field]}] + ["." method {"+" [Method]}] + ["_" bytecode {"+" [Label Bytecode]} ("#\." monad)] + ["." class {"+" [Class]}] + ["." type {"+" [Type]} + [category {"+" [Return' Value']}] ["." reflection]] ["." constant - [pool (#+ Resource)]] + [pool {"+" [Resource]}]] [encoding - ["." name (#+ External Internal)] + ["." name {"+" [External Internal]}] ["." unsigned]]]] [tool [compiler [meta - ["." archive (#+ Archive)]]]]]] - ["." / #_ + ["." archive {"+" [Archive]}]]]]]] + ["." / "_" ["#." abstract] [field [constant @@ -46,17 +46,17 @@ ["#." implementation] ["#." reset] ["#." apply]] - ["/#" // #_ - ["#." runtime (#+ Operation Phase Generator)] + ["/#" // "_" + ["#." runtime {"+" [Operation Phase Generator]}] [//// - [analysis (#+ Environment)] - [synthesis (#+ Synthesis Abstraction Apply)] + [analysis {"+" [Environment]}] + [synthesis {"+" [Synthesis Abstraction Apply]}] ["." generation] [/// - ["." arity (#+ Arity)] + ["." arity {"+" [Arity]}] ["." phase] [reference - [variable (#+ Register)]]]]]]) + [variable {"+" [Register]}]]]]]]) (def: .public (with generate archive @begin class environment arity body) (-> Phase Archive Label External (Environment Synthesis) Arity (Bytecode Any) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/abstract.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/abstract.lux index 04e3d4cda..653af8aaf 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/abstract.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/abstract.lux @@ -1,13 +1,13 @@ (.module: [library - [lux (#- Type) + [lux {"-" [Type]} [data [text ["%" format]]] [target [jvm - ["." type (#+ Type) - [category (#+ Method)]]]]]] + ["." type {"+" [Type]} + [category {"+" [Method]}]]]]]] [// [field [constant diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/constant.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/constant.lux index 47ab7df90..abbf547d4 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/constant.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/constant.lux @@ -1,17 +1,17 @@ (.module: [library - [lux (#- Type type) + [lux {"-" [Type type]} [data [collection ["." row]]] [target [jvm - ["." field (#+ Field)] - ["." modifier (#+ Modifier) ("#\." monoid)] - [type (#+ Type) - [category (#+ Value)]] + ["." field {"+" [Field]}] + ["." modifier {"+" [Modifier]} ("#\." monoid)] + [type {"+" [Type]} + [category {"+" [Value]}]] [constant - [pool (#+ Resource)]]]]]]) + [pool {"+" [Resource]}]]]]]]) (def: modifier (Modifier Field) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/constant/arity.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/constant/arity.lux index 7bb5a7f15..365e68c2c 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/constant/arity.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/constant/arity.lux @@ -1,15 +1,15 @@ (.module: [library - [lux (#- type) + [lux {"-" [type]} [target [jvm ["." type] - ["." field (#+ Field)] + ["." field {"+" [Field]}] [constant - [pool (#+ Resource)]]]]]] + [pool {"+" [Resource]}]]]]]] ["." // [///////// - [arity (#+ Arity)]]]) + [arity {"+" [Arity]}]]]) (def: .public name "arity") (def: .public type type.int) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable.lux index b843aa13a..7a8493260 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable.lux @@ -1,25 +1,25 @@ (.module: [library - [lux (#- Type type) + [lux {"-" [Type type]} [data [collection ["." list ("#\." functor)] ["." row]]] [target [jvm - ["." modifier (#+ Modifier) ("#\." monoid)] - ["." field (#+ Field)] - ["_" bytecode (#+ Bytecode)] - [type (#+ Type) - [category (#+ Value Class)]] + ["." modifier {"+" [Modifier]} ("#\." monoid)] + ["." field {"+" [Field]}] + ["_" bytecode {"+" [Bytecode]}] + [type {"+" [Type]} + [category {"+" [Value Class]}]] [constant - [pool (#+ Resource)]]]]]] - ["." //// #_ + [pool {"+" [Resource]}]]]]]] + ["." //// "_" ["#." type] ["#." reference] [////// [reference - [variable (#+ Register)]]]]) + [variable {"+" [Register]}]]]]) (def: .public type ////type.value) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable/count.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable/count.lux index 1ec854f71..f2c1e2189 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable/count.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable/count.lux @@ -1,16 +1,16 @@ (.module: [library - [lux (#- type) + [lux {"-" [type]} [control ["." try]] [target [jvm - ["_" bytecode (#+ Bytecode)] + ["_" bytecode {"+" [Bytecode]}] ["." type] [encoding - [name (#+ External)] + [name {"+" [External]}] ["." signed]]]]]] - ["." //// #_ + ["." //// "_" ["#." abstract]]) (def: .public field "partials") diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable/foreign.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable/foreign.lux index 1fb4d7d86..53a486d88 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable/foreign.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable/foreign.lux @@ -1,27 +1,27 @@ (.module: [library - [lux (#- Type) + [lux {"-" [Type]} [data [collection ["." list] ["." row]]] [target [jvm - ["_" bytecode (#+ Bytecode)] - ["." field (#+ Field)] + ["_" bytecode {"+" [Bytecode]}] + ["." field {"+" [Field]}] [constant - [pool (#+ Resource)]] - [type (#+ Type) - [category (#+ Value Class)]]]]]] + [pool {"+" [Resource]}]] + [type {"+" [Type]} + [category {"+" [Value Class]}]]]]]] ["." // - ["///#" //// #_ + ["///#" //// "_" ["#." reference] [//// - [analysis (#+ Environment)] - [synthesis (#+ Synthesis)] + [analysis {"+" [Environment]}] + [synthesis {"+" [Synthesis]}] [/// [reference - [variable (#+ Register)]]]]]]) + [variable {"+" [Register]}]]]]]]) (def: .public (closure environment) (-> (Environment Synthesis) (List (Type Value))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable/partial.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable/partial.lux index 19dc23779..1755ea7df 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable/partial.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable/partial.lux @@ -1,6 +1,6 @@ (.module: [library - [lux (#- Type) + [lux {"-" [Type]} [abstract ["." monad]] [data @@ -11,24 +11,24 @@ ["." row]]] [target [jvm - ["." field (#+ Field)] - ["_" bytecode (#+ Label Bytecode) ("#\." monad)] - [type (#+ Type) - [category (#+ Class)]] + ["." field {"+" [Field]}] + ["_" bytecode {"+" [Label Bytecode]} ("#\." monad)] + [type {"+" [Type]} + [category {"+" [Class]}]] [constant - [pool (#+ Resource)]]]]]] - ["." / #_ + [pool {"+" [Resource]}]]]]]] + ["." / "_" ["#." count] ["/#" // - ["/#" // #_ + ["/#" // "_" [constant ["#." arity]] - ["//#" /// #_ + ["//#" /// "_" ["#." reference] [////// - ["." arity (#+ Arity)] + ["." arity {"+" [Arity]}] [reference - [variable (#+ Register)]]]]]]]) + [variable {"+" [Register]}]]]]]]]) (def: .public (initial amount) (-> Nat (Bytecode Any)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method.lux index 802592b0d..6463a0983 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method.lux @@ -1,10 +1,10 @@ (.module: [library - [lux #* + [lux "*" [target [jvm - ["." modifier (#+ Modifier) ("#\." monoid)] - ["." method (#+ Method)]]]]]) + ["." modifier {"+" [Modifier]} ("#\." monoid)] + ["." method {"+" [Method]}]]]]]) (def: .public modifier (Modifier Method) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/apply.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/apply.lux index 0114ef23c..bb78e1b8a 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/apply.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/apply.lux @@ -1,8 +1,8 @@ (.module: [library - [lux (#- Type type) + [lux {"-" [Type type]} [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control ["." try]] [data @@ -14,19 +14,19 @@ ["." list ("#\." monoid functor)]]] [target [jvm - ["_" bytecode (#+ Label Bytecode) ("#\." monad)] - ["." method (#+ Method)] + ["_" bytecode {"+" [Label Bytecode]} ("#\." monad)] + ["." method {"+" [Method]}] [constant - [pool (#+ Resource)]] + [pool {"+" [Resource]}]] [encoding ["." signed]] - ["." type (#+ Type) - ["." category (#+ Class)]]]]]] + ["." type {"+" [Type]} + ["." category {"+" [Class]}]]]]]] ["." // ["#." reset] ["#." implementation] ["#." init] - ["/#" // #_ + ["/#" // "_" ["#." abstract] [field [constant @@ -35,17 +35,17 @@ ["#." partial ["#/." count]] ["#." foreign]]] - ["/#" // #_ + ["/#" // "_" ["#." runtime] ["#." value] ["#." reference] [//// - [analysis (#+ Environment)] - [synthesis (#+ Synthesis)] + [analysis {"+" [Environment]}] + [synthesis {"+" [Synthesis]}] [/// - [arity (#+ Arity)] + [arity {"+" [Arity]}] [reference - [variable (#+ Register)]]]]]]]) + [variable {"+" [Register]}]]]]]]]) (def: (increment by) (-> Nat (Bytecode Any)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/implementation.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/implementation.lux index a6bd0ef6b..12c181265 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/implementation.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/implementation.lux @@ -1,22 +1,22 @@ (.module: [library - [lux (#- Type type) + [lux {"-" [Type type]} [data [collection ["." list]]] [target [jvm - ["." method (#+ Method)] - ["_" bytecode (#+ Label Bytecode)] + ["." method {"+" [Method]}] + ["_" bytecode {"+" [Label Bytecode]}] [constant - [pool (#+ Resource)]] - ["." type (#+ Type) + [pool {"+" [Resource]}]] + ["." type {"+" [Type]} ["." category]]]]]] ["." // - ["//#" /// #_ + ["//#" /// "_" ["#." type] [////// - [arity (#+ Arity)]]]]) + [arity {"+" [Arity]}]]]]) (def: .public name "impl") diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/init.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/init.lux index a9dc55525..05cb6db7d 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/init.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/init.lux @@ -1,6 +1,6 @@ (.module: [library - [lux (#- Type type) + [lux {"-" [Type type]} [abstract ["." monad]] [control @@ -12,17 +12,17 @@ ["." list ("#\." monoid functor)]]] [target [jvm - ["_" bytecode (#+ Bytecode)] - ["." method (#+ Method)] + ["_" bytecode {"+" [Bytecode]}] + ["." method {"+" [Method]}] [encoding ["." unsigned]] [constant - [pool (#+ Resource)]] - ["." type (#+ Type) - ["." category (#+ Class Value)]]]]]] + [pool {"+" [Resource]}]] + ["." type {"+" [Type]} + ["." category {"+" [Class Value]}]]]]]] ["." // ["#." implementation] - ["/#" // #_ + ["/#" // "_" ["#." abstract] [field [constant @@ -30,16 +30,16 @@ [variable ["#." foreign] ["#." partial]]] - ["/#" // #_ + ["/#" // "_" ["#." type] ["#." reference] [//// - [analysis (#+ Environment)] - [synthesis (#+ Synthesis)] + [analysis {"+" [Environment]}] + [synthesis {"+" [Synthesis]}] [/// - ["." arity (#+ Arity)] + ["." arity {"+" [Arity]}] [reference - [variable (#+ Register)]]]]]]]) + [variable {"+" [Register]}]]]]]]]) (def: .public name "<init>") diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/new.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/new.lux index e155c518b..6a80f7b93 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/new.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/new.lux @@ -1,8 +1,8 @@ (.module: [library - [lux (#- Type type) + [lux {"-" [Type type]} [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [data [number ["n" nat]] @@ -10,36 +10,36 @@ ["." list]]] [target [jvm - ["." field (#+ Field)] - ["." method (#+ Method)] - ["_" bytecode (#+ Bytecode)] + ["." field {"+" [Field]}] + ["." method {"+" [Method]}] + ["_" bytecode {"+" [Bytecode]}] ["." constant - [pool (#+ Resource)]] - [type (#+ Type) - ["." category (#+ Class Value Return)]]]] + [pool {"+" [Resource]}]] + [type {"+" [Type]} + ["." category {"+" [Class Value Return]}]]]] [tool [compiler [meta - ["." archive (#+ Archive)]]]]]] + ["." archive {"+" [Archive]}]]]]]] ["." // ["#." init] ["#." implementation] - ["/#" // #_ + ["/#" // "_" [field [constant ["#." arity]] [variable ["#." foreign] ["#." partial]]] - ["/#" // #_ - [runtime (#+ Operation Phase)] + ["/#" // "_" + [runtime {"+" [Operation Phase]}] ["#." value] ["#." reference] [//// - [analysis (#+ Environment)] - [synthesis (#+ Synthesis)] + [analysis {"+" [Environment]}] + [synthesis {"+" [Synthesis]}] [/// - ["." arity (#+ Arity)] + ["." arity {"+" [Arity]}] ["." phase]]]]]]) (def: .public (instance' foreign_setup class environment arity) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/reset.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/reset.lux index ea526c674..502a48fd9 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/reset.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/reset.lux @@ -1,30 +1,30 @@ (.module: [library - [lux (#- Type type) + [lux {"-" [Type type]} [data [collection ["." list ("#\." functor)]]] [target [jvm - ["." method (#+ Method)] - ["_" bytecode (#+ Bytecode)] + ["." method {"+" [Method]}] + ["_" bytecode {"+" [Bytecode]}] [constant - [pool (#+ Resource)]] - ["." type (#+ Type) - ["." category (#+ Class)]]]]]] + [pool {"+" [Resource]}]] + ["." type {"+" [Type]} + ["." category {"+" [Class]}]]]]]] ["." // ["#." new] - ["/#" // #_ + ["/#" // "_" [field [variable ["#." foreign]]] - ["/#" // #_ + ["/#" // "_" ["#." reference] [//// - [analysis (#+ Environment)] - [synthesis (#+ Synthesis)] + [analysis {"+" [Environment]}] + [synthesis {"+" [Synthesis]}] [/// - ["." arity (#+ Arity)]]]]]]) + ["." arity {"+" [Arity]}]]]]]]) (def: .public name "reset") diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/host.lux index e3c07cd49..d61b6ae17 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/host.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/host.lux @@ -1,45 +1,45 @@ (.module: [library - [lux (#- Definition) - ["." ffi (#+ import: do_to object)] + [lux {"-" [Definition]} + ["." ffi {"+" [import: do_to object]}] [abstract - [monad (#+ do)]] + [monad {"+" [do]}]] [control pipe - ["." try (#+ Try)] - ["." exception (#+ exception:)] - ["." io (#+ IO io)] + ["." try {"+" [Try]}] + ["." exception {"+" [exception:]}] + ["." io {"+" [IO io]}] [concurrency - ["." atom (#+ Atom atom)]]] + ["." atom {"+" [Atom atom]}]]] [data - [binary (#+ Binary)] + [binary {"+" [Binary]}] ["." product] ["." text ("#\." hash) - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." array] - ["." dictionary (#+ Dictionary)] + ["." dictionary {"+" [Dictionary]}] ["." row]] - ["." format #_ + ["." format "_" ["#" binary]]] [target [jvm - ["." loader (#+ Library)] - ["_" bytecode (#+ Bytecode)] - ["." modifier (#+ Modifier) ("#\." monoid)] - ["." field (#+ Field)] - ["." method (#+ Method)] + ["." loader {"+" [Library]}] + ["_" bytecode {"+" [Bytecode]}] + ["." modifier {"+" [Modifier]} ("#\." monoid)] + ["." field {"+" [Field]}] + ["." method {"+" [Method]}] ["." version] - ["." class (#+ Class)] - ["." encoding #_ + ["." class {"+" [Class]}] + ["." encoding "_" ["#/." name]] ["." type ["." descriptor]]]] [tool [compiler ["." name]]]]] - ["." // #_ - ["#." runtime (#+ Definition)]] + ["." // "_" + ["#." runtime {"+" [Definition]}]] ) (import: java/lang/reflect/Field diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/loop.lux index b7e934447..38dbca9f1 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/loop.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/loop.lux @@ -1,8 +1,8 @@ (.module: [library - [lux #* + [lux "*" [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control ["." function]] [data @@ -13,17 +13,17 @@ ["." list ("#\." functor)]]] [target [jvm - ["_" bytecode (#+ Label Bytecode) ("#\." monad)]]]]] - ["." // #_ - ["#." runtime (#+ Operation Phase Generator)] + ["_" bytecode {"+" [Label Bytecode]} ("#\." monad)]]]]] + ["." // "_" + ["#." runtime {"+" [Operation Phase Generator]}] ["#." value] [//// - ["." synthesis (#+ Path Synthesis)] + ["." synthesis {"+" [Path Synthesis]}] ["." generation] [/// ["." phase] [reference - [variable (#+ Register)]]]]]) + [variable {"+" [Register]}]]]]]) (def: (invariant? register changeS) (-> Register Synthesis Bit) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/primitive.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/primitive.lux index 3a278c4d4..a2019c13c 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/primitive.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/primitive.lux @@ -1,16 +1,16 @@ (.module: [library - [lux (#- i64) - ["." ffi (#+ import:)] + [lux {"-" [i64]} + ["." ffi {"+" [import:]}] [abstract - [monad (#+ do)]] + [monad {"+" [do]}]] [target [jvm - ["_" bytecode (#+ Bytecode)] + ["_" bytecode {"+" [Bytecode]}] ["." type] [encoding ["." signed]]]]]] - ["." // #_ + ["." // "_" ["#." runtime]]) (def: $Boolean (type.class "java.lang.Boolean" (list))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/program.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/program.lux index 3b1a602da..536b23ca1 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/program.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/program.lux @@ -1,28 +1,28 @@ (.module: [library - [lux (#- Definition) + [lux {"-" [Definition]} [abstract - [monad (#+ do)]] + [monad {"+" [do]}]] [control ["." try]] [data [collection ["." row]] - ["." format #_ + ["." format "_" ["#" binary]]] [target [jvm - ["_" bytecode (#+ Bytecode)] - ["." modifier (#+ Modifier) ("#\." monoid)] - ["." method (#+ Method)] + ["_" bytecode {"+" [Bytecode]}] + ["." modifier {"+" [Modifier]} ("#\." monoid)] + ["." method {"+" [Method]}] ["." version] - ["." class (#+ Class)] + ["." class {"+" [Class]}] [encoding ["." name]] ["." type ["." reflection]]]]]] ["." // - ["#." runtime (#+ Definition)] + ["#." runtime {"+" [Definition]}] ["#." function/abstract]]) (def: .public class diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/reference.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/reference.lux index fb134924a..77717033d 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/reference.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/reference.lux @@ -1,30 +1,30 @@ (.module: [library - [lux #* + [lux "*" [abstract - [monad (#+ do)]] + [monad {"+" [do]}]] [data [text - ["%" format (#+ format)]]] + ["%" format {"+" [format]}]]] [target [jvm - ["_" bytecode (#+ Bytecode)] + ["_" bytecode {"+" [Bytecode]}] ["." type] [encoding ["." unsigned]]]]]] - ["." // #_ - ["#." runtime (#+ Operation)] + ["." // "_" + ["#." runtime {"+" [Operation]}] ["#." value] ["#." type] - ["//#" /// #_ + ["//#" /// "_" [// ["." generation] [/// ["#" phase ("operation\." monad)] [reference - ["." variable (#+ Register Variable)]] + ["." variable {"+" [Register Variable]}]] [meta - [archive (#+ Archive)]]]]]]) + [archive {"+" [Archive]}]]]]]]) (def: .public this (Bytecode Any) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/runtime.lux index 54c3ac8ba..392e36692 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/runtime.lux @@ -1,63 +1,63 @@ (.module: [library - [lux (#- Type Definition Label case false true try) + [lux {"-" [Type Definition Label case false true try]} [abstract - ["." monad (#+ do)] + ["." monad {"+" [do]}] ["." enum]] [control ["." try]] [data - [binary (#+ Binary)] + [binary {"+" [Binary]}] [collection ["." list ("#\." functor)] ["." row]] - ["." format #_ + ["." format "_" ["#" binary]] [text - ["%" format (#+ format)]]] + ["%" format {"+" [format]}]]] [math [number ["n" nat] ["." i32] ["." i64]]] [target - ["." jvm #_ - ["_" bytecode (#+ Label Bytecode)] - ["." modifier (#+ Modifier) ("#\." monoid)] - ["." field (#+ Field)] - ["." method (#+ Method)] + ["." jvm "_" + ["_" bytecode {"+" [Label Bytecode]}] + ["." modifier {"+" [Modifier]} ("#\." monoid)] + ["." field {"+" [Field]}] + ["." method {"+" [Method]}] ["#/." version] - ["." class (#+ Class)] + ["." class {"+" [Class]}] ["." constant - [pool (#+ Resource)]] + [pool {"+" [Resource]}]] [encoding ["." name]] - ["." type (#+ Type) - ["." category (#+ Return' Value')] + ["." type {"+" [Type]} + ["." category {"+" [Return' Value']}] ["." reflection]]]]]] - ["." // #_ + ["." // "_" ["#." type] ["#." value] - ["#." function #_ + ["#." function "_" ["#" abstract] [field [constant ["#/." arity]] [variable ["#/." count]]]] - ["//#" /// #_ + ["//#" /// "_" [// ["." version] ["." synthesis] ["." generation] [/// ["#" phase] - [arity (#+ Arity)] + [arity {"+" [Arity]}] [reference - [variable (#+ Register)]] + [variable {"+" [Register]}]] [meta - [io (#+ lux_context)] - [archive (#+ Archive)]]]]]]) + [io {"+" [lux_context]}] + [archive {"+" [Archive]}]]]]]]) (type: .public Byte_Code Binary) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/structure.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/structure.lux index d260cca20..537ba2a42 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/structure.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/structure.lux @@ -1,8 +1,8 @@ (.module: [library - [lux #* + [lux "*" [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [data [number ["." i32]] @@ -10,16 +10,16 @@ ["." list]]] [target [jvm - ["_" bytecode (#+ Bytecode)] + ["_" bytecode {"+" [Bytecode]}] ["." type] [encoding ["." signed]]]]]] - ["." // #_ - ["#." runtime (#+ Operation Phase Generator)] + ["." // "_" + ["#." runtime {"+" [Operation Phase Generator]}] ["#." primitive] - ["///#" //// #_ - [analysis (#+ Variant Tuple)] - ["#." synthesis (#+ Synthesis)] + ["///#" //// "_" + [analysis {"+" [Variant Tuple]}] + ["#." synthesis {"+" [Synthesis]}] [/// ["." phase]]]]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/type.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/type.lux index 2bc32f589..7ad6dffdd 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/type.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/type.lux @@ -1,6 +1,6 @@ (.module: [library - [lux #* + [lux "*" [target [jvm ["." type]]]]]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/value.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/value.lux index 2eff33115..badc179a7 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/value.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/value.lux @@ -1,11 +1,11 @@ (.module: [library - [lux (#- Type type) + [lux {"-" [Type type]} [target [jvm - ["_" bytecode (#+ Bytecode)] - ["." type (#+ Type) ("#\." equivalence) - [category (#+ Primitive)] + ["_" bytecode {"+" [Bytecode]}] + ["." type {"+" [Type]} ("#\." equivalence) + [category {"+" [Primitive]}] ["." box]]]]]]) (def: .public field "value") diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua.lux index 05fa66ca8..363f94d93 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua.lux @@ -1,34 +1,34 @@ (.module: [library - [lux #* + [lux "*" [abstract - [monad (#+ do)]] + [monad {"+" [do]}]] [control - ["." exception (#+ exception:)]] + ["." exception {"+" [exception:]}]] [target ["_" lua]]]] - ["." / #_ - [runtime (#+ Phase)] + ["." / "_" + [runtime {"+" [Phase]}] ["#." primitive] ["#." structure] ["#." reference] ["#." case] ["#." loop] ["#." function] - ["/#" // #_ + ["/#" // "_" ["#." reference] - ["/#" // #_ + ["/#" // "_" ["#." extension [generation [lua ["#/." common]]]] - ["/#" // #_ - [analysis (#+)] + ["/#" // "_" + [analysis {"+" []}] ["." synthesis] - ["//#" /// #_ + ["//#" /// "_" ["#." phase ("#\." monad)] - [reference (#+) - [variable (#+)]]]]]]]) + [reference {"+" []} + [variable {"+" []}]]]]]]]) (exception: .public cannot_recur_as_an_expression) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/case.lux index c894606cf..200873e3e 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/case.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/case.lux @@ -1,34 +1,34 @@ (.module: [library - [lux (#- case let if) + [lux {"-" [case let if]} [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [data ["." text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." list ("#\." functor mix)] ["." set]]] [target - ["_" lua (#+ Expression Var Statement)]]]] - ["." // #_ - ["#." runtime (#+ Operation Phase Phase! Generator Generator!)] + ["_" lua {"+" [Expression Var Statement]}]]]] + ["." // "_" + ["#." runtime {"+" [Operation Phase Phase! Generator Generator!]}] ["#." reference] ["#." primitive] - ["/#" // #_ + ["/#" // "_" ["#." reference] - ["/#" // #_ - ["#." synthesis #_ + ["/#" // "_" + ["#." synthesis "_" ["#/." case]] - ["/#" // #_ - ["#." synthesis (#+ Member Synthesis Path)] + ["/#" // "_" + ["#." synthesis {"+" [Member Synthesis Path]}] ["#." generation] - ["//#" /// #_ + ["//#" /// "_" [reference - ["#." variable (#+ Register)]] + ["#." variable {"+" [Register]}]] ["#." phase ("#\." monad)] [meta - [archive (#+ Archive)]]]]]]]) + [archive {"+" [Archive]}]]]]]]]) (def: .public register (-> Register Var) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/function.lux index f88bc1d3a..b5680c0bc 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/function.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/function.lux @@ -1,33 +1,33 @@ (.module: [library - [lux (#- Tuple Variant function) + [lux {"-" [Tuple Variant function]} [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control pipe] [data ["." product] [text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." list ("#\." functor mix)]]] [target - ["_" lua (#+ Var Expression Label Statement)]]]] - ["." // #_ - ["#." runtime (#+ Operation Phase Phase! Generator)] + ["_" lua {"+" [Var Expression Label Statement]}]]]] + ["." // "_" + ["#." runtime {"+" [Operation Phase Phase! Generator]}] ["#." reference] ["#." case] - ["/#" // #_ + ["/#" // "_" ["#." reference] - ["//#" /// #_ - [analysis (#+ Variant Tuple Abstraction Application Analysis)] - [synthesis (#+ Synthesis)] - ["#." generation (#+ Context)] - ["//#" /// #_ - [arity (#+ Arity)] + ["//#" /// "_" + [analysis {"+" [Variant Tuple Abstraction Application Analysis]}] + [synthesis {"+" [Synthesis]}] + ["#." generation {"+" [Context]}] + ["//#" /// "_" + [arity {"+" [Arity]}] ["#." phase ("#\." monad)] [reference - [variable (#+ Register Variable)]]]]]]) + [variable {"+" [Register Variable]}]]]]]]) (def: .public (apply expression archive [functionS argsS+]) (Generator (Application Synthesis)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/loop.lux index eb8ff0322..c80077e2a 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/loop.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/loop.lux @@ -1,12 +1,12 @@ (.module: [library - [lux (#- Scope) + [lux {"-" [Scope]} [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [data ["." product] [text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." list ("#\." functor)] ["." set]]] @@ -14,21 +14,21 @@ [number ["n" nat]]] [target - ["_" lua (#+ Var Expression Label Statement)]]]] - ["." // #_ - [runtime (#+ Operation Phase Phase! Generator Generator!)] + ["_" lua {"+" [Var Expression Label Statement]}]]]] + ["." // "_" + [runtime {"+" [Operation Phase Phase! Generator Generator!]}] ["#." case] - ["/#" // #_ + ["/#" // "_" ["#." reference] - ["//#" /// #_ - ["."synthesis (#+ Scope Synthesis)] + ["//#" /// "_" + ["."synthesis {"+" [Scope Synthesis]}] ["#." generation] - ["//#" /// #_ + ["//#" /// "_" ["#." phase] [meta - [archive (#+ Archive)]] + [archive {"+" [Archive]}]] [reference - [variable (#+ Register)]]]]]]) + [variable {"+" [Register]}]]]]]]) (def: @scope (-> Nat Label) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/primitive.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/primitive.lux index f819ca279..d6bd49cd2 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/primitive.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/primitive.lux @@ -1,8 +1,8 @@ (.module: [library - [lux (#- i64) + [lux {"-" [i64]} [target - ["_" lua (#+ Literal)]]]]) + ["_" lua {"+" [Literal]}]]]]) (template [<name> <type> <implementation>] [(def: .public <name> diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/reference.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/reference.lux index b24890947..703e88fe5 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/reference.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/reference.lux @@ -1,10 +1,10 @@ (.module: [library - [lux #* + [lux "*" [target - ["_" lua (#+ Expression)]]]] + ["_" lua {"+" [Expression]}]]]] [/// - [reference (#+ System)]]) + [reference {"+" [System]}]]) (implementation: .public system (System Expression) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/runtime.lux index 0a8cbd859..fcfc383a2 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/runtime.lux @@ -1,9 +1,9 @@ (.module: [library - [lux (#- Location) + [lux {"-" [Location]} ["." meta] [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control ["." function] ["<>" parser @@ -11,32 +11,32 @@ [data ["." product] ["." text ("#\." hash) - ["%" format (#+ format)] + ["%" format {"+" [format]}] [encoding ["." utf8]]] [collection ["." list ("#\." functor)] ["." row]]] ["." macro - [syntax (#+ syntax:)] + [syntax {"+" [syntax:]}] ["." code]] [math - [number (#+ hex) + [number {"+" [hex]} ["." i64]]] ["@" target - ["_" lua (#+ Expression Location Var Computation Literal Label Statement)]]]] - ["." /// #_ + ["_" lua {"+" [Expression Location Var Computation Literal Label Statement]}]]]] + ["." /// "_" ["#." reference] - ["//#" /// #_ - ["#." synthesis (#+ Synthesis)] + ["//#" /// "_" + ["#." synthesis {"+" [Synthesis]}] ["#." generation] ["//#" /// ["#." phase] [reference - [variable (#+ Register)]] + [variable {"+" [Register]}]] [meta - [archive (#+ Output Archive) - ["." artifact (#+ Registry)]]]]]]) + [archive {"+" [Output Archive]} + ["." artifact {"+" [Registry]}]]]]]]) (template [<name> <base>] [(type: .public <name> diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/structure.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/structure.lux index ebb503f26..41cf85418 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/structure.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/structure.lux @@ -1,17 +1,17 @@ (.module: [library - [lux (#- Tuple Variant) + [lux {"-" [Tuple Variant]} [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [target - ["_" lua (#+ Expression)]]]] - ["." // #_ - ["#." runtime (#+ Operation Phase Generator)] + ["_" lua {"+" [Expression]}]]]] + ["." // "_" + ["#." runtime {"+" [Operation Phase Generator]}] ["#." primitive] - ["///#" //// #_ - [analysis (#+ Variant Tuple)] - ["#." synthesis (#+ Synthesis)] - ["//#" /// #_ + ["///#" //// "_" + [analysis {"+" [Variant Tuple]}] + ["#." synthesis {"+" [Synthesis]}] + ["//#" /// "_" ["#." phase ("#\." monad)]]]]) (def: .public (tuple generate archive elemsS+) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php.lux index 4364995c7..c6b0decce 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php.lux @@ -1,31 +1,31 @@ (.module: [library - [lux #* + [lux "*" [abstract - [monad (#+ do)]] + [monad {"+" [do]}]] [control - ["." exception (#+ exception:)]] + ["." exception {"+" [exception:]}]] [target ["_" php]]]] - ["." / #_ - [runtime (#+ Phase Phase!)] + ["." / "_" + [runtime {"+" [Phase Phase!]}] ["#." primitive] ["#." structure] ["#." reference] ["#." case] ["#." loop] ["#." function] - ["/#" // #_ + ["/#" // "_" ["#." reference] - ["/#" // #_ + ["/#" // "_" ["#." extension] - ["/#" // #_ - [analysis (#+)] + ["/#" // "_" + [analysis {"+" []}] ["#." synthesis] - ["//#" /// #_ + ["//#" /// "_" ["#." phase ("#\." monad)] - [reference (#+) - [variable (#+)]]]]]]]) + [reference {"+" []} + [variable {"+" []}]]]]]]]) (def: (statement expression archive synthesis) Phase! diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/case.lux index dcd9a3c12..fb3cfed2e 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/case.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/case.lux @@ -1,12 +1,12 @@ (.module: [library - [lux (#- case let if) + [lux {"-" [case let if]} [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [data ["." product] ["." text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." list ("#\." functor mix)] ["." set]]] @@ -14,25 +14,25 @@ [number ["i" int]]] [target - ["_" php (#+ Expression Var Statement)]]]] - ["." // #_ - ["#." runtime (#+ Operation Phase Phase! Generator Generator!)] + ["_" php {"+" [Expression Var Statement]}]]]] + ["." // "_" + ["#." runtime {"+" [Operation Phase Phase! Generator Generator!]}] ["#." reference] ["#." primitive] - ["/#" // #_ + ["/#" // "_" ["#." reference] - ["/#" // #_ - ["#." synthesis #_ + ["/#" // "_" + ["#." synthesis "_" ["#/." case]] - ["/#" // #_ - ["#." synthesis (#+ Member Synthesis Path)] + ["/#" // "_" + ["#." synthesis {"+" [Member Synthesis Path]}] ["#." generation] - ["//#" /// #_ + ["//#" /// "_" [reference - ["#." variable (#+ Register)]] + ["#." variable {"+" [Register]}]] ["#." phase ("#\." monad)] [meta - [archive (#+ Archive)]]]]]]]) + [archive {"+" [Archive]}]]]]]]]) (def: .public register (-> Register Var) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/extension.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/extension.lux index 17052fb88..6e255664b 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/extension.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/extension.lux @@ -1,11 +1,11 @@ (.module: [library - [lux #* + [lux "*" [data [collection ["." dictionary]]]]] [// - [runtime (#+ Bundle)]] + [runtime {"+" [Bundle]}]] [/ ["." common]]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/extension/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/extension/common.lux index c236c3f75..07a9c41ab 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/extension/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/extension/common.lux @@ -1,8 +1,8 @@ (.module: [library - [lux #* + [lux "*" [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control ["." function]] [data @@ -13,13 +13,13 @@ [collection ["." dictionary]]] [target - ["_" php (#+ Expression)]]]] - ["." /// #_ - ["#." runtime (#+ Operation Phase Handler Bundle)] + ["_" php {"+" [Expression]}]]]] + ["." /// "_" + ["#." runtime {"+" [Operation Phase Handler Bundle]}] ["#." primitive] [// - [extension (#+ Nullary Unary Binary Trinary - nullary unary binary trinary)] + [extension {"+" [Nullary Unary Binary Trinary + nullary unary binary trinary]}] [// [extension ["." bundle]]]]]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/function.lux index b68f9a404..273cc581b 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/function.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/function.lux @@ -1,33 +1,33 @@ (.module: [library - [lux (#- Global function) + [lux {"-" [Global function]} [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control pipe] [data ["." product] ["." text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." list ("#\." functor mix)]]] [target - ["_" php (#+ Var Global Expression Argument Label Statement)]]]] - ["." // #_ - ["#." runtime (#+ Operation Phase Phase! Generator)] + ["_" php {"+" [Var Global Expression Argument Label Statement]}]]]] + ["." // "_" + ["#." runtime {"+" [Operation Phase Phase! Generator]}] ["#." reference] ["#." case] - ["/#" // #_ + ["/#" // "_" ["#." reference] - ["//#" /// #_ - [analysis (#+ Variant Tuple Abstraction Application Analysis)] - [synthesis (#+ Synthesis)] - ["#." generation (#+ Context)] - ["//#" /// #_ - [arity (#+ Arity)] + ["//#" /// "_" + [analysis {"+" [Variant Tuple Abstraction Application Analysis]}] + [synthesis {"+" [Synthesis]}] + ["#." generation {"+" [Context]}] + ["//#" /// "_" + [arity {"+" [Arity]}] ["#." phase ("#\." monad)] [reference - [variable (#+ Register Variable)]]]]]]) + [variable {"+" [Register Variable]}]]]]]]) (def: .public (apply expression archive [functionS argsS+]) (Generator (Application Synthesis)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/loop.lux index e513411b3..a9b0731eb 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/loop.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/loop.lux @@ -1,37 +1,37 @@ (.module: [library - [lux (#- Scope) + [lux {"-" [Scope]} [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [data ["." product] ["." text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." list ("#\." functor mix)] - ["." set (#+ Set)]]] + ["." set {"+" [Set]}]]] [math [number ["n" nat]]] [target - ["_" php (#+ Var Expression Label Statement)]]]] - ["." // #_ - [runtime (#+ Operation Phase Phase! Generator Generator!)] + ["_" php {"+" [Var Expression Label Statement]}]]]] + ["." // "_" + [runtime {"+" [Operation Phase Phase! Generator Generator!]}] ["#." case] - ["/#" // #_ + ["/#" // "_" ["#." reference] - ["/#" // #_ + ["/#" // "_" [synthesis ["." case]] - ["/#" // #_ - ["."synthesis (#+ Scope Synthesis)] + ["/#" // "_" + ["."synthesis {"+" [Scope Synthesis]}] ["#." generation] - ["//#" /// #_ + ["//#" /// "_" ["#." phase] [meta - [archive (#+ Archive)]] + [archive {"+" [Archive]}]] [reference - [variable (#+ Register)]]]]]]]) + [variable {"+" [Register]}]]]]]]]) (def: @scope (-> Nat Label) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/primitive.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/primitive.lux index cc9af8550..1b5d3138d 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/primitive.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/primitive.lux @@ -1,14 +1,14 @@ (.module: [library - [lux (#- i64) + [lux {"-" [i64]} [control - [pipe (#+ cond> new>)]] + [pipe {"+" [cond> new>]}]] [math [number ["." frac]]] [target - ["_" php (#+ Literal Expression)]]]] - ["." // #_ + ["_" php {"+" [Literal Expression]}]]]] + ["." // "_" ["#." runtime]]) (def: .public bit diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/reference.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/reference.lux index 487d08e32..b1528276e 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/reference.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/reference.lux @@ -1,10 +1,10 @@ (.module: [library - [lux #* + [lux "*" [target - ["_" php (#+ Expression)]]]] + ["_" php {"+" [Expression]}]]]] [/// - [reference (#+ System)]]) + [reference {"+" [System]}]]) (implementation: .public system (System Expression) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/runtime.lux index 41d204e66..56ea8b098 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/runtime.lux @@ -1,9 +1,9 @@ (.module: [library - [lux (#- Location) + [lux {"-" [Location]} ["." meta] [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control ["." function] ["<>" parser @@ -11,32 +11,32 @@ [data ["." product] ["." text ("#\." hash) - ["%" format (#+ format)] + ["%" format {"+" [format]}] [encoding ["." utf8]]] [collection ["." list ("#\." functor)] ["." row]]] ["." macro - [syntax (#+ syntax:)] + [syntax {"+" [syntax:]}] ["." code]] [math - [number (#+ hex) + [number {"+" [hex]} ["." i64]]] ["@" target - ["_" php (#+ Expression Label Constant Var Computation Literal Statement)]]]] - ["." /// #_ + ["_" php {"+" [Expression Label Constant Var Computation Literal Statement]}]]]] + ["." /// "_" ["#." reference] - ["//#" /// #_ - ["#." synthesis (#+ Synthesis)] + ["//#" /// "_" + ["#." synthesis {"+" [Synthesis]}] ["#." generation] ["//#" /// ["#." phase] [reference - [variable (#+ Register)]] + [variable {"+" [Register]}]] [meta - [archive (#+ Output Archive) - ["." artifact (#+ Registry)]]]]]]) + [archive {"+" [Output Archive]} + ["." artifact {"+" [Registry]}]]]]]]) (template [<name> <base>] [(type: .public <name> diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/structure.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/structure.lux index 4d73dcec5..5fa169955 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/structure.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/structure.lux @@ -1,20 +1,20 @@ (.module: [library - [lux #* + [lux "*" [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [data [collection ["." list]]] [target - ["_" php (#+ Expression)]]]] - ["." // #_ - ["#." runtime (#+ Operation Phase Generator)] + ["_" php {"+" [Expression]}]]]] + ["." // "_" + ["#." runtime {"+" [Operation Phase Generator]}] ["#." primitive] - ["///#" //// #_ - [analysis (#+ Variant Tuple)] - ["#." synthesis (#+ Synthesis)] - ["//#" /// #_ + ["///#" //// "_" + [analysis {"+" [Variant Tuple]}] + ["#." synthesis {"+" [Synthesis]}] + ["//#" /// "_" ["#." phase ("#\." monad)]]]]) (def: .public (tuple expression archive elemsS+) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python.lux index 10cb4d3b9..6140dbc57 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python.lux @@ -1,34 +1,34 @@ (.module: [library - [lux #* + [lux "*" [abstract - [monad (#+ do)]] + [monad {"+" [do]}]] [control - ["." exception (#+ exception:)]] + ["." exception {"+" [exception:]}]] [target ["_" python]]]] - ["." / #_ - [runtime (#+ Phase)] + ["." / "_" + [runtime {"+" [Phase]}] ["#." primitive] ["#." structure] ["#." reference] ["#." function] ["#." case] ["#." loop] - ["/#" // #_ + ["/#" // "_" ["#." reference] - ["/#" // #_ + ["/#" // "_" ["#." extension [generation [python ["#/." common]]]] - ["/#" // #_ - [analysis (#+)] + ["/#" // "_" + [analysis {"+" []}] ["#." synthesis] - ["//#" /// #_ + ["//#" /// "_" ["#." phase ("#\." monad)] - [reference (#+) - [variable (#+)]]]]]]]) + [reference {"+" []} + [variable {"+" []}]]]]]]]) (exception: .public cannot_recur_as_an_expression) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/case.lux index e0385c419..a8c983bc3 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/case.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/case.lux @@ -1,11 +1,11 @@ (.module: [library - [lux (#- case let if) + [lux {"-" [case let if]} [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [data ["." text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." list ("#\." functor mix)] ["." set]]] @@ -14,25 +14,25 @@ ["n" nat] ["i" int]]] [target - ["_" python (#+ Expression SVar Statement)]]]] - ["." // #_ - ["#." runtime (#+ Operation Phase Generator Phase! Generator!)] + ["_" python {"+" [Expression SVar Statement]}]]]] + ["." // "_" + ["#." runtime {"+" [Operation Phase Generator Phase! Generator!]}] ["#." reference] ["#." primitive] - ["/#" // #_ + ["/#" // "_" ["#." reference] - ["/#" // #_ + ["/#" // "_" [synthesis ["." case]] - ["/#" // #_ - ["#." synthesis (#+ Member Synthesis Path)] + ["/#" // "_" + ["#." synthesis {"+" [Member Synthesis Path]}] ["#." generation] - ["//#" /// #_ + ["//#" /// "_" [reference - ["#." variable (#+ Register)]] + ["#." variable {"+" [Register]}]] ["#." phase ("#\." monad)] [meta - [archive (#+ Archive)]]]]]]]) + [archive {"+" [Archive]}]]]]]]]) (def: .public (identifier prefix) (-> Text (Operation SVar)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/function.lux index bd8bd4047..bfa8a26cf 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/function.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/function.lux @@ -1,34 +1,34 @@ (.module: [library - [lux (#- function) + [lux {"-" [function]} [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [data ["." product] [text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." list ("#\." functor mix)]]] [target - ["_" python (#+ SVar Expression Statement)]]]] - ["." // #_ - [runtime (#+ Operation Phase Generator Phase! Generator!)] + ["_" python {"+" [SVar Expression Statement]}]]]] + ["." // "_" + [runtime {"+" [Operation Phase Generator Phase! Generator!]}] ["#." reference] ["#." case] ["#." loop] - ["/#" // #_ + ["/#" // "_" ["#." reference] - ["//#" /// #_ - [analysis (#+ Environment Abstraction Application Analysis)] - [synthesis (#+ Synthesis)] - ["#." generation (#+ Context)] - ["//#" /// #_ - [arity (#+ Arity)] + ["//#" /// "_" + [analysis {"+" [Environment Abstraction Application Analysis]}] + [synthesis {"+" [Synthesis]}] + ["#." generation {"+" [Context]}] + ["//#" /// "_" + [arity {"+" [Arity]}] ["#." phase] [reference - [variable (#+ Register Variable)]] + [variable {"+" [Register Variable]}]] [meta - [archive (#+ Archive) + [archive {"+" [Archive]} ["." artifact]]]]]]]) (def: .public (apply expression archive [functionS argsS+]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/loop.lux index 670480f8e..6597c2271 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/loop.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/loop.lux @@ -1,12 +1,12 @@ (.module: [library - [lux (#- Scope) + [lux {"-" [Scope]} [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [data ["." product] [text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." list ("#\." functor mix)] ["." set]]] @@ -14,22 +14,22 @@ [number ["n" nat]]] [target - ["_" python (#+ Expression SVar Statement)]]]] - ["." // #_ - [runtime (#+ Operation Phase Generator Phase! Generator!)] + ["_" python {"+" [Expression SVar Statement]}]]]] + ["." // "_" + [runtime {"+" [Operation Phase Generator Phase! Generator!]}] ["#." case] - ["/#" // #_ + ["/#" // "_" ["#." reference] - ["/#" // #_ + ["/#" // "_" [synthesis ["." case]] - ["/#" // #_ - ["." synthesis (#+ Scope Synthesis)] + ["/#" // "_" + ["." synthesis {"+" [Scope Synthesis]}] ["#." generation] - ["//#" /// #_ + ["//#" /// "_" ["#." phase] [reference - ["#." variable (#+ Register)]]]]]]]) + ["#." variable {"+" [Register]}]]]]]]]) (def: (setup offset bindings body) (-> Register (List (Expression Any)) (Statement Any) (Statement Any)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/primitive.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/primitive.lux index 9d02d3974..c9c505798 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/primitive.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/primitive.lux @@ -1,9 +1,9 @@ (.module: [library - [lux (#- i64) + [lux {"-" [i64]} [target - ["_" python (#+ Expression)]]]] - ["." // #_ + ["_" python {"+" [Expression]}]]]] + ["." // "_" ["#." runtime]]) (template [<type> <name> <implementation>] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/reference.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/reference.lux index b53b3ff9d..647090e47 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/reference.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/reference.lux @@ -1,10 +1,10 @@ (.module: [library - [lux #* + [lux "*" [target - ["_" python (#+ Expression)]]]] + ["_" python {"+" [Expression]}]]]] [/// - [reference (#+ System)]]) + [reference {"+" [System]}]]) (implementation: .public system (System (Expression Any)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/runtime.lux index fafc59235..3cd1226b0 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/runtime.lux @@ -1,9 +1,9 @@ (.module: [library - [lux (#- ++) + [lux {"-" [++]} ["." meta] [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control ["." function] ["<>" parser @@ -11,34 +11,34 @@ [data ["." product] ["." text ("#\." hash) - ["%" format (#+ format)] + ["%" format {"+" [format]}] [encoding ["." utf8]]] [collection ["." list ("#\." functor)] ["." row]]] ["." macro - [syntax (#+ syntax:)] + [syntax {"+" [syntax:]}] ["." code]] [math - [number (#+ hex) + [number {"+" [hex]} ["f" frac] ["." i64]]] ["@" target - ["_" python (#+ Expression SVar Computation Literal Statement)]]]] - ["." /// #_ + ["_" python {"+" [Expression SVar Computation Literal Statement]}]]]] + ["." /// "_" ["#." reference] - ["//#" /// #_ + ["//#" /// "_" ["$" version] - ["#." synthesis (#+ Synthesis)] + ["#." synthesis {"+" [Synthesis]}] ["#." generation] ["//#" /// ["#." phase] [reference - [variable (#+ Register)]] + [variable {"+" [Register]}]] [meta - [archive (#+ Output Archive) - ["." artifact (#+ Registry)]]]]]]) + [archive {"+" [Output Archive]} + ["." artifact {"+" [Registry]}]]]]]]) (template [<name> <base>] [(type: .public <name> diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/structure.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/structure.lux index 85dc6218c..4ecbea30f 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/structure.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/structure.lux @@ -1,17 +1,17 @@ (.module: [library - [lux (#- Variant Tuple) + [lux {"-" [Variant Tuple]} [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [target - ["_" python (#+ Expression)]]]] - ["." // #_ - ["#." runtime (#+ Operation Phase Generator)] + ["_" python {"+" [Expression]}]]]] + ["." // "_" + ["#." runtime {"+" [Operation Phase Generator]}] ["#." primitive] - ["///#" //// #_ - [analysis (#+ Variant Tuple)] - ["#." synthesis (#+ Synthesis)] - ["//#" /// #_ + ["///#" //// "_" + [analysis {"+" [Variant Tuple]}] + ["#." synthesis {"+" [Synthesis]}] + ["//#" /// "_" ["#." phase ("#\." monad)]]]]) (def: .public (tuple generate archive elemsS+) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r.lux index a87076394..36950ea53 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r.lux @@ -1,29 +1,29 @@ (.module: [library - [lux #* + [lux "*" [abstract - [monad (#+ do)]] + [monad {"+" [do]}]] [target ["_" r]]]] - ["." / #_ - [runtime (#+ Phase)] + ["." / "_" + [runtime {"+" [Phase]}] ["#." primitive] ["#." structure] ["#." reference] ["#." case] ["#." loop] ["#." function] - ["/#" // #_ + ["/#" // "_" ["#." reference] - ["/#" // #_ + ["/#" // "_" ["#." extension] - ["/#" // #_ - [analysis (#+)] + ["/#" // "_" + [analysis {"+" []}] ["#." synthesis] - ["//#" /// #_ + ["//#" /// "_" ["#." phase ("#\." monad)] - [reference (#+) - [variable (#+)]]]]]]]) + [reference {"+" []} + [variable {"+" []}]]]]]]]) (def: .public (generate archive synthesis) Phase diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/case.lux index 86f376beb..b374c2fa2 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/case.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/case.lux @@ -1,12 +1,12 @@ (.module: [library - [lux (#- case let if) + [lux {"-" [case let if]} [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [data ["." product] ["." text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." list ("#\." functor mix)] ["." set]]] @@ -16,25 +16,25 @@ [number ["i" int]]] [target - ["_" r (#+ Expression SVar)]]]] - ["." // #_ - ["#." runtime (#+ Operation Phase Generator)] + ["_" r {"+" [Expression SVar]}]]]] + ["." // "_" + ["#." runtime {"+" [Operation Phase Generator]}] ["#." reference] ["#." primitive] - ["/#" // #_ + ["/#" // "_" ["#." reference] - ["/#" // #_ - ["#." synthesis #_ + ["/#" // "_" + ["#." synthesis "_" ["#/." case]] - ["/#" // #_ - ["#." synthesis (#+ Member Synthesis Path)] + ["/#" // "_" + ["#." synthesis {"+" [Member Synthesis Path]}] ["#." generation] - ["//#" /// #_ + ["//#" /// "_" [reference - ["#." variable (#+ Register)]] + ["#." variable {"+" [Register]}]] ["#." phase ("#\." monad)] [meta - [archive (#+ Archive)]]]]]]]) + [archive {"+" [Archive]}]]]]]]]) (def: .public register (-> Register SVar) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/function.lux index 5a4914c31..3a8fe9ec4 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/function.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/function.lux @@ -1,33 +1,33 @@ (.module: [library - [lux (#- function) + [lux {"-" [function]} [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control pipe] [data ["." product] ["." text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." list ("#\." functor mix)]]] [target - ["_" r (#+ Expression SVar)]]]] - ["." // #_ - ["#." runtime (#+ Operation Phase Generator)] + ["_" r {"+" [Expression SVar]}]]]] + ["." // "_" + ["#." runtime {"+" [Operation Phase Generator]}] ["#." reference] ["#." case] - ["/#" // #_ + ["/#" // "_" ["#." reference] - ["//#" /// #_ - [analysis (#+ Variant Tuple Abstraction Application Analysis)] - [synthesis (#+ Synthesis)] - ["#." generation (#+ Context)] - ["//#" /// #_ - [arity (#+ Arity)] + ["//#" /// "_" + [analysis {"+" [Variant Tuple Abstraction Application Analysis]}] + [synthesis {"+" [Synthesis]}] + ["#." generation {"+" [Context]}] + ["//#" /// "_" + [arity {"+" [Arity]}] ["#." phase ("#\." monad)] [reference - [variable (#+ Register Variable)]] + [variable {"+" [Register Variable]}]] [meta [archive ["." artifact]]]]]]]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/loop.lux index 82b97c26a..f19c655e2 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/loop.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/loop.lux @@ -1,37 +1,37 @@ (.module: [library - [lux (#- Scope) + [lux {"-" [Scope]} [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [data ["." product] ["." text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." list ("#\." functor)] - ["." set (#+ Set)]]] + ["." set {"+" [Set]}]]] [math [number ["n" nat]]] [target ["_" r]]]] - ["." // #_ - [runtime (#+ Operation Phase Generator)] + ["." // "_" + [runtime {"+" [Operation Phase Generator]}] ["#." case] - ["/#" // #_ + ["/#" // "_" ["#." reference] - ["/#" // #_ + ["/#" // "_" [synthesis ["." case]] - ["/#" // #_ - ["."synthesis (#+ Scope Synthesis)] + ["/#" // "_" + ["."synthesis {"+" [Scope Synthesis]}] ["#." generation] - ["//#" /// #_ + ["//#" /// "_" ["#." phase] [meta - [archive (#+ Archive)]] + [archive {"+" [Archive]}]] [reference - [variable (#+ Register)]]]]]]]) + [variable {"+" [Register]}]]]]]]]) (def: .public (scope expression archive [offset initsS+ bodyS]) (Generator (Scope Synthesis)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/primitive.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/primitive.lux index 1d4788f77..5d4361b81 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/primitive.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/primitive.lux @@ -1,9 +1,9 @@ (.module: [library - [lux (#- i64) + [lux {"-" [i64]} [target - ["_" r (#+ Expression)]]]] - ["." // #_ + ["_" r {"+" [Expression]}]]]] + ["." // "_" ["#." runtime]]) (template [<name> <type> <code>] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/common.lux index eb15a08a7..c1ebe76b6 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/common.lux @@ -1,23 +1,23 @@ (.module: lux (lux (control [library - [monad #+ do]] - ["ex" exception #+ exception:] + [monad {"+" [do]}]] + ["ex" exception {"+" [exception:]}] ["p" parser]) (data ["e" error] [text] text/format [number] (coll [list "list/" Functor<List>] - (dictionary ["dict" unordered #+ Dict]))) - [macro #+ with_identifiers] + (dictionary ["dict" unordered {"+" [Dict]}]))) + [macro {"+" [with_identifiers]}] (macro [code] - ["s" syntax #+ syntax:]) + ["s" syntax {"+" [syntax:]}]) [host]) (luxc ["&" lang] (lang ["la" analysis] ["ls" synthesis] - (host [r #+ Expression]))) + (host [r {"+" [Expression]}]))) [///] (/// [".T" runtime] [".T" case] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/host.lux index b810862e2..770e542de 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/host.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/host.lux @@ -1,16 +1,16 @@ (.module: lux (lux (control [library - [monad #+ do]]) + [monad {"+" [do]}]]) (data [text] text/format (coll [list "list/" Functor<List>] - (dictionary ["dict" unordered #+ Dict]))) + (dictionary ["dict" unordered {"+" [Dict]}]))) [macro "macro/" Monad<Meta>]) (luxc ["&" lang] (lang ["la" analysis] ["ls" synthesis] - (host [ruby #+ Ruby Expression Statement]))) + (host [ruby {"+" [Ruby Expression Statement]}]))) [///] (/// [".T" runtime]) (// ["@" common])) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/reference.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/reference.lux index 4e518e02a..cfbb6f02c 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/reference.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/reference.lux @@ -1,10 +1,10 @@ (.module: [library - [lux #* + [lux "*" [target - ["_" r (#+ Expression)]]]] + ["_" r {"+" [Expression]}]]]] [/// - [reference (#+ System)]]) + [reference {"+" [System]}]]) (implementation: .public system (System Expression) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/runtime.lux index 26c962945..c6529aa11 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/runtime.lux @@ -1,9 +1,9 @@ (.module: [library - [lux (#- Location ++ i64) + [lux {"-" [Location ++ i64]} ["." meta] [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control ["." function] ["<>" parser @@ -11,35 +11,35 @@ [data ["." product] ["." text ("#\." hash) - ["%" format (#+ format)] + ["%" format {"+" [format]}] [encoding ["." utf8]]] [collection ["." list ("#\." functor)] ["." row]]] ["." macro - [syntax (#+ syntax:)] + [syntax {"+" [syntax:]}] ["." code]] [math - [number (#+ hex) + [number {"+" [hex]} ["n" nat] ["i" int ("#\." interval)] ["." i64]]] ["@" target - ["_" r (#+ SVar Expression)]]]] - ["." /// #_ + ["_" r {"+" [SVar Expression]}]]]] + ["." /// "_" ["#." reference] - ["//#" /// #_ - [analysis (#+ Variant)] - ["#." synthesis (#+ Synthesis)] + ["//#" /// "_" + [analysis {"+" [Variant]}] + ["#." synthesis {"+" [Synthesis]}] ["#." generation] ["//#" /// ["#." phase] [reference - [variable (#+ Register)]] + [variable {"+" [Register]}]] [meta - [archive (#+ Output Archive) - ["." artifact (#+ Registry)]]]]]]) + [archive {"+" [Output Archive]} + ["." artifact {"+" [Registry]}]]]]]]) (def: module_id 0) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/structure.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/structure.lux index 2a69cfb08..bbe263ee8 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/structure.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/structure.lux @@ -1,20 +1,20 @@ (.module: [library - [lux #* + [lux "*" [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [data [collection ["." list]]] [target - ["_" r (#+ Expression)]]]] - ["." // #_ - ["#." runtime (#+ Operation Phase Generator)] + ["_" r {"+" [Expression]}]]]] + ["." // "_" + ["#." runtime {"+" [Operation Phase Generator]}] ["#." primitive] - ["///#" //// #_ - [analysis (#+ Variant Tuple)] - ["#." synthesis (#+ Synthesis)] - ["//#" /// #_ + ["///#" //// "_" + [analysis {"+" [Variant Tuple]}] + ["#." synthesis {"+" [Synthesis]}] + ["//#" /// "_" ["#." phase ("#\." monad)]]]]) (def: .public (tuple expression archive elemsS+) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/reference.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/reference.lux index 7c29f3367..5ccc49977 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/reference.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/reference.lux @@ -1,19 +1,19 @@ (.module: [library - [lux (#- local) + [lux {"-" [local]} ["@" target] [data [text - ["%" format (#+ format)]]]]] - ["." //// #_ + ["%" format {"+" [format]}]]]]] + ["." //// "_" ["." version] - ["#." generation (#+ Context)] - ["//#" /// #_ - ["." reference (#+ Reference) - ["." variable (#+ Register Variable)]] + ["#." generation {"+" [Context]}] + ["//#" /// "_" + ["." reference {"+" [Reference]} + ["." variable {"+" [Register Variable]}]] ["." phase ("#\." monad)] [meta - [archive (#+ Archive)]]]]) + [archive {"+" [Archive]}]]]]) ... This universe constant is for languages where one can't just turn all compiled definitions ... into the local variables of some scoping function. diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby.lux index a88cade6b..e0df52b0d 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby.lux @@ -1,34 +1,34 @@ (.module: [library - [lux #* + [lux "*" [abstract - [monad (#+ do)]] + [monad {"+" [do]}]] [control - ["." exception (#+ exception:)]] + ["." exception {"+" [exception:]}]] [target ["_" ruby]]]] - ["." / #_ - [runtime (#+ Phase Phase!)] + ["." / "_" + [runtime {"+" [Phase Phase!]}] ["#." primitive] ["#." structure] ["#." reference] ["#." function] ["#." case] ["#." loop] - ["/#" // #_ + ["/#" // "_" ["#." reference] - ["/#" // #_ + ["/#" // "_" ["#." extension [generation [ruby ["#/." common]]]] - ["/#" // #_ - [analysis (#+)] + ["/#" // "_" + [analysis {"+" []}] ["#." synthesis] - ["//#" /// #_ + ["//#" /// "_" ["#." phase ("#\." monad)] - [reference (#+) - [variable (#+)]]]]]]]) + [reference {"+" []} + [variable {"+" []}]]]]]]]) (exception: .public cannot_recur_as_an_expression) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/case.lux index a9ab2c87b..62de42847 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/case.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/case.lux @@ -1,13 +1,13 @@ (.module: [library - [lux (#- case let if) + [lux {"-" [case let if]} [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control - [exception (#+ exception:)]] + [exception {"+" [exception:]}]] [data ["." text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." list ("#\." functor mix)] ["." set]]] @@ -16,25 +16,25 @@ ["n" nat] ["i" int]]] [target - ["_" ruby (#+ Expression LVar Statement)]]]] - ["." // #_ - ["#." runtime (#+ Operation Phase Generator Phase! Generator!)] + ["_" ruby {"+" [Expression LVar Statement]}]]]] + ["." // "_" + ["#." runtime {"+" [Operation Phase Generator Phase! Generator!]}] ["#." reference] ["#." primitive] - ["/#" // #_ + ["/#" // "_" ["#." reference] - ["/#" // #_ + ["/#" // "_" [synthesis ["." case]] - ["/#" // #_ - ["#." synthesis (#+ Member Synthesis Path)] + ["/#" // "_" + ["#." synthesis {"+" [Member Synthesis Path]}] ["#." generation] - ["//#" /// #_ + ["//#" /// "_" [reference - ["#." variable (#+ Register)]] + ["#." variable {"+" [Register]}]] ["#." phase ("#\." monad)] [meta - [archive (#+ Archive)]]]]]]]) + [archive {"+" [Archive]}]]]]]]]) (def: .public (identifier prefix) (-> Text (Operation LVar)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/function.lux index dbca8e747..ab980ecb7 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/function.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/function.lux @@ -1,34 +1,34 @@ (.module: [library - [lux (#- Variant Tuple function) + [lux {"-" [Variant Tuple function]} [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [data ["." product] [text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." list ("#\." functor mix)]]] [target - ["_" ruby (#+ LVar GVar Expression Statement)]]]] - ["." // #_ - [runtime (#+ Operation Phase Generator Phase! Generator!)] + ["_" ruby {"+" [LVar GVar Expression Statement]}]]]] + ["." // "_" + [runtime {"+" [Operation Phase Generator Phase! Generator!]}] ["#." reference] ["#." case] ["#." loop] - ["/#" // #_ + ["/#" // "_" ["#." reference] - ["//#" /// #_ - [analysis (#+ Variant Tuple Environment Abstraction Application Analysis)] - [synthesis (#+ Synthesis)] - ["#." generation (#+ Context)] - ["//#" /// #_ - [arity (#+ Arity)] + ["//#" /// "_" + [analysis {"+" [Variant Tuple Environment Abstraction Application Analysis]}] + [synthesis {"+" [Synthesis]}] + ["#." generation {"+" [Context]}] + ["//#" /// "_" + [arity {"+" [Arity]}] ["#." phase] [reference - [variable (#+ Register Variable)]] + [variable {"+" [Register Variable]}]] [meta - [archive (#+ Archive) + [archive {"+" [Archive]} ["." artifact]]]]]]]) (def: .public (apply expression archive [functionS argsS+]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/loop.lux index 2c6f7dbe9..dcfac3da2 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/loop.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/loop.lux @@ -1,12 +1,12 @@ (.module: [library - [lux (#- Scope) + [lux {"-" [Scope]} [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [data ["." product] ["." text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." list ("#\." functor mix)] ["." set]]] @@ -14,22 +14,22 @@ [number ["n" nat]]] [target - ["_" ruby (#+ Expression LVar Statement)]]]] - ["." // #_ - [runtime (#+ Operation Phase Generator Phase! Generator!)] + ["_" ruby {"+" [Expression LVar Statement]}]]]] + ["." // "_" + [runtime {"+" [Operation Phase Generator Phase! Generator!]}] ["#." case] - ["/#" // #_ + ["/#" // "_" ["#." reference] - ["/#" // #_ + ["/#" // "_" [synthesis ["." case]] - ["/#" // #_ - ["." synthesis (#+ Scope Synthesis)] + ["/#" // "_" + ["." synthesis {"+" [Scope Synthesis]}] ["#." generation] - ["//#" /// #_ + ["//#" /// "_" ["#." phase] [reference - ["#." variable (#+ Register)]]]]]]]) + ["#." variable {"+" [Register]}]]]]]]]) (def: (setup offset bindings body) (-> Register (List Expression) Statement Statement) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/primitive.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/primitive.lux index 38b35b7a6..40055af95 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/primitive.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/primitive.lux @@ -1,8 +1,8 @@ (.module: [library - [lux (#- i64) + [lux {"-" [i64]} [target - ["_" ruby (#+ Literal)]]]]) + ["_" ruby {"+" [Literal]}]]]]) (template [<type> <name> <implementation>] [(def: .public <name> diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/reference.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/reference.lux index 827cca197..8ac89ceb9 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/reference.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/reference.lux @@ -1,10 +1,10 @@ (.module: [library - [lux #* + [lux "*" [target - ["_" ruby (#+ Expression)]]]] + ["_" ruby {"+" [Expression]}]]]] [/// - [reference (#+ System)]]) + [reference {"+" [System]}]]) (implementation: .public system (System Expression) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/runtime.lux index c4d57ef09..5168467ef 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/runtime.lux @@ -1,9 +1,9 @@ (.module: [library - [lux #* + [lux "*" ["." meta] [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control ["." function] ["<>" parser @@ -11,33 +11,33 @@ [data ["." product] ["." text ("#\." hash) - ["%" format (#+ format)] + ["%" format {"+" [format]}] [encoding ["." utf8]]] [collection ["." list ("#\." functor)] ["." row]]] ["." macro - [syntax (#+ syntax:)] + [syntax {"+" [syntax:]}] ["." code]] [math - [number (#+ hex) + [number {"+" [hex]} ["." i64]]] ["@" target - ["_" ruby (#+ Expression LVar Computation Literal Statement)]]]] - ["." /// #_ + ["_" ruby {"+" [Expression LVar Computation Literal Statement]}]]]] + ["." /// "_" ["#." reference] - ["//#" /// #_ + ["//#" /// "_" ["$" version] - ["#." synthesis (#+ Synthesis)] + ["#." synthesis {"+" [Synthesis]}] ["#." generation] ["//#" /// ["#." phase] [reference - [variable (#+ Register)]] + [variable {"+" [Register]}]] [meta - [archive (#+ Output Archive) - ["." artifact (#+ Registry)]]]]]]) + [archive {"+" [Output Archive]} + ["." artifact {"+" [Registry]}]]]]]]) (template [<name> <base>] [(type: .public <name> diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/structure.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/structure.lux index 136d05d92..e66199340 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/structure.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/structure.lux @@ -1,17 +1,17 @@ (.module: [library - [lux (#- Variant Tuple) + [lux {"-" [Variant Tuple]} [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [target - ["_" ruby (#+ Expression)]]]] - ["." // #_ - ["#." runtime (#+ Operation Phase Generator)] + ["_" ruby {"+" [Expression]}]]]] + ["." // "_" + ["#." runtime {"+" [Operation Phase Generator]}] ["#." primitive] - ["///#" //// #_ - [analysis (#+ Variant Tuple)] - ["#." synthesis (#+ Synthesis)] - ["//#" /// #_ + ["///#" //// "_" + [analysis {"+" [Variant Tuple]}] + ["#." synthesis {"+" [Synthesis]}] + ["//#" /// "_" ["#." phase ("#\." monad)]]]]) (def: .public (tuple generate archive elemsS+) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme.lux index c2a62c407..c1ec7c339 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme.lux @@ -1,29 +1,29 @@ (.module: [library - [lux #* + [lux "*" [abstract - [monad (#+ do)]] + [monad {"+" [do]}]] [target ["_" scheme]]]] - ["." / #_ - [runtime (#+ Phase)] + ["." / "_" + [runtime {"+" [Phase]}] ["#." primitive] ["#." structure] ["#." reference] ["#." case] ["#." loop] ["#." function] - ["/#" // #_ + ["/#" // "_" ["#." reference] - ["/#" // #_ + ["/#" // "_" ["#." extension] - ["/#" // #_ - [analysis (#+)] + ["/#" // "_" + [analysis {"+" []}] ["#." synthesis] - ["//#" /// #_ + ["//#" /// "_" ["#." phase ("#\." monad)] - [reference (#+) - [variable (#+)]]]]]]]) + [reference {"+" []} + [variable {"+" []}]]]]]]]) (def: .public (generate archive synthesis) Phase diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/case.lux index de65969b2..aa81c3c04 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/case.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/case.lux @@ -1,12 +1,12 @@ (.module: [library - [lux (#- case let if) + [lux {"-" [case let if]} [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [data ["." product] ["." text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." list ("#\." functor mix)] ["." set]]] @@ -16,25 +16,25 @@ [number ["i" int]]] [target - ["_" scheme (#+ Expression Computation Var)]]]] - ["." // #_ - ["#." runtime (#+ Operation Phase Generator)] + ["_" scheme {"+" [Expression Computation Var]}]]]] + ["." // "_" + ["#." runtime {"+" [Operation Phase Generator]}] ["#." reference] ["#." primitive] - ["/#" // #_ + ["/#" // "_" ["#." reference] - ["/#" // #_ - ["#." synthesis #_ + ["/#" // "_" + ["#." synthesis "_" ["#/." case]] - ["/#" // #_ - ["#." synthesis (#+ Member Synthesis Path)] + ["/#" // "_" + ["#." synthesis {"+" [Member Synthesis Path]}] ["#." generation] - ["//#" /// #_ + ["//#" /// "_" [reference - ["#." variable (#+ Register)]] + ["#." variable {"+" [Register]}]] ["#." phase ("#\." monad)] [meta - [archive (#+ Archive)]]]]]]]) + [archive {"+" [Archive]}]]]]]]]) (def: .public register (-> Register Var) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/extension.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/extension.lux index 17052fb88..6e255664b 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/extension.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/extension.lux @@ -1,11 +1,11 @@ (.module: [library - [lux #* + [lux "*" [data [collection ["." dictionary]]]]] [// - [runtime (#+ Bundle)]] + [runtime {"+" [Bundle]}]] [/ ["." common]]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/extension/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/extension/common.lux index b46b2e0b5..15e75a8e4 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/extension/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/extension/common.lux @@ -1,32 +1,32 @@ (.module: [library - [lux #* + [lux "*" [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control - ["ex" exception (#+ exception:)] + ["ex" exception {"+" [exception:]}] [parser ["<.>" code]]] [data ["." product] ["." text] - [number (#+ hex) + [number {"+" [hex]} ["f" frac]] [collection ["." list ("#\." functor)] - ["dict" dictionary (#+ Dictionary)]]] - ["." macro (#+ with_identifiers) + ["dict" dictionary {"+" [Dictionary]}]]] + ["." macro {"+" [with_identifiers]} ["." code] - [syntax (#+ syntax:)]] + [syntax {"+" [syntax:]}]] [target - ["_" scheme (#+ Expression Computation)]]]] - ["." /// #_ - ["#." runtime (#+ Operation Phase Handler Bundle)] + ["_" scheme {"+" [Expression Computation]}]]]] + ["." /// "_" + ["#." runtime {"+" [Operation Phase Handler Bundle]}] ["#//" /// ["#." extension ["." bundle]] - ["#/" // #_ - ["#." synthesis (#+ Synthesis)]]]]) + ["#/" // "_" + ["#." synthesis {"+" [Synthesis]}]]]]) (syntax: (Vector [size <code>.nat elemT <code>.any]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/function.lux index c7d8dbcd4..7a8d428b1 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/function.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/function.lux @@ -1,33 +1,33 @@ (.module: [library - [lux (#- function) + [lux {"-" [function]} [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control pipe] [data ["." product] ["." text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." list ("#\." functor)]]] [target - ["_" scheme (#+ Expression Computation Var)]]]] - ["." // #_ - ["#." runtime (#+ Operation Phase Generator)] + ["_" scheme {"+" [Expression Computation Var]}]]]] + ["." // "_" + ["#." runtime {"+" [Operation Phase Generator]}] ["#." reference] ["#." case] - ["/#" // #_ + ["/#" // "_" ["#." reference] - ["//#" /// #_ - [analysis (#+ Variant Tuple Abstraction Application Analysis)] - [synthesis (#+ Synthesis)] - ["#." generation (#+ Context)] - ["//#" /// #_ - [arity (#+ Arity)] + ["//#" /// "_" + [analysis {"+" [Variant Tuple Abstraction Application Analysis]}] + [synthesis {"+" [Synthesis]}] + ["#." generation {"+" [Context]}] + ["//#" /// "_" + [arity {"+" [Arity]}] ["#." phase ("#\." monad)] [reference - [variable (#+ Register Variable)]]]]]]) + [variable {"+" [Register Variable]}]]]]]]) (def: .public (apply expression archive [functionS argsS+]) (Generator (Application Synthesis)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/loop.lux index d0610fdfa..62bfc3d69 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/loop.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/loop.lux @@ -1,37 +1,37 @@ (.module: [library - [lux (#- Scope) + [lux {"-" [Scope]} [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [data ["." product] ["." text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." list ("#\." functor)] - ["." set (#+ Set)]]] + ["." set {"+" [Set]}]]] [math [number ["n" nat]]] [target ["_" scheme]]]] - ["." // #_ - [runtime (#+ Operation Phase Generator)] + ["." // "_" + [runtime {"+" [Operation Phase Generator]}] ["#." case] - ["/#" // #_ + ["/#" // "_" ["#." reference] - ["/#" // #_ + ["/#" // "_" [synthesis ["." case]] - ["/#" // #_ - ["."synthesis (#+ Scope Synthesis)] + ["/#" // "_" + ["."synthesis {"+" [Scope Synthesis]}] ["#." generation] - ["//#" /// #_ + ["//#" /// "_" ["#." phase] [meta - [archive (#+ Archive)]] + [archive {"+" [Archive]}]] [reference - [variable (#+ Register)]]]]]]]) + [variable {"+" [Register]}]]]]]]]) (def: @scope (_.var "scope")) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/primitive.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/primitive.lux index 1cb915b8e..05ce654e2 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/primitive.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/primitive.lux @@ -1,8 +1,8 @@ (.module: [library - [lux (#- i64) + [lux {"-" [i64]} [target - ["_" scheme (#+ Expression)]]]]) + ["_" scheme {"+" [Expression]}]]]]) (template [<name> <type> <code>] [(def: .public <name> diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/reference.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/reference.lux index b44d3f887..e72101b5b 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/reference.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/reference.lux @@ -1,10 +1,10 @@ (.module: [library - [lux #* + [lux "*" [target - ["_" scheme (#+ Expression)]]]] + ["_" scheme {"+" [Expression]}]]]] [/// - [reference (#+ System)]]) + [reference {"+" [System]}]]) (implementation: .public system (System Expression) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/runtime.lux index fefd850ce..316607dc7 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/runtime.lux @@ -1,9 +1,9 @@ (.module: [library - [lux (#- Location) + [lux {"-" [Location]} ["." meta] [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control ["." function] ["<>" parser @@ -11,33 +11,33 @@ [data ["." product] ["." text ("#\." hash) - ["%" format (#+ format)] + ["%" format {"+" [format]}] [encoding ["." utf8]]] [collection ["." list ("#\." functor)] ["." row]]] ["." macro - [syntax (#+ syntax:)] + [syntax {"+" [syntax:]}] ["." code]] [math - [number (#+ hex) + [number {"+" [hex]} ["." i64]]] ["@" target - ["_" scheme (#+ Expression Computation Var)]]]] - ["." /// #_ + ["_" scheme {"+" [Expression Computation Var]}]]]] + ["." /// "_" ["#." reference] - ["//#" /// #_ - [analysis (#+ Variant)] - ["#." synthesis (#+ Synthesis)] + ["//#" /// "_" + [analysis {"+" [Variant]}] + ["#." synthesis {"+" [Synthesis]}] ["#." generation] ["//#" /// ["#." phase] [reference - [variable (#+ Register)]] + [variable {"+" [Register]}]] [meta - [archive (#+ Output Archive) - ["." artifact (#+ Registry)]]]]]]) + [archive {"+" [Output Archive]} + ["." artifact {"+" [Registry]}]]]]]]) (def: module_id 0) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/structure.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/structure.lux index 0e5d70dbf..a0cf0e8d6 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/structure.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/structure.lux @@ -1,20 +1,20 @@ (.module: [library - [lux #* + [lux "*" [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [data [collection ["." list]]] [target - ["_" scheme (#+ Expression)]]]] - ["." // #_ - ["#." runtime (#+ Operation Phase Generator)] + ["_" scheme {"+" [Expression]}]]]] + ["." // "_" + ["#." runtime {"+" [Operation Phase Generator]}] ["#." primitive] - ["///#" //// #_ - [analysis (#+ Variant Tuple)] - ["#." synthesis (#+ Synthesis)] - ["//#" /// #_ + ["///#" //// "_" + [analysis {"+" [Variant Tuple]}] + ["#." synthesis {"+" [Synthesis]}] + ["//#" /// "_" ["#." phase ("#\." monad)]]]]) (def: .public (tuple expression archive elemsS+) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis.lux index f71e89b0c..65ba177f3 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis.lux @@ -1,28 +1,28 @@ (.module: [library - [lux (#- primitive) + [lux {"-" [primitive]} [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control - [pipe (#+ case>)] + [pipe {"+" [case>]}] ["." try]] [data [collection ["." list ("#\." functor)] - ["." dictionary (#+ Dictionary)]]]]] - ["." / #_ + ["." dictionary {"+" [Dictionary]}]]]]] + ["." / "_" ["#." function] ["#." case] ["#." variable] - ["/#" // #_ + ["/#" // "_" ["#." extension] - ["/#" // #_ - ["#." analysis (#+ Analysis)] - ["/" synthesis (#+ Synthesis Phase)] + ["/#" // "_" + ["#." analysis {"+" [Analysis]}] + ["/" synthesis {"+" [Synthesis Phase]}] [/// ["." phase ("#\." monad)] - [reference (#+) - [variable (#+)]]]]]]) + [reference {"+" []} + [variable {"+" []}]]]]]]) (def: (primitive analysis) (-> ///analysis.Primitive /.Primitive) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/case.lux index 4347ace80..a6271e4cc 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/case.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/case.lux @@ -1,33 +1,33 @@ (.module: [library - [lux #* + [lux "*" [abstract - [equivalence (#+ Equivalence)] - ["." monad (#+ do)]] + [equivalence {"+" [Equivalence]}] + ["." monad {"+" [do]}]] [control - [pipe (#+ when> new> case>)]] + [pipe {"+" [when> new> case>]}]] [data ["." product] ["." bit ("#\." equivalence)] ["." text ("#\." equivalence)] [collection ["." list ("#\." functor mix monoid)] - ["." set (#+ Set)]]] + ["." set {"+" [Set]}]]] [math [number ["n" nat] ["." i64] ["." frac ("#\." equivalence)]]]]] - ["." /// #_ + ["." /// "_" [// - ["#." analysis (#+ Pattern Match Analysis)] - ["/" synthesis (#+ Path Synthesis Operation Phase)] + ["#." analysis {"+" [Pattern Match Analysis]}] + ["/" synthesis {"+" [Path Synthesis Operation Phase]}] [/// ["#" phase ("#\." monad)] ["#." reference - ["#/." variable (#+ Register Variable)]] + ["#/." variable {"+" [Register Variable]}]] [meta - [archive (#+ Archive)]]]]]) + [archive {"+" [Archive]}]]]]]) (def: clean_up (-> Path Path) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/function.lux index 40689678f..d34765656 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/function.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/function.lux @@ -1,30 +1,30 @@ (.module: [library - [lux #* + [lux "*" [abstract - ["." monad (#+ do)] + ["." monad {"+" [do]}] ["." enum]] [control - [pipe (#+ case>)] + [pipe {"+" [case>]}] ["." maybe ("#\." functor)] - ["." exception (#+ exception:)]] + ["." exception {"+" [exception:]}]] [data ["." text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." list ("#\." functor monoid)]]] [math [number ["n" nat]]]]] - ["." // #_ - ["#." loop (#+ Transform)] - ["//#" /// #_ - ["#." analysis (#+ Environment Analysis)] - ["/" synthesis (#+ Path Abstraction Synthesis Operation Phase)] + ["." // "_" + ["#." loop {"+" [Transform]}] + ["//#" /// "_" + ["#." analysis {"+" [Environment Analysis]}] + ["/" synthesis {"+" [Path Abstraction Synthesis Operation Phase]}] [/// - [arity (#+ Arity)] + [arity {"+" [Arity]}] ["#." reference - ["#/." variable (#+ Register Variable)]] + ["#/." variable {"+" [Register Variable]}]] ["." phase ("#\." monad)]]]]) (exception: .public (cannot_find_foreign_variable_in_environment {foreign Register} {environment (Environment Synthesis)}) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/loop.lux index b4e79bd6d..8250d9ea9 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/loop.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/loop.lux @@ -1,8 +1,8 @@ (.module: [library - [lux #* + [lux "*" [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control ["." maybe ("#\." monad)]] [data @@ -12,12 +12,12 @@ [number ["n" nat]]]]] [//// - ["." analysis (#+ Environment)] - ["/" synthesis (#+ Path Abstraction Synthesis)] + ["." analysis {"+" [Environment]}] + ["/" synthesis {"+" [Path Abstraction Synthesis]}] [/// - [arity (#+ Arity)] + [arity {"+" [Arity]}] ["." reference - ["." variable (#+ Register Variable)]]]]) + ["." variable {"+" [Register Variable]}]]]]) (type: .public (Transform a) (-> a (Maybe a))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/variable.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/variable.lux index f4eb9691c..4c6deb529 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/variable.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/variable.lux @@ -1,30 +1,30 @@ (.module: [library - [lux #* + [lux "*" [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control ["." maybe ("#\." functor)] - ["." try (#+ Try)] - ["." exception (#+ exception:)]] + ["." try {"+" [Try]}] + ["." exception {"+" [exception:]}]] [data ["." product] ["." text ["%" format]] [collection - ["." dictionary (#+ Dictionary)] + ["." dictionary {"+" [Dictionary]}] ["." list ("#\." functor mix)] ["." set]]] [math [number ["n" nat]]]]] [//// - ["/" synthesis (#+ Path Synthesis)] + ["/" synthesis {"+" [Path Synthesis]}] ["." analysis] [/// - [arity (#+ Arity)] + [arity {"+" [Arity]}] ["." reference - ["." variable (#+ Register Variable)]]]]) + ["." variable {"+" [Register Variable]}]]]]) (def: (prune redundant register) (-> Register Register Register) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/program.lux b/stdlib/source/library/lux/tool/compiler/language/lux/program.lux index 047565e77..76bf6d43e 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/program.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/program.lux @@ -1,24 +1,24 @@ (.module: [library - [lux (#- Module) + [lux {"-" [Module]} [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control ["." maybe] - ["." try (#+ Try)] - ["." exception (#+ exception:)]] + ["." try {"+" [Try]}] + ["." exception {"+" [exception:]}]] [data ["." product] [text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." list ("#\." functor)]]]]] [// - [generation (#+ Context)] + [generation {"+" [Context]}] [/// [meta - ["." archive (#+ Archive) - ["." descriptor (#+ Module)] + ["." archive {"+" [Archive]} + ["." descriptor {"+" [Module]}] ["." artifact]]]]]) (type: .public (Program expression directive) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux b/stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux index 734f38260..08bff3cbf 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux @@ -26,21 +26,21 @@ ... location, which is helpful for documentation and debugging. (.module: [library - [lux #* + [lux "*" ["@" target] [abstract monad] [control ["." maybe] - ["." exception (#+ exception:)] + ["." exception {"+" [exception:]}] [parser - [text (#+ Offset)]]] + [text {"+" [Offset]}]]] [data ["." text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." list] - ["." dictionary (#+ Dictionary)]]] + ["." dictionary {"+" [Dictionary]}]]] [macro ["." template]] [math diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/synthesis.lux b/stdlib/source/library/lux/tool/compiler/language/lux/synthesis.lux index 9b4e1ad57..df124fba8 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/synthesis.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/synthesis.lux @@ -1,23 +1,23 @@ (.module: [library - [lux (#- i64 Scope) + [lux {"-" [i64 Scope]} [abstract - [monad (#+ do)] - [equivalence (#+ Equivalence)] - [hash (#+ Hash)]] + [monad {"+" [do]}] + [equivalence {"+" [Equivalence]}] + [hash {"+" [Hash]}]] [control - [pipe (#+ case>)] + [pipe {"+" [case>]}] ["." maybe] - ["." exception (#+ exception:)]] + ["." exception {"+" [exception:]}]] [data ["." sum] ["." product] ["." bit ("#\." equivalence)] ["." text ("#\." equivalence) - ["%" format (#+ Format format)]] + ["%" format {"+" [Format format]}]] [collection ["." list ("#\." functor)] - ["." dictionary (#+ Dictionary)]]] + ["." dictionary {"+" [Dictionary]}]]] [math [number ["." i64] @@ -25,14 +25,14 @@ ["i" int] ["f" frac]]]]] [// - ["." analysis (#+ Environment Composite Analysis)] + ["." analysis {"+" [Environment Composite Analysis]}] [phase - ["." extension (#+ Extension)]] + ["." extension {"+" [Extension]}]] [/// - [arity (#+ Arity)] + [arity {"+" [Arity]}] ["." phase] - ["." reference (#+ Reference) - ["." variable (#+ Register Variable)]]]]) + ["." reference {"+" [Reference]} + ["." variable {"+" [Register Variable]}]]]]) (type: .public Resolver (Dictionary Variable Variable)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/version.lux b/stdlib/source/library/lux/tool/compiler/language/lux/version.lux index 1ad0a00b4..e472c3a03 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/version.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/version.lux @@ -1,8 +1,8 @@ (.module: [library - [lux #*]] + [lux "*"]] [//// - [version (#+ Version)]]) + [version {"+" [Version]}]]) (def: .public version Version diff --git a/stdlib/source/library/lux/tool/compiler/meta.lux b/stdlib/source/library/lux/tool/compiler/meta.lux index 2d61d0c94..c15c11ee4 100644 --- a/stdlib/source/library/lux/tool/compiler/meta.lux +++ b/stdlib/source/library/lux/tool/compiler/meta.lux @@ -1,8 +1,8 @@ (.module: [library - [lux #*]] + [lux "*"]] [// - [version (#+ Version)]]) + [version {"+" [Version]}]]) (def: .public version Version diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive.lux b/stdlib/source/library/lux/tool/compiler/meta/archive.lux index d54234a8e..55f1bd5c0 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/archive.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/archive.lux @@ -1,29 +1,29 @@ (.module: [library - [lux (#- Module) + [lux {"-" [Module]} [abstract - ["." equivalence (#+ Equivalence)] - ["." monad (#+ do)]] + ["." equivalence {"+" [Equivalence]}] + ["." monad {"+" [do]}]] [control - ["." try (#+ Try)] - ["." exception (#+ exception:)] + ["." try {"+" [Try]}] + ["." exception {"+" [exception:]}] ["." function] ["<>" parser - ["<.>" binary (#+ Parser)]]] + ["<.>" binary {"+" [Parser]}]]] [data - [binary (#+ Binary)] + [binary {"+" [Binary]}] ["." bit] ["." product] ["." name] ["." text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [format - ["." binary (#+ Writer)]] + ["." binary {"+" [Writer]}]] [collection ["." list ("#\." functor mix)] - ["." dictionary (#+ Dictionary)] + ["." dictionary {"+" [Dictionary]}] ["." set] - ["." row (#+ Row)]]] + ["." row {"+" [Row]}]]] [math [number ["n" nat ("#\." equivalence)]]] @@ -31,12 +31,12 @@ abstract]]] [/ ["." artifact] - ["." signature (#+ Signature)] - ["." key (#+ Key)] - ["." descriptor (#+ Module Descriptor)] - ["." document (#+ Document)] + ["." signature {"+" [Signature]}] + ["." key {"+" [Key]}] + ["." descriptor {"+" [Module Descriptor]}] + ["." document {"+" [Document]}] [/// - [version (#+ Version)]]]) + [version {"+" [Version]}]]]) (type: .public Output (Row [artifact.ID (Maybe Text) Binary])) diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive/artifact.lux b/stdlib/source/library/lux/tool/compiler/meta/archive/artifact.lux index 23a9eae99..65211607f 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/archive/artifact.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/archive/artifact.lux @@ -1,23 +1,23 @@ (.module: [library - [lux #* + [lux "*" [abstract - [monad (#+ do)]] + [monad {"+" [do]}]] [control - [pipe (#+ case>)] - ["." exception (#+ exception:)] + [pipe {"+" [case>]}] + ["." exception {"+" [exception:]}] ["<>" parser - ["<.>" binary (#+ Parser)]]] + ["<.>" binary {"+" [Parser]}]]] [data ["." product] ["." text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." list] - ["." row (#+ Row) ("#\." functor mix)] - ["." dictionary (#+ Dictionary)]] + ["." row {"+" [Row]} ("#\." functor mix)] + ["." dictionary {"+" [Dictionary]}]] [format - ["." binary (#+ Writer)]]] + ["." binary {"+" [Writer]}]]] [type abstract]]]) diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive/descriptor.lux b/stdlib/source/library/lux/tool/compiler/meta/archive/descriptor.lux index fec78853e..28fedf1b7 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/archive/descriptor.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/archive/descriptor.lux @@ -1,19 +1,19 @@ (.module: [library - [lux (#- Module) + [lux {"-" [Module]} [control ["<>" parser - ["<b>" binary (#+ Parser)]]] + ["<b>" binary {"+" [Parser]}]]] [data ["." text] [collection - [set (#+ Set)]] + [set {"+" [Set]}]] [format - ["." binary (#+ Writer)]]] + ["." binary {"+" [Writer]}]]] [world - [file (#+ Path)]]]] + [file {"+" [Path]}]]]] [// - ["." artifact (#+ Registry)]]) + ["." artifact {"+" [Registry]}]]) (type: .public Module Text) diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive/document.lux b/stdlib/source/library/lux/tool/compiler/meta/archive/document.lux index 6bc6d4e80..ce7ebd327 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/archive/document.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/archive/document.lux @@ -1,24 +1,24 @@ (.module: [library - [lux (#- Module) + [lux {"-" [Module]} [abstract - [monad (#+ do)]] + [monad {"+" [do]}]] [control - ["." try (#+ Try)] - ["." exception (#+ exception:)] + ["." try {"+" [Try]}] + ["." exception {"+" [exception:]}] ["<>" parser - [binary (#+ Parser)]]] + [binary {"+" [Parser]}]]] [data [collection - ["." dictionary (#+ Dictionary)]] + ["." dictionary {"+" [Dictionary]}]] [format - ["." binary (#+ Writer)]]] - [type (#+ :sharing) + ["." binary {"+" [Writer]}]]] + [type {"+" [:sharing]} abstract]]] [// - ["." signature (#+ Signature)] - ["." key (#+ Key)] - [descriptor (#+ Module)]]) + ["." signature {"+" [Signature]}] + ["." key {"+" [Key]}] + [descriptor {"+" [Module]}]]) (exception: .public (invalid_signature {expected Signature} {actual Signature}) (exception.report diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive/key.lux b/stdlib/source/library/lux/tool/compiler/meta/archive/key.lux index 494956e83..e6cac3246 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/archive/key.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/archive/key.lux @@ -1,10 +1,10 @@ (.module: [library - [lux #* + [lux "*" [type abstract]]] [// - [signature (#+ Signature)]]) + [signature {"+" [Signature]}]]) (abstract: .public (Key k) {} diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive/signature.lux b/stdlib/source/library/lux/tool/compiler/meta/archive/signature.lux index 8dae11fe4..acfedec58 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/archive/signature.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/archive/signature.lux @@ -1,23 +1,23 @@ (.module: [library - [lux #* + [lux "*" [abstract - [equivalence (#+ Equivalence)]] + [equivalence {"+" [Equivalence]}]] [control ["<>" parser - ["<b>" binary (#+ Parser)]]] + ["<b>" binary {"+" [Parser]}]]] [data ["." product] ["." name] ["." text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [format - ["." binary (#+ Writer)]]] + ["." binary {"+" [Writer]}]]] [math [number ["." nat]]]]] [//// - [version (#+ Version)]]) + [version {"+" [Version]}]]) (type: .public Signature (Record diff --git a/stdlib/source/library/lux/tool/compiler/meta/cache/dependency.lux b/stdlib/source/library/lux/tool/compiler/meta/cache/dependency.lux index 8944ceeb8..c0e638425 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/cache/dependency.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/cache/dependency.lux @@ -1,26 +1,26 @@ (.module: [library - [lux (#- Module) + [lux {"-" [Module]} [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control ["." maybe ("#\." functor)] - ["." try (#+ Try)] + ["." try {"+" [Try]}] ["." state] ["." function - ["." memo (#+ Memo)]]] + ["." memo {"+" [Memo]}]]] [data ["." text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." list ("#\." functor mix)] - ["." dictionary (#+ Dictionary)] - ["." set (#+ Set)]]]]] + ["." dictionary {"+" [Dictionary]}] + ["." set {"+" [Set]}]]]]] [/// - ["." archive (#+ Output Archive) - [key (#+ Key)] - ["." descriptor (#+ Module Descriptor)] - ["." document (#+ Document)]]]) + ["." archive {"+" [Output Archive]} + [key {"+" [Key]}] + ["." descriptor {"+" [Module Descriptor]}] + ["." document {"+" [Document]}]]]) (type: Ancestry (Set Module)) diff --git a/stdlib/source/library/lux/tool/compiler/meta/io.lux b/stdlib/source/library/lux/tool/compiler/meta/io.lux index 9e54f0df9..25a77d0af 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/io.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/io.lux @@ -1,10 +1,10 @@ (.module: [library - [lux (#- Code) + [lux {"-" [Code]} [data ["." text]] [world - [file (#+ Path System)]]]]) + [file {"+" [Path System]}]]]]) (type: .public Context Path) diff --git a/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux b/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux index a2b2908b3..6e4fd6d12 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux @@ -1,27 +1,27 @@ (.module: [library - [lux (#- Module) - [target (#+ Target)] + [lux {"-" [Module]} + [target {"+" [Target]}] [abstract - [predicate (#+ Predicate)] - ["." monad (#+ do)]] + [predicate {"+" [Predicate]}] + ["." monad {"+" [do]}]] [control - [pipe (#+ case>)] - ["." try (#+ Try)] - ["." exception (#+ exception:)] + [pipe {"+" [case>]}] + ["." try {"+" [Try]}] + ["." exception {"+" [exception:]}] [concurrency - ["." async (#+ Async) ("#\." monad)]] + ["." async {"+" [Async]} ("#\." monad)]] ["<>" parser - ["<.>" binary (#+ Parser)]]] + ["<.>" binary {"+" [Parser]}]]] [data - [binary (#+ Binary)] + [binary {"+" [Binary]}] ["." product] ["." text ("#\." equivalence) - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." list ("#\." functor mix)] - ["." dictionary (#+ Dictionary)] - ["." row (#+ Row)] + ["." dictionary {"+" [Dictionary]}] + ["." row {"+" [Row]}] ["." set]]] [math [number @@ -30,18 +30,18 @@ ["." file]]]] [program [compositor - [import (#+ Import)] - ["." static (#+ Static)]]] - ["." // (#+ Context) + [import {"+" [Import]}] + ["." static {"+" [Static]}]]] + ["." // {"+" [Context]} ["#." context] ["/#" // - ["." archive (#+ Output Archive) - ["." artifact (#+ Artifact)] - ["." descriptor (#+ Module Descriptor)] - ["." document (#+ Document)]] + ["." archive {"+" [Output Archive]} + ["." artifact {"+" [Artifact]}] + ["." descriptor {"+" [Module Descriptor]}] + ["." document {"+" [Document]}]] [cache ["." dependency]] - ["/#" // (#+ Input) + ["/#" // {"+" [Input]} [language ["$" lux ["." version] diff --git a/stdlib/source/library/lux/tool/compiler/meta/io/context.lux b/stdlib/source/library/lux/tool/compiler/meta/io/context.lux index 250849940..161700dd4 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/io/context.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/io/context.lux @@ -1,35 +1,35 @@ (.module: [library - [lux (#- Module Code) + [lux {"-" [Module Code]} ["@" target] [abstract - [predicate (#+ Predicate)] - ["." monad (#+ Monad do)]] + [predicate {"+" [Predicate]}] + ["." monad {"+" [Monad do]}]] [control ["." maybe] - ["." try (#+ Try)] - ["." exception (#+ exception:)] + ["." try {"+" [Try]}] + ["." exception {"+" [exception:]}] [concurrency - ["." async (#+ Async) ("#\." monad)]]] + ["." async {"+" [Async]} ("#\." monad)]]] [data - [binary (#+ Binary)] + [binary {"+" [Binary]}] ["." text ("#\." hash) - ["%" format (#+ format)] + ["%" format {"+" [format]}] [encoding ["." utf8]]] [collection - ["." dictionary (#+ Dictionary)] + ["." dictionary {"+" [Dictionary]}] ["." list]]] [world ["." file]]]] [program [compositor - [import (#+ Import)]]] - ["." // (#+ Context Code) - ["/#" // #_ + [import {"+" [Import]}]]] + ["." // {"+" [Context Code]} + ["/#" // "_" [archive - [descriptor (#+ Module)]] - ["/#" // (#+ Input)]]]) + [descriptor {"+" [Module]}]] + ["/#" // {"+" [Input]}]]]) (exception: .public (cannot_find_module {importer Module} {module Module}) (exception.report diff --git a/stdlib/source/library/lux/tool/compiler/meta/packager.lux b/stdlib/source/library/lux/tool/compiler/meta/packager.lux index f846a28a8..5a4a7ea1f 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/packager.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/packager.lux @@ -1,12 +1,12 @@ (.module: [library - [lux #* + [lux "*" [control - [try (#+ Try)]] + [try {"+" [Try]}]] [data - [binary (#+ Binary)] + [binary {"+" [Binary]}] [collection - [dictionary (#+ Dictionary)] + [dictionary {"+" [Dictionary]}] ["." row] ["." list ("#\." functor)]]] [world @@ -14,13 +14,13 @@ [// [cache ["." dependency]] - ["." archive (#+ Archive) + ["." archive {"+" [Archive]} ["." descriptor] ["." artifact]] [// [language [lux - [generation (#+ Context)]]]]]) + [generation {"+" [Context]}]]]]]) (type: .public Packager (-> (Dictionary file.Path Binary) diff --git a/stdlib/source/library/lux/tool/compiler/meta/packager/jvm.lux b/stdlib/source/library/lux/tool/compiler/meta/packager/jvm.lux index 37d9f7623..c82916769 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/packager/jvm.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/packager/jvm.lux @@ -1,21 +1,21 @@ (.module: [library - [lux (#- Module Definition) - ["." ffi (#+ import: do_to)] + [lux {"-" [Module Definition]} + ["." ffi {"+" [import: do_to]}] [abstract - ["." monad (#+ Monad do)]] + ["." monad {"+" [Monad do]}]] [control ["." maybe ("#\." functor)] - ["." try (#+ Try)]] + ["." try {"+" [Try]}]] [data - ["." binary (#+ Binary)] + ["." binary {"+" [Binary]}] ["." text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." row] ["." list ("#\." functor)] ["." dictionary] - ["." set (#+ Set)]]] + ["." set {"+" [Set]}]]] [math [number ["n" nat] @@ -28,24 +28,24 @@ ["." file]]]] [program [compositor - ["." static (#+ Static)]]] - ["." // (#+ Packager) + ["." static {"+" [Static]}]]] + ["." // {"+" [Packager]} [// - ["." archive (#+ Output) - ["." descriptor (#+ Module)] + ["." archive {"+" [Output]} + ["." descriptor {"+" [Module]}] ["." artifact]] [cache ["." dependency]] - ["." io #_ + ["." io "_" ["#" archive]] [// [language ["$" lux - [generation (#+ Context)] + [generation {"+" [Context]}] [phase [generation [jvm - ["." runtime (#+ Definition)]]]]]]]]]) + ["." runtime {"+" [Definition]}]]]]]]]]]) (import: java/lang/Object) diff --git a/stdlib/source/library/lux/tool/compiler/meta/packager/scheme.lux b/stdlib/source/library/lux/tool/compiler/meta/packager/scheme.lux index 2531459ce..d1f8d6349 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/packager/scheme.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/packager/scheme.lux @@ -1,21 +1,21 @@ (.module: [library - [lux (#- Module) - [type (#+ :sharing)] + [lux {"-" [Module]} + [type {"+" [:sharing]}] [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control - ["." try (#+ Try)]] + ["." try {"+" [Try]}]] [data - [binary (#+ Binary)] + [binary {"+" [Binary]}] ["." product] ["." text - ["%" format (#+ format)] + ["%" format {"+" [format]}] ["." encoding]] [collection ["." row] ["." list ("#\." functor mix)] - ["." dictionary (#+ Dictionary)] + ["." dictionary {"+" [Dictionary]}] ["." set]] [format ["." tar] @@ -23,26 +23,26 @@ [target ["_" scheme]] [time - ["." instant (#+ Instant)]] + ["." instant {"+" [Instant]}]] [world ["." file]]]] [program [compositor - ["." static (#+ Static)]]] - ["." // (#+ Packager) + ["." static {"+" [Static]}]]] + ["." // {"+" [Packager]} [// - ["." archive (#+ Output) - ["." descriptor (#+ Module Descriptor)] + ["." archive {"+" [Output]} + ["." descriptor {"+" [Module Descriptor]}] ["." artifact] - ["." document (#+ Document)]] + ["." document {"+" [Document]}]] [cache ["." dependency]] - ["." io #_ + ["." io "_" ["#" archive]] [// [language ["$" lux - [generation (#+ Context)]]]]]]) + [generation {"+" [Context]}]]]]]]) ... TODO: Delete ASAP (type: (Action ! a) diff --git a/stdlib/source/library/lux/tool/compiler/meta/packager/script.lux b/stdlib/source/library/lux/tool/compiler/meta/packager/script.lux index 10ef01271..6ed4f3f71 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/packager/script.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/packager/script.lux @@ -1,16 +1,16 @@ (.module: [library - [lux #* - [type (#+ :sharing)] + [lux "*" + [type {"+" [:sharing]}] [abstract - ["." monad (#+ Monad do)]] + ["." monad {"+" [Monad do]}]] [control - ["." try (#+ Try)]] + ["." try {"+" [Try]}]] [data - [binary (#+ Binary)] + [binary {"+" [Binary]}] ["." product] [text - ["%" format (#+ format)] + ["%" format {"+" [format]}] [encoding ["." utf8]]] [collection @@ -18,20 +18,20 @@ ["." list ("#\." functor)]]]]] [program [compositor - ["." static (#+ Static)]]] - ["." // (#+ Packager) + ["." static {"+" [Static]}]]] + ["." // {"+" [Packager]} [// - ["." archive (#+ Output) + ["." archive {"+" [Output]} ["." descriptor] ["." artifact]] [cache ["." dependency]] - ["." io #_ + ["." io "_" ["#" archive]] [// [language ["$" lux - [generation (#+ Context)]]]]]]) + [generation {"+" [Context]}]]]]]]) (def: (write_module sequence [module output] so_far) (All (_ directive) diff --git a/stdlib/source/library/lux/tool/compiler/phase.lux b/stdlib/source/library/lux/tool/compiler/phase.lux index b80e262c4..80dfdb208 100644 --- a/stdlib/source/library/lux/tool/compiler/phase.lux +++ b/stdlib/source/library/lux/tool/compiler/phase.lux @@ -1,28 +1,28 @@ (.module: [library - [lux #* + [lux "*" ["." debug] [abstract - [monad (#+ Monad do)]] + [monad {"+" [Monad do]}]] [control ["." state] - ["." try (#+ Try) ("#\." functor)] - ["ex" exception (#+ Exception exception:)] + ["." try {"+" [Try]} ("#\." functor)] + ["ex" exception {"+" [Exception exception:]}] ["." io] [parser ["<.>" code]]] [data ["." product] ["." text - ["%" format (#+ format)]]] + ["%" format {"+" [format]}]]] [time ["." instant] ["." duration]] [macro - [syntax (#+ syntax:)]]]] + [syntax {"+" [syntax:]}]]]] [// [meta - [archive (#+ Archive)]]]) + [archive {"+" [Archive]}]]]) (type: .public (Operation s o) (state.+State Try s o)) diff --git a/stdlib/source/library/lux/tool/compiler/reference.lux b/stdlib/source/library/lux/tool/compiler/reference.lux index c90aa41f6..b3e804abb 100644 --- a/stdlib/source/library/lux/tool/compiler/reference.lux +++ b/stdlib/source/library/lux/tool/compiler/reference.lux @@ -1,20 +1,20 @@ (.module: [library - [lux (#- local) + [lux {"-" [local]} [abstract - [equivalence (#+ Equivalence)] - [hash (#+ Hash)]] + [equivalence {"+" [Equivalence]}] + [hash {"+" [Hash]}]] [control - [pipe (#+ case>)]] + [pipe {"+" [case>]}]] [data ["." name] [text - ["%" format (#+ Format)]]] + ["%" format {"+" [Format]}]]] [math [number ["n" nat]]]]] - ["." / #_ - ["#." variable (#+ Variable)]]) + ["." / "_" + ["#." variable {"+" [Variable]}]]) (type: .public Constant Name) diff --git a/stdlib/source/library/lux/tool/compiler/reference/variable.lux b/stdlib/source/library/lux/tool/compiler/reference/variable.lux index 0c0eaad22..eea52b976 100644 --- a/stdlib/source/library/lux/tool/compiler/reference/variable.lux +++ b/stdlib/source/library/lux/tool/compiler/reference/variable.lux @@ -1,14 +1,14 @@ (.module: [library - [lux #* + [lux "*" [abstract - [equivalence (#+ Equivalence)] - [hash (#+ Hash)]] + [equivalence {"+" [Equivalence]}] + [hash {"+" [Hash]}]] [control - [pipe (#+ case>)]] + [pipe {"+" [case>]}]] [data [text - ["%" format (#+ Format)]]] + ["%" format {"+" [Format]}]]] [math [number ["n" nat] diff --git a/stdlib/source/library/lux/tool/compiler/version.lux b/stdlib/source/library/lux/tool/compiler/version.lux index 4d34cab77..d389122f1 100644 --- a/stdlib/source/library/lux/tool/compiler/version.lux +++ b/stdlib/source/library/lux/tool/compiler/version.lux @@ -1,6 +1,6 @@ (.module: [library - [lux #* + [lux "*" [data [text ["%" format]]] diff --git a/stdlib/source/library/lux/tool/interpreter.lux b/stdlib/source/library/lux/tool/interpreter.lux index eb4ac9de7..3a91862f8 100644 --- a/stdlib/source/library/lux/tool/interpreter.lux +++ b/stdlib/source/library/lux/tool/interpreter.lux @@ -1,14 +1,14 @@ (.module: [library - [lux #* + [lux "*" [control - [monad (#+ Monad do)] - ["." try (#+ Try)] - ["ex" exception (#+ exception:)]] + [monad {"+" [Monad do]}] + ["." try {"+" [Try]}] + ["ex" exception {"+" [exception:]}]] [data ["." text ("#\." equivalence) - ["%" format (#+ format)]]] - [type (#+ :sharing) + ["%" format {"+" [format]}]]] + [type {"+" [:sharing]} ["." check]] [compiler ["." phase @@ -16,17 +16,17 @@ ["." module] ["." type]] ["." generation] - ["." directive (#+ State+ Operation) + ["." directive {"+" [State+ Operation]} ["." total]] ["." extension]] ["." default ["." syntax] - ["." platform (#+ Platform)] + ["." platform {"+" [Platform]}] ["." init]] - ["." cli (#+ Configuration)]] + ["." cli {"+" [Configuration]}]] [world - ["." file (#+ File)] - ["." console (#+ Console)]]]] + ["." file {"+" [File]}] + ["." console {"+" [Console]}]]]] ["." /type]) (exception: .public (error {message Text}) diff --git a/stdlib/source/library/lux/tool/mediator.lux b/stdlib/source/library/lux/tool/mediator.lux index f46d2f486..a73bb0bfd 100644 --- a/stdlib/source/library/lux/tool/mediator.lux +++ b/stdlib/source/library/lux/tool/mediator.lux @@ -1,14 +1,14 @@ (.module: [library - [lux (#- Source Module) + [lux {"-" [Source Module]} [world - ["." binary (#+ Binary)] - ["." file (#+ Path)]]]] + ["." binary {"+" [Binary]}] + ["." file {"+" [Path]}]]]] [// - [compiler (#+ Compiler) + [compiler {"+" [Compiler]} [meta - ["." archive (#+ Archive) - [descriptor (#+ Module)]]]]]) + ["." archive {"+" [Archive]} + [descriptor {"+" [Module]}]]]]]) (type: .public Source Path) diff --git a/stdlib/source/library/lux/type.lux b/stdlib/source/library/lux/type.lux index 0ef1ba1af..c6f57f52f 100644 --- a/stdlib/source/library/lux/type.lux +++ b/stdlib/source/library/lux/type.lux @@ -1,16 +1,16 @@ (.module: [library - [lux (#- function :as) + [lux {"-" [function :as]} ["@" target] [abstract - [equivalence (#+ Equivalence)] - [monad (#+ Monad do)]] + [equivalence {"+" [Equivalence]}] + [monad {"+" [Monad do]}]] [control ["." function] ["." maybe] - ["." exception (#+ exception:)] + ["." exception {"+" [exception:]}] ["<>" parser - ["<.>" code (#+ Parser)]]] + ["<.>" code {"+" [Parser]}]]] [data ["." product] ["." text ("#\." monoid equivalence)] @@ -19,7 +19,7 @@ ["." array] ["." list ("#\." functor monoid mix)]]] ["." macro - [syntax (#+ syntax:)] + [syntax {"+" [syntax:]}] ["." code]] [math [number diff --git a/stdlib/source/library/lux/type/abstract.lux b/stdlib/source/library/lux/type/abstract.lux index bd2fe150f..8ea539e97 100644 --- a/stdlib/source/library/lux/type/abstract.lux +++ b/stdlib/source/library/lux/type/abstract.lux @@ -1,13 +1,13 @@ (.module: [library - [lux #* + [lux "*" ["." meta] [abstract - [monad (#+ Monad do)]] + [monad {"+" [Monad do]}]] [control - ["." exception (#+ exception:)] + ["." exception {"+" [exception:]}] ["<>" parser ("#\." monad) - ["<.>" code (#+ Parser)]]] + ["<.>" code {"+" [Parser]}]]] [data ["." name ("#\." codec)] ["." text ("#\." equivalence monoid)] @@ -15,7 +15,7 @@ ["." list ("#\." functor monoid)]]] [macro ["." code] - [syntax (#+ syntax:) + [syntax {"+" [syntax:]} ["|.|" annotations]]]]] ["." //]) diff --git a/stdlib/source/library/lux/type/check.lux b/stdlib/source/library/lux/type/check.lux index ed8afab5b..2cac17f57 100644 --- a/stdlib/source/library/lux/type/check.lux +++ b/stdlib/source/library/lux/type/check.lux @@ -1,21 +1,21 @@ (.module: [library - [lux #* + [lux "*" ["@" target] [abstract - [functor (#+ Functor)] - [apply (#+ Apply)] - ["." monad (#+ Monad do)]] + [functor {"+" [Functor]}] + [apply {"+" [Apply]}] + ["." monad {"+" [Monad do]}]] [control ["." maybe] - ["." try (#+ Try)] - ["." exception (#+ Exception exception:)]] + ["." try {"+" [Try]}] + ["." exception {"+" [Exception exception:]}]] [data ["." product] ["." text ("#\." monoid equivalence)] [collection ["." list] - ["." set (#+ Set)]]] + ["." set {"+" [Set]}]]] [math [number ["n" nat ("#\." decimal)]]]]] diff --git a/stdlib/source/library/lux/type/dynamic.lux b/stdlib/source/library/lux/type/dynamic.lux index 19898da65..6311e8a2f 100644 --- a/stdlib/source/library/lux/type/dynamic.lux +++ b/stdlib/source/library/lux/type/dynamic.lux @@ -1,17 +1,17 @@ (.module: [library - [lux #* + [lux "*" ["." debug] [control - ["." try (#+ Try)] - ["." exception (#+ exception:)] + ["." try {"+" [Try]}] + ["." exception {"+" [exception:]}] [parser ["<.>" code]]] [data [text ["%" format]]] - [macro (#+ with_identifiers) - ["." syntax (#+ syntax:)]] + [macro {"+" [with_identifiers]} + ["." syntax {"+" [syntax:]}]] ["." type abstract]]]) diff --git a/stdlib/source/library/lux/type/implicit.lux b/stdlib/source/library/lux/type/implicit.lux index fe815482d..6c3d91881 100644 --- a/stdlib/source/library/lux/type/implicit.lux +++ b/stdlib/source/library/lux/type/implicit.lux @@ -1,31 +1,31 @@ (.module: [library - [lux #* + [lux "*" [abstract - ["." monad (#+ do)] + ["." monad {"+" [do]}] ["." equivalence]] [control ["." maybe] ["." try] ["<>" parser - ["<.>" code (#+ Parser)]]] + ["<.>" code {"+" [Parser]}]]] [data ["." product] ["." text ("#\." equivalence) - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." list ("#\." monad mix)] - ["." dictionary (#+ Dictionary)]]] + ["." dictionary {"+" [Dictionary]}]]] ["." macro ["." code] - [syntax (#+ syntax:)]] + [syntax {"+" [syntax:]}]] [math ["." number ["n" nat]]] ["." meta ["." annotation]] ["." type - ["." check (#+ Check)]]]]) + ["." check {"+" [Check]}]]]]) (def: (type_var id env) (-> Nat Type_Context (Meta Type)) diff --git a/stdlib/source/library/lux/type/poly.lux b/stdlib/source/library/lux/type/poly.lux index 9fb6a945b..f4b2e0d4f 100644 --- a/stdlib/source/library/lux/type/poly.lux +++ b/stdlib/source/library/lux/type/poly.lux @@ -1,24 +1,24 @@ (.module: [library - [lux #* + [lux "*" ["." meta] ["." type] [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control ["." maybe] ["<>" parser ("#\." monad) - ["<.>" type (#+ Env)] - ["<.>" code (#+ Parser)]]] + ["<.>" type {"+" [Env]}] + ["<.>" code {"+" [Parser]}]]] [data ["." product] ["." text] [collection ["." list ("#\." functor)] ["." dictionary]]] - [macro (#+ with_identifiers) + [macro {"+" [with_identifiers]} ["." code] - [syntax (#+ syntax:)]] + [syntax {"+" [syntax:]}]] [math [number ["n" nat]]]]]) diff --git a/stdlib/source/library/lux/type/quotient.lux b/stdlib/source/library/lux/type/quotient.lux index 163af82d6..5033db2a0 100644 --- a/stdlib/source/library/lux/type/quotient.lux +++ b/stdlib/source/library/lux/type/quotient.lux @@ -1,13 +1,13 @@ (.module: [library - [lux (#- type) + [lux {"-" [type]} [abstract - [equivalence (#+ Equivalence)]] + [equivalence {"+" [Equivalence]}]] [control [parser ["<.>" code]]] - [macro (#+ with_identifiers) - [syntax (#+ syntax:)]] + [macro {"+" [with_identifiers]} + [syntax {"+" [syntax:]}]] ["." type abstract]]]) diff --git a/stdlib/source/library/lux/type/refinement.lux b/stdlib/source/library/lux/type/refinement.lux index 93d962ae3..172ddee2c 100644 --- a/stdlib/source/library/lux/type/refinement.lux +++ b/stdlib/source/library/lux/type/refinement.lux @@ -1,13 +1,13 @@ (.module: [library - [lux (#- type) + [lux {"-" [type]} [abstract - [predicate (#+ Predicate)]] + [predicate {"+" [Predicate]}]] [control [parser ["<.>" code]]] ["." macro - [syntax (#+ syntax:)]] + [syntax {"+" [syntax:]}]] ["." type abstract]]]) diff --git a/stdlib/source/library/lux/type/resource.lux b/stdlib/source/library/lux/type/resource.lux index f9ca4ea6e..27eb7ce86 100644 --- a/stdlib/source/library/lux/type/resource.lux +++ b/stdlib/source/library/lux/type/resource.lux @@ -1,24 +1,24 @@ (.module: [library - [lux #* + [lux "*" ["." meta] [abstract - ["." monad (#+ Monad do) - [indexed (#+ IxMonad)]]] + ["." monad {"+" [Monad do]} + [indexed {"+" [IxMonad]}]]] [control ["." maybe] - ["." exception (#+ exception:)] + ["." exception {"+" [exception:]}] ["<>" parser - ["<.>" code (#+ Parser)]]] + ["<.>" code {"+" [Parser]}]]] [data [text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." set] - ["." row (#+ Row)] + ["." row {"+" [Row]}] ["." list ("#\." functor mix)]]] ["." macro - [syntax (#+ syntax:)]] + [syntax {"+" [syntax:]}]] [math [number ["n" nat]]] diff --git a/stdlib/source/library/lux/type/unit.lux b/stdlib/source/library/lux/type/unit.lux index adc5b8dc3..8ace4333f 100644 --- a/stdlib/source/library/lux/type/unit.lux +++ b/stdlib/source/library/lux/type/unit.lux @@ -1,29 +1,29 @@ (.module: [library - [lux #* + [lux "*" ["." meta] [abstract - [monad (#+ Monad do)] - [equivalence (#+ Equivalence)] - [order (#+ Order)] - [enum (#+ Enum)]] + [monad {"+" [Monad do]}] + [equivalence {"+" [Equivalence]}] + [order {"+" [Order]}] + [enum {"+" [Enum]}]] [control ["<>" parser ("#\." monad) - ["<.>" code (#+ Parser)]]] + ["<.>" code {"+" [Parser]}]]] [data ["." text - ["%" format (#+ format)]]] + ["%" format {"+" [format]}]]] [macro ["." code] ["." template] - [syntax (#+ syntax:) + [syntax {"+" [syntax:]} ["|.|" export] ["|.|" annotations]]] [math [number ["n" nat] ["i" int] - ["." ratio (#+ Ratio)]]] + ["." ratio {"+" [Ratio]}]]] [type abstract]]]) diff --git a/stdlib/source/library/lux/type/variance.lux b/stdlib/source/library/lux/type/variance.lux index ae2c889ca..a0706ce22 100644 --- a/stdlib/source/library/lux/type/variance.lux +++ b/stdlib/source/library/lux/type/variance.lux @@ -1,6 +1,6 @@ (.module: [library - [lux #*]]) + [lux "*"]]) (type: .public (Co it) (-> Any it)) diff --git a/stdlib/source/library/lux/world/console.lux b/stdlib/source/library/lux/world/console.lux index b34096ea5..98f960519 100644 --- a/stdlib/source/library/lux/world/console.lux +++ b/stdlib/source/library/lux/world/console.lux @@ -1,20 +1,20 @@ (.module: [library - [lux #* - [ffi (#+ import:)] + [lux "*" + [ffi {"+" [import:]}] ["@" target] [abstract - [monad (#+ do)]] + [monad {"+" [do]}]] [control - ["." try (#+ Try)] - ["." exception (#+ exception:)] - ["." io (#+ IO io)] + ["." try {"+" [Try]}] + ["." exception {"+" [exception:]}] + ["." io {"+" [IO io]}] [concurrency - ["." async (#+ Async)] + ["." async {"+" [Async]}] ["." atom]]] [data - ["." text (#+ Char) - ["%" format (#+ format)]]]]]) + ["." text {"+" [Char]} + ["%" format {"+" [format]}]]]]]) (type: .public (Console !) (Interface diff --git a/stdlib/source/library/lux/world/db/jdbc.lux b/stdlib/source/library/lux/world/db/jdbc.lux index 8fb53e9b0..e9df26b7f 100644 --- a/stdlib/source/library/lux/world/db/jdbc.lux +++ b/stdlib/source/library/lux/world/db/jdbc.lux @@ -1,29 +1,29 @@ (.module: [library - [lux (#- and int) + [lux {"-" [and int]} [control - [functor (#+ Functor)] - [apply (#+ Apply)] - [monad (#+ Monad do)] - ["." try (#+ Try)] + [functor {"+" [Functor]}] + [apply {"+" [Apply]}] + [monad {"+" [Monad do]}] + ["." try {"+" [Try]}] ["ex" exception] [concurrency - ["." async (#+ Async) ("#\." monad)]] + ["." async {"+" [Async]} ("#\." monad)]] [security - ["!" capability (#+ capability:)]]] + ["!" capability {"+" [capability:]}]]] [data ["." product] [text - ["%" format (#+ format)]]] - ["." io (#+ IO)] + ["%" format {"+" [format]}]]] + ["." io {"+" [IO]}] [world - [net (#+ URL)]] - [host (#+ import:)]]] + [net {"+" [URL]}]] + [host {"+" [import:]}]]] [// ["." sql]] - ["." / #_ - ["#." input (#+ Input)] - ["#." output (#+ Output)]]) + ["." / "_" + ["#." input {"+" [Input]}] + ["#." output {"+" [Output]}]]) (import: java/lang/String) diff --git a/stdlib/source/library/lux/world/db/jdbc/input.lux b/stdlib/source/library/lux/world/db/jdbc/input.lux index 633663bcf..790e60c83 100644 --- a/stdlib/source/library/lux/world/db/jdbc/input.lux +++ b/stdlib/source/library/lux/world/db/jdbc/input.lux @@ -1,16 +1,16 @@ (.module: [library - [lux (#- and int) - [ffi (#+ import:)] + [lux {"-" [and int]} + [ffi {"+" [import:]}] [control - [functor (#+ Contravariant)] - [monad (#+ Monad do)] - ["." try (#+ Try)]] + [functor {"+" [Contravariant]}] + [monad {"+" [Monad do]}] + ["." try {"+" [Try]}]] [time - ["." instant (#+ Instant)]] - ["." io (#+ IO)] + ["." instant {"+" [Instant]}]] + ["." io {"+" [IO]}] [world - [binary (#+ Binary)]]]]) + [binary {"+" [Binary]}]]]]) (import: java/lang/String) diff --git a/stdlib/source/library/lux/world/db/jdbc/output.lux b/stdlib/source/library/lux/world/db/jdbc/output.lux index dd3e19751..c36a4f2c0 100644 --- a/stdlib/source/library/lux/world/db/jdbc/output.lux +++ b/stdlib/source/library/lux/world/db/jdbc/output.lux @@ -1,18 +1,18 @@ (.module: [library - [lux (#- and int) - [ffi (#+ import:)] + [lux {"-" [and int]} + [ffi {"+" [import:]}] [control - [functor (#+ Functor)] - [apply (#+ Apply)] - [monad (#+ Monad do)] + [functor {"+" [Functor]}] + [apply {"+" [Apply]}] + [monad {"+" [Monad do]}] ["ex" exception] - ["." try (#+ Try)]] + ["." try {"+" [Try]}]] [time - ["." instant (#+ Instant)]] - ["." io (#+ IO)] + ["." instant {"+" [Instant]}]] + ["." io {"+" [IO]}] [world - [binary (#+ Binary)]]]]) + [binary {"+" [Binary]}]]]]) (import: java/lang/String) diff --git a/stdlib/source/library/lux/world/db/sql.lux b/stdlib/source/library/lux/world/db/sql.lux index aff994825..1db248bbb 100644 --- a/stdlib/source/library/lux/world/db/sql.lux +++ b/stdlib/source/library/lux/world/db/sql.lux @@ -1,13 +1,13 @@ (.module: [library - [lux (#- Source Definition function and or not type int) + [lux {"-" [Source Definition function and or not type int]} [control - [monad (#+ do)]] + [monad {"+" [do]}]] [data [number ["i" int]] ["." text ("#\." equivalence) - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection ["." list ("#\." functor)]]] [macro diff --git a/stdlib/source/library/lux/world/file.lux b/stdlib/source/library/lux/world/file.lux index 377f07b4f..8589e5f90 100644 --- a/stdlib/source/library/lux/world/file.lux +++ b/stdlib/source/library/lux/world/file.lux @@ -1,30 +1,30 @@ (.module: [library - [lux #* + [lux "*" ["@" target] ["." ffi] [abstract - ["." monad (#+ Monad do)]] + ["." monad {"+" [Monad do]}]] [control - [pipe (#+ case>)] + [pipe {"+" [case>]}] ["." maybe ("#\." functor)] - ["." try (#+ Try) ("#\." functor)] - ["." exception (#+ exception:)] - ["." io (#+ IO) ("#\." functor)] + ["." try {"+" [Try]} ("#\." functor)] + ["." exception {"+" [exception:]}] + ["." io {"+" [IO]} ("#\." functor)] ["." function] [concurrency - ["." async (#+ Async)] - ["." stm (#+ Var STM)]]] + ["." async {"+" [Async]}] + ["." stm {"+" [Var STM]}]]] [data ["." bit ("#\." equivalence)] ["." product] - ["." binary (#+ Binary)] + ["." binary {"+" [Binary]}] ["." text ("#\." equivalence) - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection - ["." array (#+ Array)] + ["." array {"+" [Array]}] ["." list ("#\." functor)] - ["." dictionary (#+ Dictionary)]]] + ["." dictionary {"+" [Dictionary]}]]] [macro ["." template]] [math @@ -32,7 +32,7 @@ ["i" int] ["f" frac]]] [time - ["." instant (#+ Instant)] + ["." instant {"+" [Instant]}] ["." duration]]]]) (type: .public Path diff --git a/stdlib/source/library/lux/world/file/watch.lux b/stdlib/source/library/lux/world/file/watch.lux index b094a1e0d..0bbc4643c 100644 --- a/stdlib/source/library/lux/world/file/watch.lux +++ b/stdlib/source/library/lux/world/file/watch.lux @@ -1,25 +1,25 @@ (.module: [library - [lux #* + [lux "*" ["@" target] - ["." ffi (#+ import:)] + ["." ffi {"+" [import:]}] [abstract - [predicate (#+ Predicate)] - ["." monad (#+ do)]] + [predicate {"+" [Predicate]}] + ["." monad {"+" [do]}]] [control - ["." io (#+ IO)] + ["." io {"+" [IO]}] ["." maybe] - ["." try (#+ Try)] - ["." exception (#+ exception:)] + ["." try {"+" [Try]}] + ["." exception {"+" [exception:]}] [concurrency - ["." async (#+ Async)] - ["." stm (#+ STM Var)]]] + ["." async {"+" [Async]}] + ["." stm {"+" [STM Var]}]]] [data ["." product] ["." text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection - ["." dictionary (#+ Dictionary)] + ["." dictionary {"+" [Dictionary]}] ["." list ("#\." functor monoid mix)] ["." set] ["." array]]] @@ -27,9 +27,9 @@ [number ["n" nat]]] [time - ["." instant (#+ Instant) ("#\." equivalence)]] + ["." instant {"+" [Instant]} ("#\." equivalence)]] [type - [abstract (#+ abstract: :representation :abstraction)]]]] + [abstract {"+" [abstract: :representation :abstraction]}]]]] ["." //]) (abstract: .public Concern diff --git a/stdlib/source/library/lux/world/input/keyboard.lux b/stdlib/source/library/lux/world/input/keyboard.lux index b3b64f1d1..1089d79ae 100644 --- a/stdlib/source/library/lux/world/input/keyboard.lux +++ b/stdlib/source/library/lux/world/input/keyboard.lux @@ -1,6 +1,6 @@ (.module: [library - [lux #*]]) + [lux "*"]]) (type: .public Key Nat) diff --git a/stdlib/source/library/lux/world/net.lux b/stdlib/source/library/lux/world/net.lux index 4f5626900..940c86fec 100644 --- a/stdlib/source/library/lux/world/net.lux +++ b/stdlib/source/library/lux/world/net.lux @@ -1,6 +1,6 @@ (.module: [library - [lux (#- Location)]]) + [lux {"-" [Location]}]]) (type: .public Address Text) diff --git a/stdlib/source/library/lux/world/net/http.lux b/stdlib/source/library/lux/world/net/http.lux index b34b904c9..05466bc1c 100644 --- a/stdlib/source/library/lux/world/net/http.lux +++ b/stdlib/source/library/lux/world/net/http.lux @@ -1,16 +1,16 @@ (.module: [library - [lux #* + [lux "*" [control - [try (#+ Try)] + [try {"+" [Try]}] [concurrency - [frp (#+ Channel)]] + [frp {"+" [Channel]}]] [parser - ["." environment (#+ Environment)]]] + ["." environment {"+" [Environment]}]]] [data - [binary (#+ Binary)]]]] - [// (#+ URL) - [uri (#+ URI)]]) + [binary {"+" [Binary]}]]]] + [// {"+" [URL]} + [uri {"+" [URI]}]]) (type: .public Version Text) diff --git a/stdlib/source/library/lux/world/net/http/client.lux b/stdlib/source/library/lux/world/net/http/client.lux index c3d70e625..bee4a6466 100644 --- a/stdlib/source/library/lux/world/net/http/client.lux +++ b/stdlib/source/library/lux/world/net/http/client.lux @@ -1,26 +1,26 @@ (.module: [library - [lux #* + [lux "*" ["@" target] ["." ffi] [abstract - ["." monad (#+ do)]] + ["." monad {"+" [do]}]] [control - [pipe (#+ case>)] - ["." io (#+ IO)] + [pipe {"+" [case>]}] + ["." io {"+" [IO]}] ["." maybe ("#\." functor)] - ["." try (#+ Try)] + ["." try {"+" [Try]}] [concurrency - ["." async (#+ Async)]] + ["." async {"+" [Async]}]] [parser ["<.>" code]]] [data - ["." binary (#+ Binary)] + ["." binary {"+" [Binary]}] ["." text] [collection ["." dictionary]]] [macro - [syntax (#+ syntax:)] + [syntax {"+" [syntax:]}] ["." code] ["." template]] [math @@ -28,7 +28,7 @@ ["n" nat] ["i" int]]]]] ["." // - [// (#+ URL)]]) + [// {"+" [URL]}]]) (type: .public (Client !) (Interface diff --git a/stdlib/source/library/lux/world/net/http/cookie.lux b/stdlib/source/library/lux/world/net/http/cookie.lux index bb93c2c82..1f894d194 100644 --- a/stdlib/source/library/lux/world/net/http/cookie.lux +++ b/stdlib/source/library/lux/world/net/http/cookie.lux @@ -1,23 +1,23 @@ (.module: [library - [lux #* + [lux "*" [control - [monad (#+ do)] - ["." try (#+ Try)] + [monad {"+" [do]}] + ["." try {"+" [Try]}] ["p" parser ("#\." monad) - ["l" text (#+ Parser)]]] + ["l" text {"+" [Parser]}]]] [data [number ["i" int]] [text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [format - ["." context (#+ Context)]] + ["." context {"+" [Context]}]] [collection ["." dictionary]]] [time - ["." duration (#+ Duration)]]]] - ["." // (#+ Header) + ["." duration {"+" [Duration]}]]]] + ["." // {"+" [Header]} ["." header]]) (type: .public Directive diff --git a/stdlib/source/library/lux/world/net/http/header.lux b/stdlib/source/library/lux/world/net/http/header.lux index 5b5a20194..d593ee3e5 100644 --- a/stdlib/source/library/lux/world/net/http/header.lux +++ b/stdlib/source/library/lux/world/net/http/header.lux @@ -1,16 +1,16 @@ (.module: [library - [lux #* + [lux "*" [control - [pipe (#+ case>)]] + [pipe {"+" [case>]}]] [data [text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection - ["." dictionary (#+ Dictionary)]]]]] - [// (#+ Header) - ["." mime (#+ MIME)] - [// (#+ URL)]]) + ["." dictionary {"+" [Dictionary]}]]]]] + [// {"+" [Header]} + ["." mime {"+" [MIME]}] + [// {"+" [URL]}]]) (def: .public (has name value) (-> Text Text Header) diff --git a/stdlib/source/library/lux/world/net/http/mime.lux b/stdlib/source/library/lux/world/net/http/mime.lux index 5df977504..6f18a1399 100644 --- a/stdlib/source/library/lux/world/net/http/mime.lux +++ b/stdlib/source/library/lux/world/net/http/mime.lux @@ -1,10 +1,10 @@ (.module: [library - [lux #* + [lux "*" [data ["." text - ["%" format (#+ format)] - ["." encoding (#+ Encoding)]]] + ["%" format {"+" [format]}] + ["." encoding {"+" [Encoding]}]]] [type abstract]]]) diff --git a/stdlib/source/library/lux/world/net/http/query.lux b/stdlib/source/library/lux/world/net/http/query.lux index 1f71fbcc7..e6a719c3b 100644 --- a/stdlib/source/library/lux/world/net/http/query.lux +++ b/stdlib/source/library/lux/world/net/http/query.lux @@ -1,19 +1,19 @@ (.module: [library - [lux #* + [lux "*" [control pipe - [monad (#+ do)] - ["." try (#+ Try)] + [monad {"+" [do]}] + ["." try {"+" [Try]}] ["p" parser - ["l" text (#+ Parser)]]] + ["l" text {"+" [Parser]}]]] [data [number ["." nat]] ["." text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [format - ["." context (#+ Context)]] + ["." context {"+" [Context]}]] [collection ["." dictionary]]]]]) diff --git a/stdlib/source/library/lux/world/net/http/request.lux b/stdlib/source/library/lux/world/net/http/request.lux index 1db8ac044..8ab8781cf 100644 --- a/stdlib/source/library/lux/world/net/http/request.lux +++ b/stdlib/source/library/lux/world/net/http/request.lux @@ -1,13 +1,13 @@ (.module: [library - [lux #* + [lux "*" [control pipe - ["." monad (#+ do)] + ["." monad {"+" [do]}] ["." maybe] - ["." try (#+ Try)] + ["." try {"+" [Try]}] [concurrency - ["." async (#+ Async)] + ["." async {"+" [Async]}] ["." frp]] [parser ["<.>" json]]] @@ -17,14 +17,14 @@ ["." text ["." encoding]] [format - ["." json (#+ JSON)] - ["." context (#+ Context Property)]] + ["." json {"+" [JSON]}] + ["." context {"+" [Context Property]}]] [collection ["." list ("#\." functor mix)] ["." dictionary]]] [world - ["." binary (#+ Binary)]]]] - ["." // (#+ Body Response Server) + ["." binary {"+" [Binary]}]]]] + ["." // {"+" [Body Response Server]} ["#." response] ["#." query] ["#." cookie]]) diff --git a/stdlib/source/library/lux/world/net/http/response.lux b/stdlib/source/library/lux/world/net/http/response.lux index 26a1e10fd..a69eacb5c 100644 --- a/stdlib/source/library/lux/world/net/http/response.lux +++ b/stdlib/source/library/lux/world/net/http/response.lux @@ -1,6 +1,6 @@ (.module: [library - [lux (#- static) + [lux {"-" [static]} [control [concurrency ["." async] @@ -10,17 +10,17 @@ ["." encoding]] [format ["." html] - ["." css (#+ CSS)] + ["." css {"+" [CSS]}] ["." context] - ["." json (#+ JSON) ("#\." codec)]]] + ["." json {"+" [JSON]} ("#\." codec)]]] ["." io] [world - ["." binary (#+ Binary)]]]] - ["." // (#+ Status Body Response Server) + ["." binary {"+" [Binary]}]]]] + ["." // {"+" [Status Body Response Server]} ["." status] - ["." mime (#+ MIME)] + ["." mime {"+" [MIME]}] ["." header] - [// (#+ URL)]]) + [// {"+" [URL]}]]) (def: .public (static response) (-> Response Server) diff --git a/stdlib/source/library/lux/world/net/http/route.lux b/stdlib/source/library/lux/world/net/http/route.lux index c3bcd9be6..07578b549 100644 --- a/stdlib/source/library/lux/world/net/http/route.lux +++ b/stdlib/source/library/lux/world/net/http/route.lux @@ -1,8 +1,8 @@ (.module: [library - [lux (#- or) + [lux {"-" [or]} [control - [monad (#+ do)] + [monad {"+" [do]}] ["." maybe] [concurrency ["." async]]] @@ -10,7 +10,7 @@ ["." text] [number ["n" nat]]]]] - ["." // (#+ URI Server) + ["." // {"+" [URI Server]} ["#." status] ["#." response]]) diff --git a/stdlib/source/library/lux/world/net/http/status.lux b/stdlib/source/library/lux/world/net/http/status.lux index e7810c7fa..829f078f1 100644 --- a/stdlib/source/library/lux/world/net/http/status.lux +++ b/stdlib/source/library/lux/world/net/http/status.lux @@ -1,7 +1,7 @@ (.module: [library - [lux #*]] - [// (#+ Status)]) + [lux "*"]] + [// {"+" [Status]}]) ... https://en.wikipedia.org/wiki/List_of_HTTP_status_codes (template [<status> <name>] diff --git a/stdlib/source/library/lux/world/net/http/version.lux b/stdlib/source/library/lux/world/net/http/version.lux index 535d4736a..7f6cf852b 100644 --- a/stdlib/source/library/lux/world/net/http/version.lux +++ b/stdlib/source/library/lux/world/net/http/version.lux @@ -1,7 +1,7 @@ (.module: [library - [lux #*]] - [// (#+ Version)]) + [lux "*"]] + [// {"+" [Version]}]) (template [<name> <version>] [(def: .public <name> Version <version>)] diff --git a/stdlib/source/library/lux/world/net/uri.lux b/stdlib/source/library/lux/world/net/uri.lux index b25d6c40e..b8883276f 100644 --- a/stdlib/source/library/lux/world/net/uri.lux +++ b/stdlib/source/library/lux/world/net/uri.lux @@ -1,6 +1,6 @@ (.module: [library - [lux #*]]) + [lux "*"]]) ... https://en.wikipedia.org/wiki/Uniform_Resource_Identifier (type: .public URI diff --git a/stdlib/source/library/lux/world/output/video/resolution.lux b/stdlib/source/library/lux/world/output/video/resolution.lux index 3f79a0040..81a0e96b8 100644 --- a/stdlib/source/library/lux/world/output/video/resolution.lux +++ b/stdlib/source/library/lux/world/output/video/resolution.lux @@ -1,9 +1,9 @@ (.module: [library - [lux #* + [lux "*" [abstract - [equivalence (#+ Equivalence)] - [hash (#+ Hash)]] + [equivalence {"+" [Equivalence]}] + [hash {"+" [Hash]}]] [data ["." product]] [math diff --git a/stdlib/source/library/lux/world/program.lux b/stdlib/source/library/lux/world/program.lux index 1a8304c8a..52a579f79 100644 --- a/stdlib/source/library/lux/world/program.lux +++ b/stdlib/source/library/lux/world/program.lux @@ -1,28 +1,28 @@ (.module: [library - [lux #* + [lux "*" ["@" target] - ["." ffi (#+ import:)] + ["." ffi {"+" [import:]}] [abstract - ["." monad (#+ Monad do)]] + ["." monad {"+" [Monad do]}]] [control ["." function] - ["." io (#+ IO)] + ["." io {"+" [IO]}] ["." maybe] - ["." try (#+ Try)] - ["." exception (#+ exception:)] + ["." try {"+" [Try]}] + ["." exception {"+" [exception:]}] [concurrency ["." atom] - ["." async (#+ Async)]] + ["." async {"+" [Async]}]] [parser - ["." environment (#+ Environment)]]] + ["." environment {"+" [Environment]}]]] [data ["." bit ("#\." equivalence)] ["." text - ["%" format (#+ format)]] + ["%" format {"+" [format]}]] [collection - ["." array (#+ Array)] - ["." dictionary (#+ Dictionary)] + ["." array {"+" [Array]}] + ["." dictionary {"+" [Dictionary]}] ["." list ("#\." functor)]]] ["." macro ["." template]] @@ -32,8 +32,8 @@ [type abstract]]] [// - [file (#+ Path)] - [shell (#+ Exit)]]) + [file {"+" [Path]}] + [shell {"+" [Exit]}]]) (exception: .public (unknown_environment_variable {name Text}) (exception.report diff --git a/stdlib/source/library/lux/world/service/authentication.lux b/stdlib/source/library/lux/world/service/authentication.lux index 1916f1238..141f24e55 100644 --- a/stdlib/source/library/lux/world/service/authentication.lux +++ b/stdlib/source/library/lux/world/service/authentication.lux @@ -1,10 +1,10 @@ (.module: [library - [lux #* + [lux "*" [control - [try (#+ Try)] + [try {"+" [Try]}] [security - [capability (#+ Capability)]]]]]) + [capability {"+" [Capability]}]]]]]) (type: .public (Can_Register ! account secret value) (Capability [account secret value] (! (Try Any)))) diff --git a/stdlib/source/library/lux/world/service/crud.lux b/stdlib/source/library/lux/world/service/crud.lux index 5635bc1c3..876f5e4cb 100644 --- a/stdlib/source/library/lux/world/service/crud.lux +++ b/stdlib/source/library/lux/world/service/crud.lux @@ -1,12 +1,12 @@ (.module: [library - [lux #* + [lux "*" [control - ["." try (#+ Try)] + ["." try {"+" [Try]}] [security - ["!" capability (#+ capability:)]]] + ["!" capability {"+" [capability:]}]]] [time - ["." instant (#+ Instant)]]]]) + ["." instant {"+" [Instant]}]]]]) (type: .public ID Nat) diff --git a/stdlib/source/library/lux/world/service/inventory.lux b/stdlib/source/library/lux/world/service/inventory.lux index 6f1ca494a..964809212 100644 --- a/stdlib/source/library/lux/world/service/inventory.lux +++ b/stdlib/source/library/lux/world/service/inventory.lux @@ -1,10 +1,10 @@ (.module: [library - [lux #* + [lux "*" [control - [try (#+ Try)] + [try {"+" [Try]}] [security - ["!" capability (#+ capability:)]]]]]) + ["!" capability {"+" [capability:]}]]]]]) (type: .public ID Nat) diff --git a/stdlib/source/library/lux/world/service/journal.lux b/stdlib/source/library/lux/world/service/journal.lux index 311be09bf..878da3eb7 100644 --- a/stdlib/source/library/lux/world/service/journal.lux +++ b/stdlib/source/library/lux/world/service/journal.lux @@ -1,16 +1,16 @@ (.module: [library - [lux #* + [lux "*" [control - [equivalence (#+ Equivalence)] - [interval (#+ Interval)] - [try (#+ Try)] + [equivalence {"+" [Equivalence]}] + [interval {"+" [Interval]}] + [try {"+" [Try]}] [security - ["!" capability (#+ capability:)]]] + ["!" capability {"+" [capability:]}]]] [data ["." text ("#\." equivalence)]] [time - ["." instant (#+ Instant) ("#\." equivalence)]]]]) + ["." instant {"+" [Instant]} ("#\." equivalence)]]]]) (type: .public (Entry a) (Record diff --git a/stdlib/source/library/lux/world/service/mail.lux b/stdlib/source/library/lux/world/service/mail.lux index 9a7384a71..5d4256c20 100644 --- a/stdlib/source/library/lux/world/service/mail.lux +++ b/stdlib/source/library/lux/world/service/mail.lux @@ -1,12 +1,12 @@ (.module: [library - [lux #* + [lux "*" [control - [try (#+ Try)] + [try {"+" [Try]}] [concurrency - [frp (#+ Channel)]] + [frp {"+" [Channel]}]] [security - ["!" capability (#+ capability:)]]]]]) + ["!" capability {"+" [capability:]}]]]]]) (capability: .public (Can_Send ! address message) (can_send [address message] (! (Try Any)))) diff --git a/stdlib/source/library/lux/world/shell.lux b/stdlib/source/library/lux/world/shell.lux index 216b2c856..186d241d4 100644 --- a/stdlib/source/library/lux/world/shell.lux +++ b/stdlib/source/library/lux/world/shell.lux @@ -1,37 +1,37 @@ (.module: [library - [lux #* + [lux "*" ["@" target] - ["jvm" ffi (#+ import:)] + ["jvm" ffi {"+" [import:]}] [abstract - [monad (#+ do)]] + [monad {"+" [do]}]] [control ["." function] - ["." try (#+ Try)] - ["." exception (#+ exception:)] - ["." io (#+ IO)] + ["." try {"+" [Try]}] + ["." exception {"+" [exception:]}] + ["." io {"+" [IO]}] [security - ["?" policy (#+ Context Safety Safe)]] + ["?" policy {"+" [Context Safety Safe]}]] [concurrency - ["." atom (#+ Atom)] - ["." async (#+ Async)]] + ["." atom {"+" [Atom]}] + ["." async {"+" [Async]}]] [parser - [environment (#+ Environment)]]] + [environment {"+" [Environment]}]]] [data ["." product] ["." text - ["%" format (#+ format)] + ["%" format {"+" [format]}] [encoding ["." utf8]]] [collection - ["." array (#+ Array)] + ["." array {"+" [Array]}] ["." list ("#\." mix functor)] ["." dictionary]]] [math - [number (#+ hex) + [number {"+" [hex]} ["n" nat]]]]] [// - [file (#+ Path)]]) + [file {"+" [Path]}]]) (type: .public Exit Int) |