From 392582885500d8201bbe502943ca4b02c5c77ac0 Mon Sep 17 00:00:00 2001 From: Eduardo Julian Date: Wed, 8 Sep 2021 03:08:13 -0400 Subject: Normalized the syntax of "abstract:" and "actor:". --- .../library/lux/control/concurrency/actor.lux | 327 ++- .../library/lux/control/concurrency/async.lux | 114 +- .../library/lux/control/concurrency/atom.lux | 46 +- .../library/lux/control/concurrency/semaphore.lux | 234 +- .../source/library/lux/control/concurrency/stm.lux | 92 +- stdlib/source/library/lux/control/io.lux | 76 +- stdlib/source/library/lux/control/lazy.lux | 32 +- .../library/lux/control/security/capability.lux | 78 +- .../source/library/lux/control/security/policy.lux | 146 +- stdlib/source/library/lux/control/thread.lux | 66 +- .../library/lux/data/collection/queue/priority.lux | 154 +- .../library/lux/data/collection/set/multi.lux | 222 +- .../library/lux/data/collection/set/ordered.lux | 116 +- .../source/library/lux/data/collection/stack.lux | 86 +- .../library/lux/data/collection/tree/finger.lux | 164 +- stdlib/source/library/lux/data/color.lux | 158 +- stdlib/source/library/lux/data/format/css.lux | 204 +- .../library/lux/data/format/css/property.lux | 886 ++++--- .../source/library/lux/data/format/css/query.lux | 194 +- .../library/lux/data/format/css/selector.lux | 340 ++- .../source/library/lux/data/format/css/style.lux | 32 +- .../source/library/lux/data/format/css/value.lux | 2548 ++++++++++---------- stdlib/source/library/lux/data/format/html.lux | 974 ++++---- stdlib/source/library/lux/data/format/markdown.lux | 326 ++- stdlib/source/library/lux/data/format/tar.lux | 568 +++-- stdlib/source/library/lux/data/text/buffer.lux | 138 +- stdlib/source/library/lux/data/text/encoding.lux | 298 ++- .../source/library/lux/data/text/unicode/block.lux | 70 +- .../source/library/lux/data/text/unicode/set.lux | 402 ++- stdlib/source/library/lux/ffi.js.lux | 11 +- stdlib/source/library/lux/ffi.lua.lux | 6 +- stdlib/source/library/lux/ffi.php.lux | 4 +- stdlib/source/library/lux/ffi.py.lux | 6 +- stdlib/source/library/lux/ffi.rb.lux | 6 +- stdlib/source/library/lux/ffi.scm.lux | 4 +- stdlib/source/library/lux/locale.lux | 42 +- stdlib/source/library/lux/locale/language.lux | 1110 +++++---- stdlib/source/library/lux/locale/territory.lux | 570 +++-- stdlib/source/library/lux/math/modular.lux | 214 +- stdlib/source/library/lux/math/modulus.lux | 44 +- stdlib/source/library/lux/target/common_lisp.lux | 870 ++++--- stdlib/source/library/lux/target/js.lux | 736 +++--- .../library/lux/target/jvm/bytecode/address.lux | 76 +- .../jvm/bytecode/environment/limit/registry.lux | 96 +- .../jvm/bytecode/environment/limit/stack.lux | 72 +- .../lux/target/jvm/bytecode/instruction.lux | 34 +- stdlib/source/library/lux/target/jvm/constant.lux | 118 +- .../source/library/lux/target/jvm/constant/tag.lux | 56 +- .../library/lux/target/jvm/encoding/name.lux | 32 +- .../library/lux/target/jvm/encoding/signed.lux | 136 +- .../library/lux/target/jvm/encoding/unsigned.lux | 188 +- stdlib/source/library/lux/target/jvm/index.lux | 30 +- stdlib/source/library/lux/target/jvm/modifier.lux | 84 +- .../library/lux/target/jvm/modifier/inner.lux | 2 +- stdlib/source/library/lux/target/jvm/type.lux | 324 +-- .../library/lux/target/jvm/type/category.lux | 16 +- .../library/lux/target/jvm/type/descriptor.lux | 196 +- stdlib/source/library/lux/target/jvm/type/lux.lux | 2 +- .../library/lux/target/jvm/type/reflection.lux | 142 +- .../library/lux/target/jvm/type/signature.lux | 276 ++- stdlib/source/library/lux/target/lua.lux | 630 +++-- stdlib/source/library/lux/target/php.lux | 946 ++++---- stdlib/source/library/lux/target/python.lux | 790 +++--- stdlib/source/library/lux/target/r.lux | 716 +++--- stdlib/source/library/lux/target/ruby.lux | 740 +++--- stdlib/source/library/lux/target/scheme.lux | 700 +++--- stdlib/source/library/lux/time.lux | 130 +- stdlib/source/library/lux/time/date.lux | 126 +- stdlib/source/library/lux/time/duration.lux | 114 +- stdlib/source/library/lux/time/instant.lux | 96 +- stdlib/source/library/lux/time/year.lux | 24 +- .../library/lux/tool/compiler/meta/archive.lux | 400 ++- .../lux/tool/compiler/meta/archive/artifact.lux | 240 +- .../lux/tool/compiler/meta/archive/document.lux | 72 +- .../library/lux/tool/compiler/meta/archive/key.lux | 14 +- stdlib/source/library/lux/type/abstract.lux | 24 +- stdlib/source/library/lux/type/dynamic.lux | 50 +- stdlib/source/library/lux/type/quotient.lux | 58 +- stdlib/source/library/lux/type/refinement.lux | 60 +- stdlib/source/library/lux/type/resource.lux | 52 +- stdlib/source/library/lux/type/unit.lux | 56 +- stdlib/source/library/lux/world/db/sql.lux | 816 +++---- stdlib/source/library/lux/world/file/watch.lux | 84 +- stdlib/source/library/lux/world/net/http/mime.lux | 14 +- stdlib/source/library/lux/world/program.lux | 4 +- 85 files changed, 10672 insertions(+), 10878 deletions(-) (limited to 'stdlib/source/library') diff --git a/stdlib/source/library/lux/control/concurrency/actor.lux b/stdlib/source/library/lux/control/concurrency/actor.lux index d127feec3..27d413c10 100644 --- a/stdlib/source/library/lux/control/concurrency/actor.lux +++ b/stdlib/source/library/lux/control/concurrency/actor.lux @@ -23,12 +23,11 @@ ["[0]" code] [syntax {"+" [syntax:]} ["|[0]|" input] - ["|[0]|" annotations]]] + ["|[0]|" export]]] [math [number ["n" nat]]] - ["[0]" meta {"+" [monad]} - ["[0]" annotation]] + ["[0]" meta {"+" [monad]}] [type {"+" [:sharing]} ["[0]" abstract {"+" [abstract: :representation :abstraction]}]]]] [// @@ -63,138 +62,136 @@ (in #.End)))) (abstract: .public (Actor s) - {} - (Record [#obituary [(Async ) (Resolver )] #mailbox (Atom )]) - (type: .public (Mail s) - ) - - (type: .public (Obituary s) - ) - - (type: .public (Behavior o s) - (Record - [#on_init (-> o s) - #on_mail (-> (Mail s) s (Actor s) (Async (Try s)))])) - - (def: .public (spawn! behavior init) - (All (_ o s) (-> (Behavior o s) o (IO (Actor s)))) - (io (let [[on_init on_mail] behavior - self (:sharing [o s] - (Behavior o s) - behavior - - (Actor s) - (:abstraction [#obituary (async.async []) - #mailbox (atom (async.async []))])) - process (loop [state (on_init init) - [|mailbox| _] (io.run! (atom.read! (value@ #mailbox (:representation self))))] - (do [! async.monad] - [[head tail] |mailbox| - ?state' (on_mail head state self)] - (case ?state' - (#try.Failure error) - (let [[_ resolve] (value@ #obituary (:representation self))] - (exec (io.run! - (do io.monad - [pending (..pending tail)] - (resolve [error state (#.Item head pending)]))) - (in []))) - - (#try.Success state') - (recur state' tail))))] - self))) - - (def: .public (alive? actor) - (All (_ s) (-> (Actor s) (IO Bit))) - (let [[obituary _] (value@ #obituary (:representation actor))] - (|> obituary - async.value - (\ io.functor each - (|>> (case> #.None - bit.yes - - _ - bit.no)))))) - - (def: .public (obituary' actor) - (All (_ s) (-> (Actor s) (IO (Maybe (Obituary s))))) - (let [[obituary _] (value@ #obituary (:representation actor))] - (async.value obituary))) - - (def: .public obituary - (All (_ s) (-> (Actor s) (Async (Obituary s)))) - (|>> :representation - (value@ #obituary) - product.left)) - - (def: .public (mail! mail actor) - (All (_ s) (-> (Mail s) (Actor s) (IO (Try Any)))) - (do [! io.monad] - [alive? (..alive? actor)] - (if alive? - (let [entry [mail (async.async [])]] - (do ! - [|mailbox|&resolve (atom.read! (value@ #mailbox (:representation actor)))] - (loop [[|mailbox| resolve] |mailbox|&resolve] - (do ! - [|mailbox| (async.value |mailbox|)] - (case |mailbox| - #.None - (do ! - [resolved? (resolve entry)] - (if resolved? - (do ! - [_ (atom.write! (product.right entry) (value@ #mailbox (:representation actor)))] - (in (#try.Success []))) - (recur |mailbox|&resolve))) - - (#.Some [_ |mailbox|']) - (recur |mailbox|')))))) - (in (exception.except ..dead []))))) - - (type: .public (Message s o) - (-> s (Actor s) (Async (Try [s o])))) - - (def: (mail message) - (All (_ s o) (-> (Message s o) [(Async (Try o)) (Mail s)])) - (let [[async resolve] (:sharing [s o] - (Message s o) - message - - [(Async (Try o)) - (Resolver (Try o))] - (async.async []))] - [async - (function (_ state self) - (do [! async.monad] - [outcome (message state self)] - (case outcome - (#try.Success [state' return]) - (exec - (io.run! (resolve (#try.Success return))) - (async.resolved (#try.Success state'))) - - (#try.Failure error) - (exec - (io.run! (resolve (#try.Failure error))) - (async.resolved (#try.Failure error))))))])) - - (def: .public (tell! message actor) - (All (_ s o) (-> (Message s o) (Actor s) (Async (Try o)))) - (let [[async mail] (..mail message)] - (do async.monad - [outcome (async.future (..mail! mail actor))] - (case outcome - (#try.Success) - async - - (#try.Failure error) - (in (#try.Failure error)))))) + [(type: .public (Mail s) + ) + + (type: .public (Obituary s) + ) + + (type: .public (Behavior o s) + (Record + [#on_init (-> o s) + #on_mail (-> (Mail s) s (Actor s) (Async (Try s)))])) + + (def: .public (spawn! behavior init) + (All (_ o s) (-> (Behavior o s) o (IO (Actor s)))) + (io (let [[on_init on_mail] behavior + self (:sharing [o s] + (Behavior o s) + behavior + + (Actor s) + (:abstraction [#obituary (async.async []) + #mailbox (atom (async.async []))])) + process (loop [state (on_init init) + [|mailbox| _] (io.run! (atom.read! (value@ #mailbox (:representation self))))] + (do [! async.monad] + [[head tail] |mailbox| + ?state' (on_mail head state self)] + (case ?state' + (#try.Failure error) + (let [[_ resolve] (value@ #obituary (:representation self))] + (exec (io.run! + (do io.monad + [pending (..pending tail)] + (resolve [error state (#.Item head pending)]))) + (in []))) + + (#try.Success state') + (recur state' tail))))] + self))) + + (def: .public (alive? actor) + (All (_ s) (-> (Actor s) (IO Bit))) + (let [[obituary _] (value@ #obituary (:representation actor))] + (|> obituary + async.value + (\ io.functor each + (|>> (case> #.None + bit.yes + + _ + bit.no)))))) + + (def: .public (obituary' actor) + (All (_ s) (-> (Actor s) (IO (Maybe (Obituary s))))) + (let [[obituary _] (value@ #obituary (:representation actor))] + (async.value obituary))) + + (def: .public obituary + (All (_ s) (-> (Actor s) (Async (Obituary s)))) + (|>> :representation + (value@ #obituary) + product.left)) + + (def: .public (mail! mail actor) + (All (_ s) (-> (Mail s) (Actor s) (IO (Try Any)))) + (do [! io.monad] + [alive? (..alive? actor)] + (if alive? + (let [entry [mail (async.async [])]] + (do ! + [|mailbox|&resolve (atom.read! (value@ #mailbox (:representation actor)))] + (loop [[|mailbox| resolve] |mailbox|&resolve] + (do ! + [|mailbox| (async.value |mailbox|)] + (case |mailbox| + #.None + (do ! + [resolved? (resolve entry)] + (if resolved? + (do ! + [_ (atom.write! (product.right entry) (value@ #mailbox (:representation actor)))] + (in (#try.Success []))) + (recur |mailbox|&resolve))) + + (#.Some [_ |mailbox|']) + (recur |mailbox|')))))) + (in (exception.except ..dead []))))) + + (type: .public (Message s o) + (-> s (Actor s) (Async (Try [s o])))) + + (def: (mail message) + (All (_ s o) (-> (Message s o) [(Async (Try o)) (Mail s)])) + (let [[async resolve] (:sharing [s o] + (Message s o) + message + + [(Async (Try o)) + (Resolver (Try o))] + (async.async []))] + [async + (function (_ state self) + (do [! async.monad] + [outcome (message state self)] + (case outcome + (#try.Success [state' return]) + (exec + (io.run! (resolve (#try.Success return))) + (async.resolved (#try.Success state'))) + + (#try.Failure error) + (exec + (io.run! (resolve (#try.Failure error))) + (async.resolved (#try.Failure error))))))])) + + (def: .public (tell! message actor) + (All (_ s o) (-> (Message s o) (Actor s) (Async (Try o)))) + (let [[async mail] (..mail message)] + (do async.monad + [outcome (async.future (..mail! mail actor))] + (case outcome + (#try.Success) + async + + (#try.Failure error) + (in (#try.Failure error))))))] ) ) @@ -228,13 +225,18 @@ (Parser Text) .local_identifier) +(def: on_mail^ + (Parser (Maybe On_MailC)) + (<>.maybe (.form (<>.and (.form (<>.after (.this! (' on_mail)) + ($_ <>.and ..argument ..argument ..argument))) + .any)))) + (def: behavior^ (Parser BehaviorC) - (let [on_mail_args ($_ <>.and ..argument ..argument ..argument)] - ($_ <>.and - (<>.maybe (.form (<>.and (.form (<>.after (.this! (' on_mail)) on_mail_args)) - .any))) - (<>.some .any)))) + (.tuple + ($_ <>.and + ..on_mail^ + (<>.some .any)))) (def: (on_mail g!_ ?on_mail) (-> Code (Maybe On_MailC) Code) @@ -250,37 +252,32 @@ (~ bodyC))))) (def: actorP - (Parser [Code [Text (List Text)] |annotations|.Annotations Code BehaviorC]) - (let [private ($_ <>.and - ..actor_decl^ - |annotations|.parser - .any - behavior^)] - ($_ <>.either - (<>.and .any private) - (<>.and (<>\in (` .private)) private)))) - -(syntax: .public (actor: [[export_policy [name vars] annotations state_type [?on_mail messages]] ..actorP]) + (Parser [Code [Text (List Text)] Code BehaviorC]) + (|export|.parser + ($_ <>.and + ..actor_decl^ + .any + behavior^))) + +(syntax: .public (actor: [[export_policy [name vars] state_type [?on_mail messages]] ..actorP]) (with_identifiers [g!_] (do meta.monad [g!type (macro.identifier (format name "_abstract_type")) .let [g!actor (code.local_identifier name) g!vars (list\each code.local_identifier vars)]] (in (list (` ((~! abstract:) (~ export_policy) ((~ g!type) (~+ g!vars)) - {} - (~ state_type) - (def: (~ export_policy) (~ g!actor) - (All ((~ g!_) (~+ g!vars)) - (..Behavior (~ state_type) ((~ g!type) (~+ g!vars)))) - [#..on_init (|>> ((~! abstract.:abstraction) (~ g!type))) - #..on_mail (~ (..on_mail g!_ ?on_mail))]) + [(def: (~ export_policy) (~ g!actor) + (All ((~ g!_) (~+ g!vars)) + (..Behavior (~ state_type) ((~ g!type) (~+ g!vars)))) + [#..on_init (|>> ((~! abstract.:abstraction) (~ g!type))) + #..on_mail (~ (..on_mail g!_ ?on_mail))]) - (~+ messages)))))))) + (~+ messages)]))))))) (syntax: .public (actor [[state_type init] (.record (<>.and .any .any)) - [?on_mail messages] behavior^]) + ?on_mail on_mail^]) (with_identifiers [g!_] (in (list (` (: ((~! io.IO) (..Actor (~ state_type))) (..spawn! (: (..Behavior (~ state_type) (~ state_type)) @@ -312,17 +309,14 @@ (<>.and .identifier (\ <>.monad in (list))))) (def: messageP - (Parser [Code Signature |annotations|.Annotations Code Code]) - (let [private ($_ <>.and - ..signature^ - (<>.else |annotations|.empty |annotations|.parser) - .any - .any)] - ($_ <>.either - (<>.and .any private) - (<>.and (<>\in (` .private)) private)))) - -(syntax: .public (message: [[export_policy signature annotations output_type body] ..messageP]) + (Parser [Code Signature Code Code]) + (|export|.parser + ($_ <>.and + ..signature^ + .any + .any))) + +(syntax: .public (message: [[export_policy signature output_type body] ..messageP]) (with_identifiers [g!_ g!return] (do meta.monad [actor_scope abstract.current @@ -335,7 +329,6 @@ g!state (|> signature (value@ #state) code.local_identifier) g!self (|> signature (value@ #self) code.local_identifier)]] (in (list (` (def: (~ export_policy) ((~ g!message) (~+ g!inputsC)) - (~ (|annotations|.format annotations)) (All ((~ g!_) (~+ g!all_vars)) (-> (~+ g!inputsT) (..Message (~ (value@ #abstract.abstraction actor_scope)) diff --git a/stdlib/source/library/lux/control/concurrency/async.lux b/stdlib/source/library/lux/control/concurrency/async.lux index aec52dcf9..903ac8bd9 100644 --- a/stdlib/source/library/lux/control/concurrency/async.lux +++ b/stdlib/source/library/lux/control/concurrency/async.lux @@ -18,66 +18,64 @@ ["[0]" atom {"+" [Atom atom]}]]) (abstract: .public (Async a) - {} - (Atom [(Maybe a) (List (-> a (IO Any)))]) - (type: .public (Resolver a) - (-> a (IO Bit))) - - ... Sets an async's value if it has not been done yet. - (def: (resolver async) - (All (_ a) (-> (Async a) (Resolver a))) - (function (resolve value) - (let [async (:representation async)] - (do [! io.monad] - [(^@ old [_value _observers]) (atom.read! async)] - (case _value - (#.Some _) - (in #0) - - #.None - (do ! - [.let [new [(#.Some value) #.None]] - succeeded? (atom.compare_and_swap! old new async)] - (if succeeded? - (do ! - [_ (monad.each ! (function (_ f) (f value)) - _observers)] - (in #1)) - (resolve value)))))))) - - (def: .public (resolved value) - (All (_ a) (-> a (Async a))) - (:abstraction (atom [(#.Some value) (list)]))) - - (def: .public (async _) - (All (_ a) (-> Any [(Async a) (Resolver a)])) - (let [async (:abstraction (atom [#.None (list)]))] - [async (..resolver async)])) - - (def: .public value - (All (_ a) (-> (Async a) (IO (Maybe a)))) - (|>> :representation - atom.read! - (\ io.functor each product.left))) - - (def: .public (upon! f async) - (All (_ a) (-> (-> a (IO Any)) (Async a) (IO Any))) - (do [! io.monad] - [.let [async (:representation async)] - (^@ old [_value _observers]) (atom.read! async)] - (case _value - (#.Some value) - (f value) - - #.None - (let [new [_value (#.Item f _observers)]] - (do ! - [swapped? (atom.compare_and_swap! old new async)] - (if swapped? - (in []) - (upon! f (:abstraction async)))))))) + [(type: .public (Resolver a) + (-> a (IO Bit))) + + ... Sets an async's value if it has not been done yet. + (def: (resolver async) + (All (_ a) (-> (Async a) (Resolver a))) + (function (resolve value) + (let [async (:representation async)] + (do [! io.monad] + [(^@ old [_value _observers]) (atom.read! async)] + (case _value + (#.Some _) + (in #0) + + #.None + (do ! + [.let [new [(#.Some value) #.None]] + succeeded? (atom.compare_and_swap! old new async)] + (if succeeded? + (do ! + [_ (monad.each ! (function (_ f) (f value)) + _observers)] + (in #1)) + (resolve value)))))))) + + (def: .public (resolved value) + (All (_ a) (-> a (Async a))) + (:abstraction (atom [(#.Some value) (list)]))) + + (def: .public (async _) + (All (_ a) (-> Any [(Async a) (Resolver a)])) + (let [async (:abstraction (atom [#.None (list)]))] + [async (..resolver async)])) + + (def: .public value + (All (_ a) (-> (Async a) (IO (Maybe a)))) + (|>> :representation + atom.read! + (\ io.functor each product.left))) + + (def: .public (upon! f async) + (All (_ a) (-> (-> a (IO Any)) (Async a) (IO Any))) + (do [! io.monad] + [.let [async (:representation async)] + (^@ old [_value _observers]) (atom.read! async)] + (case _value + (#.Some value) + (f value) + + #.None + (let [new [_value (#.Item f _observers)]] + (do ! + [swapped? (atom.compare_and_swap! old new async)] + (if swapped? + (in []) + (upon! f (:abstraction async))))))))] ) (def: .public resolved? diff --git a/stdlib/source/library/lux/control/concurrency/atom.lux b/stdlib/source/library/lux/control/concurrency/atom.lux index 802ea9298..6309f4f35 100644 --- a/stdlib/source/library/lux/control/concurrency/atom.lux +++ b/stdlib/source/library/lux/control/concurrency/atom.lux @@ -47,37 +47,35 @@ @.scheme "scheme array read"} (as_is))] (abstract: .public (Atom a) - {} - (with_expansions [ (java/util/concurrent/atomic/AtomicReference a)] (for {@.old @.jvm } (array.Array a))) - (def: .public (atom value) - (All (_ a) (-> a (Atom a))) - (:abstraction (with_expansions [ (java/util/concurrent/atomic/AtomicReference::new value)] - (for {@.old - @.jvm } - ( 0 value ( 1)))))) + [(def: .public (atom value) + (All (_ a) (-> a (Atom a))) + (:abstraction (with_expansions [ (java/util/concurrent/atomic/AtomicReference::new value)] + (for {@.old + @.jvm } + ( 0 value ( 1)))))) - (def: .public (read! atom) - (All (_ a) (-> (Atom a) (IO a))) - (io.io (with_expansions [ (java/util/concurrent/atomic/AtomicReference::get (:representation atom))] - (for {@.old - @.jvm } - ( 0 (:representation atom)))))) + (def: .public (read! atom) + (All (_ a) (-> (Atom a) (IO a))) + (io.io (with_expansions [ (java/util/concurrent/atomic/AtomicReference::get (:representation atom))] + (for {@.old + @.jvm } + ( 0 (:representation atom)))))) - (def: .public (compare_and_swap! current new atom) - (All (_ a) (-> a a (Atom a) (IO Bit))) - (io.io (with_expansions [ (java/util/concurrent/atomic/AtomicReference::compareAndSet current new (:representation atom))] - (for {@.old - @.jvm } - (let [old ( 0 (:representation atom))] - (if (same? old current) - (exec ( 0 new (:representation atom)) - true) - false)))))) + (def: .public (compare_and_swap! current new atom) + (All (_ a) (-> a a (Atom a) (IO Bit))) + (io.io (with_expansions [ (java/util/concurrent/atomic/AtomicReference::compareAndSet current new (:representation atom))] + (for {@.old + @.jvm } + (let [old ( 0 (:representation atom))] + (if (same? old current) + (exec ( 0 new (:representation atom)) + true) + false))))))] )) (def: .public (update! f atom) diff --git a/stdlib/source/library/lux/control/concurrency/semaphore.lux b/stdlib/source/library/lux/control/concurrency/semaphore.lux index 3b0461579..bcbd71158 100644 --- a/stdlib/source/library/lux/control/concurrency/semaphore.lux +++ b/stdlib/source/library/lux/control/concurrency/semaphore.lux @@ -31,95 +31,91 @@ #waiting_list (Queue (Resolver Any))])) (abstract: .public Semaphore - {} - (Atom State) - (def: most_positions_possible - (.nat (\ i.interval top))) - - (def: .public (semaphore initial_open_positions) - (-> Nat Semaphore) - (let [max_positions (n.min initial_open_positions - ..most_positions_possible)] - (:abstraction (atom.atom [#max_positions max_positions - #open_positions (.int max_positions) - #waiting_list queue.empty])))) - - (def: .public (wait! semaphore) - (Ex (_ k) (-> Semaphore (Async Any))) - (let [semaphore (:representation semaphore) - [signal sink] (: [(Async Any) (Resolver Any)] - (async.async []))] - (exec - (io.run! - (with_expansions [ (as_is (value@ #open_positions) (i.> -1))] - (do io.monad - [[_ state'] (atom.update! (|>> (revised@ #open_positions --) - (if> [] - [] - [(revised@ #waiting_list (queue.end sink))])) - semaphore)] - (with_expansions [ (sink []) - (in false)] - (if (|> state' ) - - ))))) - signal))) - - (exception: .public (semaphore_is_maxed_out {max_positions Nat}) - (exception.report - ["Max Positions" (%.nat max_positions)])) - - (def: .public (signal! semaphore) - (Ex (_ k) (-> Semaphore (Async (Try Int)))) - (let [semaphore (:representation semaphore)] - (async.future - (do [! io.monad] - [[pre post] (atom.update! (function (_ state) - (if (i.= (.int (value@ #max_positions state)) - (value@ #open_positions state)) - state - (|> state - (revised@ #open_positions ++) - (revised@ #waiting_list queue.next)))) - semaphore)] - (if (same? pre post) - (in (exception.except ..semaphore_is_maxed_out [(value@ #max_positions pre)])) - (do ! - [_ (case (queue.front (value@ #waiting_list pre)) - #.None - (in true) - - (#.Some sink) - (sink []))] - (in (#try.Success (value@ #open_positions post))))))))) + [(def: most_positions_possible + (.nat (\ i.interval top))) + + (def: .public (semaphore initial_open_positions) + (-> Nat Semaphore) + (let [max_positions (n.min initial_open_positions + ..most_positions_possible)] + (:abstraction (atom.atom [#max_positions max_positions + #open_positions (.int max_positions) + #waiting_list queue.empty])))) + + (def: .public (wait! semaphore) + (Ex (_ k) (-> Semaphore (Async Any))) + (let [semaphore (:representation semaphore) + [signal sink] (: [(Async Any) (Resolver Any)] + (async.async []))] + (exec + (io.run! + (with_expansions [ (as_is (value@ #open_positions) (i.> -1))] + (do io.monad + [[_ state'] (atom.update! (|>> (revised@ #open_positions --) + (if> [] + [] + [(revised@ #waiting_list (queue.end sink))])) + semaphore)] + (with_expansions [ (sink []) + (in false)] + (if (|> state' ) + + ))))) + signal))) + + (exception: .public (semaphore_is_maxed_out {max_positions Nat}) + (exception.report + ["Max Positions" (%.nat max_positions)])) + + (def: .public (signal! semaphore) + (Ex (_ k) (-> Semaphore (Async (Try Int)))) + (let [semaphore (:representation semaphore)] + (async.future + (do [! io.monad] + [[pre post] (atom.update! (function (_ state) + (if (i.= (.int (value@ #max_positions state)) + (value@ #open_positions state)) + state + (|> state + (revised@ #open_positions ++) + (revised@ #waiting_list queue.next)))) + semaphore)] + (if (same? pre post) + (in (exception.except ..semaphore_is_maxed_out [(value@ #max_positions pre)])) + (do ! + [_ (case (queue.front (value@ #waiting_list pre)) + #.None + (in true) + + (#.Some sink) + (sink []))] + (in (#try.Success (value@ #open_positions post)))))))))] ) (abstract: .public Mutex - {} - Semaphore - (def: .public (mutex _) - (-> Any Mutex) - (:abstraction (semaphore 1))) - - (def: acquire! - (-> Mutex (Async Any)) - (|>> :representation ..wait!)) - - (def: release! - (-> Mutex (Async Any)) - (|>> :representation ..signal!)) - - (def: .public (synchronize! mutex procedure) - (All (_ a) (-> Mutex (IO (Async a)) (Async a))) - (do async.monad - [_ (..acquire! mutex) - output (io.run! procedure) - _ (..release! mutex)] - (in output))) + [(def: .public (mutex _) + (-> Any Mutex) + (:abstraction (semaphore 1))) + + (def: acquire! + (-> Mutex (Async Any)) + (|>> :representation ..wait!)) + + (def: release! + (-> Mutex (Async Any)) + (|>> :representation ..signal!)) + + (def: .public (synchronize! mutex procedure) + (All (_ a) (-> Mutex (IO (Async a)) (Async a))) + (do async.monad + [_ (..acquire! mutex) + output (io.run! procedure) + _ (..release! mutex)] + (in output)))] ) (def: .public limit @@ -129,49 +125,47 @@ (:~ (refinement.type limit))) (abstract: .public Barrier - {} - (Record [#limit Limit #count (Atom Nat) #start_turnstile Semaphore #end_turnstile Semaphore]) - (def: .public (barrier limit) - (-> Limit Barrier) - (:abstraction [#limit limit - #count (atom.atom 0) - #start_turnstile (..semaphore 0) - #end_turnstile (..semaphore 0)])) - - (def: (un_block! times turnstile) - (-> Nat Semaphore (Async Any)) - (loop [step 0] - (if (n.< times step) + [(def: .public (barrier limit) + (-> Limit Barrier) + (:abstraction [#limit limit + #count (atom.atom 0) + #start_turnstile (..semaphore 0) + #end_turnstile (..semaphore 0)])) + + (def: (un_block! times turnstile) + (-> Nat Semaphore (Async Any)) + (loop [step 0] + (if (n.< times step) + (do async.monad + [outcome (..signal! turnstile)] + (recur (++ step))) + (\ async.monad in [])))) + + (template [ ] + [(def: ( (^:representation barrier)) + (-> Barrier (Async Any)) (do async.monad - [outcome (..signal! turnstile)] - (recur (++ step))) - (\ async.monad in [])))) - - (template [ ] - [(def: ( (^:representation barrier)) - (-> Barrier (Async Any)) - (do async.monad - [.let [limit (refinement.value (value@ #limit barrier)) - goal - [_ count] (io.run! (atom.update! (value@ #count barrier))) - reached? (n.= goal count)]] - (if reached? - (..un_block! (-- limit) (value@ barrier)) - (..wait! (value@ barrier)))))] - - [start! ++ limit #start_turnstile] - [end! -- 0 #end_turnstile] - ) - - (def: .public (block! barrier) - (-> Barrier (Async Any)) - (do async.monad - [_ (..start! barrier)] - (..end! barrier))) + [.let [limit (refinement.value (value@ #limit barrier)) + goal + [_ count] (io.run! (atom.update! (value@ #count barrier))) + reached? (n.= goal count)]] + (if reached? + (..un_block! (-- limit) (value@ barrier)) + (..wait! (value@ barrier)))))] + + [start! ++ limit #start_turnstile] + [end! -- 0 #end_turnstile] + ) + + (def: .public (block! barrier) + (-> Barrier (Async Any)) + (do async.monad + [_ (..start! barrier)] + (..end! barrier)))] ) diff --git a/stdlib/source/library/lux/control/concurrency/stm.lux b/stdlib/source/library/lux/control/concurrency/stm.lux index c62540890..6b89926ff 100644 --- a/stdlib/source/library/lux/control/concurrency/stm.lux +++ b/stdlib/source/library/lux/control/concurrency/stm.lux @@ -24,55 +24,53 @@ (-> a (IO Any))) (abstract: .public (Var a) - {} - (Atom [a (List (Sink a))]) - (def: .public (var value) - (All (_ a) (-> a (Var a))) - (:abstraction (atom.atom [value (list)]))) - - (def: read! - (All (_ a) (-> (Var a) a)) - (|>> :representation atom.read! io.run! product.left)) - - (def: (un_follow! sink var) - (All (_ a) (-> (Sink a) (Var a) (IO Any))) - (do io.monad - [_ (atom.update! (function (_ [value observers]) - [value (list.only (|>> (same? sink) not) observers)]) - (:representation var))] - (in []))) - - (def: (write! new_value var) - (All (_ a) (-> a (Var a) (IO Any))) - (do [! io.monad] - [.let [var' (:representation var)] - (^@ old [old_value observers]) (atom.read! var') - succeeded? (atom.compare_and_swap! old [new_value observers] var')] - (if succeeded? - (do ! - [_ (monad.each ! (function (_ sink) - (do ! - [result (\ sink feed new_value)] - (case result - (#try.Success _) - (in []) - - (#try.Failure _) - (un_follow! sink var)))) - observers)] - (in [])) - (write! new_value var)))) - - (def: .public (follow! target) - (All (_ a) (-> (Var a) (IO [(Channel a) (Sink a)]))) - (do io.monad - [.let [[channel sink] (frp.channel [])] - _ (atom.update! (function (_ [value observers]) - [value (#.Item sink observers)]) - (:representation target))] - (in [channel sink]))) + [(def: .public (var value) + (All (_ a) (-> a (Var a))) + (:abstraction (atom.atom [value (list)]))) + + (def: read! + (All (_ a) (-> (Var a) a)) + (|>> :representation atom.read! io.run! product.left)) + + (def: (un_follow! sink var) + (All (_ a) (-> (Sink a) (Var a) (IO Any))) + (do io.monad + [_ (atom.update! (function (_ [value observers]) + [value (list.only (|>> (same? sink) not) observers)]) + (:representation var))] + (in []))) + + (def: (write! new_value var) + (All (_ a) (-> a (Var a) (IO Any))) + (do [! io.monad] + [.let [var' (:representation var)] + (^@ old [old_value observers]) (atom.read! var') + succeeded? (atom.compare_and_swap! old [new_value observers] var')] + (if succeeded? + (do ! + [_ (monad.each ! (function (_ sink) + (do ! + [result (\ sink feed new_value)] + (case result + (#try.Success _) + (in []) + + (#try.Failure _) + (un_follow! sink var)))) + observers)] + (in [])) + (write! new_value var)))) + + (def: .public (follow! target) + (All (_ a) (-> (Var a) (IO [(Channel a) (Sink a)]))) + (do io.monad + [.let [[channel sink] (frp.channel [])] + _ (atom.update! (function (_ [value observers]) + [value (#.Item sink observers)]) + (:representation target))] + (in [channel sink])))] ) (type: (Tx_Frame a) diff --git a/stdlib/source/library/lux/control/io.lux b/stdlib/source/library/lux/control/io.lux index 8ff12b40b..654415bd3 100644 --- a/stdlib/source/library/lux/control/io.lux +++ b/stdlib/source/library/lux/control/io.lux @@ -15,54 +15,52 @@ ["[0]" template]]]]) (abstract: .public (IO a) - {} - (-> Any a) - (def: label - (All (_ _ a) (-> (-> Any a) (IO a))) - (|>> :abstraction)) + [(def: label + (All (_ _ a) (-> (-> Any a) (IO a))) + (|>> :abstraction)) - (template: (!io computation) - [(:abstraction (template.with_locals [g!func g!arg] - (function (g!func g!arg) - computation)))]) + (template: (!io computation) + [(:abstraction (template.with_locals [g!func g!arg] + (function (g!func g!arg) + computation)))]) - (template: (run!' io) - ... creatio ex nihilo - [((:representation io) [])]) + (template: (run!' io) + ... creatio ex nihilo + [((:representation io) [])]) - (syntax: .public (io [computation .any]) - (with_identifiers [g!func g!arg] - (in (list (` ((~! ..label) (function ((~ g!func) (~ g!arg)) - (~ computation)))))))) + (syntax: .public (io [computation .any]) + (with_identifiers [g!func g!arg] + (in (list (` ((~! ..label) (function ((~ g!func) (~ g!arg)) + (~ computation)))))))) - (def: .public run! - (All (_ _ a) (-> (IO a) a)) - (|>> ..run!')) + (def: .public run! + (All (_ _ a) (-> (IO a) a)) + (|>> ..run!')) - (implementation: .public functor - (Functor IO) - - (def: (each f) - (|>> ..run!' f !io))) + (implementation: .public functor + (Functor IO) + + (def: (each f) + (|>> ..run!' f !io))) - (implementation: .public apply - (Apply IO) - - (def: &functor ..functor) + (implementation: .public apply + (Apply IO) + + (def: &functor ..functor) - (def: (on fa ff) - (!io ((..run!' ff) (..run!' fa))))) + (def: (on fa ff) + (!io ((..run!' ff) (..run!' fa))))) - (implementation: .public monad - (Monad IO) - - (def: &functor ..functor) + (implementation: .public monad + (Monad IO) + + (def: &functor ..functor) - (def: in - (|>> !io)) - - (def: conjoint - (|>> ..run!' ..run!' !io))) + (def: in + (|>> !io)) + + (def: conjoint + (|>> ..run!' ..run!' !io)))] ) diff --git a/stdlib/source/library/lux/control/lazy.lux b/stdlib/source/library/lux/control/lazy.lux index e38166d14..16b501d9e 100644 --- a/stdlib/source/library/lux/control/lazy.lux +++ b/stdlib/source/library/lux/control/lazy.lux @@ -18,27 +18,25 @@ abstract]]]) (abstract: .public (Lazy a) - {} - (-> [] a) - (def: (lazy' generator) - (All (_ a) (-> (-> [] a) (Lazy a))) - (let [cache (atom.atom #.None)] - (:abstraction (function (_ _) - (case (io.run! (atom.read! cache)) - (#.Some value) - value + [(def: (lazy' generator) + (All (_ a) (-> (-> [] a) (Lazy a))) + (let [cache (atom.atom #.None)] + (:abstraction (function (_ _) + (case (io.run! (atom.read! cache)) + (#.Some value) + value - _ - (let [value (generator [])] - (exec - (io.run! (atom.compare_and_swap! _ (#.Some value) cache)) - value))))))) + _ + (let [value (generator [])] + (exec + (io.run! (atom.compare_and_swap! _ (#.Some value) cache)) + value))))))) - (def: .public (value lazy) - (All (_ a) (-> (Lazy a) a)) - ((:representation lazy) []))) + (def: .public (value lazy) + (All (_ a) (-> (Lazy a) a)) + ((:representation lazy) []))]) (syntax: .public (lazy [expression .any]) (with_identifiers [g!_] diff --git a/stdlib/source/library/lux/control/security/capability.lux b/stdlib/source/library/lux/control/security/capability.lux index 49b19e07f..5d7ff9ebb 100644 --- a/stdlib/source/library/lux/control/security/capability.lux +++ b/stdlib/source/library/lux/control/security/capability.lux @@ -25,49 +25,47 @@ ["|[0]|" annotations]]]]]) (abstract: .public (Capability brand input output) - {} - (-> input output) - (def: capability - (All (_ brand input output) - (-> (-> input output) - (Capability brand input output))) - (|>> :abstraction)) + [(def: capability + (All (_ brand input output) + (-> (-> input output) + (Capability brand input output))) + (|>> :abstraction)) - (def: .public (use capability input) - (All (_ brand input output) - (-> (Capability brand input output) - input - output)) - ((:representation capability) input)) + (def: .public (use capability input) + (All (_ brand input output) + (-> (Capability brand input output) + input + output)) + ((:representation capability) input)) - (syntax: .public (capability: [[export_policy declaration annotations [forger input output]] - (|export|.parser - ($_ <>.and - |declaration|.parser - (<>.maybe |annotations|.parser) - (.form ($_ <>.and .local_identifier .any .any))))]) - (macro.with_identifiers [g!_] - (do [! meta.monad] - [this_module meta.current_module_name - .let [[name vars] declaration] - g!brand (\ ! each (|>> %.code code.text) - (macro.identifier (format (%.name [this_module name])))) - .let [capability (` (..Capability (.primitive (~ g!brand)) (~ input) (~ output)))]] - (in (list (` (type: (~ export_policy) - (~ (|declaration|.format declaration)) - (~ capability))) - (` (def: (~ (code.local_identifier forger)) - (All ((~ g!_) (~+ (list\each code.local_identifier vars))) - (-> (-> (~ input) (~ output)) - (~ capability))) - (~! ..capability))) - ))))) + (syntax: .public (capability: [[export_policy declaration annotations [forger input output]] + (|export|.parser + ($_ <>.and + |declaration|.parser + (<>.maybe |annotations|.parser) + (.form ($_ <>.and .local_identifier .any .any))))]) + (macro.with_identifiers [g!_] + (do [! meta.monad] + [this_module meta.current_module_name + .let [[name vars] declaration] + g!brand (\ ! each (|>> %.code code.text) + (macro.identifier (format (%.name [this_module name])))) + .let [capability (` (..Capability (.primitive (~ g!brand)) (~ input) (~ output)))]] + (in (list (` (type: (~ export_policy) + (~ (|declaration|.format declaration)) + (~ capability))) + (` (def: (~ (code.local_identifier forger)) + (All ((~ g!_) (~+ (list\each code.local_identifier vars))) + (-> (-> (~ input) (~ output)) + (~ capability))) + (~! ..capability))) + ))))) - (def: .public (async capability) - (All (_ brand input output) - (-> (Capability brand input (IO output)) - (Capability brand input (Async output)))) - (..capability (|>> ((:representation capability)) async.future))) + (def: .public (async capability) + (All (_ brand input output) + (-> (Capability brand input (IO output)) + (Capability brand input (Async output)))) + (..capability (|>> ((:representation capability)) async.future)))] ) diff --git a/stdlib/source/library/lux/control/security/policy.lux b/stdlib/source/library/lux/control/security/policy.lux index 498469d63..f0a55bdd4 100644 --- a/stdlib/source/library/lux/control/security/policy.lux +++ b/stdlib/source/library/lux/control/security/policy.lux @@ -9,89 +9,85 @@ abstract]]]) (abstract: .public (Policy brand value label) - {} - value - (type: .public (Can_Upgrade brand label value) - (-> value (Policy brand value label))) - - (type: .public (Can_Downgrade brand label value) - (-> (Policy brand value label) value)) - - (type: .public (Privilege brand label) - (Record - [#can_upgrade (Can_Upgrade brand label) - #can_downgrade (Can_Downgrade brand label)])) - - (type: .public (Delegation brand from to) - (All (_ value) - (-> (Policy brand value from) - (Policy brand value to)))) - - (def: .public (delegation downgrade upgrade) - (All (_ brand from to) - (-> (Can_Downgrade brand from) (Can_Upgrade brand to) - (Delegation brand from to))) - (|>> downgrade upgrade)) - - (type: .public (Context brand scope label) - (-> (Privilege brand label) - (scope label))) - - (def: privilege - Privilege - [#can_upgrade (|>> :abstraction) - #can_downgrade (|>> :representation)]) - - (def: .public (with_policy context) - (All (_ brand scope) - (Ex (_ label) - (-> (Context brand scope label) - (scope label)))) - (context ..privilege)) - - (def: (of_policy constructor) - (-> Type Type) - (type (All (_ brand label) - (constructor (All (_ value) (Policy brand value label)))))) - - (implementation: .public functor - (:~ (..of_policy Functor)) - - (def: (each f fa) - (|> fa :representation f :abstraction))) - - (implementation: .public apply - (:~ (..of_policy Apply)) - - (def: &functor ..functor) - - (def: (on fa ff) - (:abstraction ((:representation ff) (:representation fa))))) - - (implementation: .public monad - (:~ (..of_policy Monad)) - - (def: &functor ..functor) - (def: in (|>> :abstraction)) - (def: conjoint (|>> :representation))) + [(type: .public (Can_Upgrade brand label value) + (-> value (Policy brand value label))) + + (type: .public (Can_Downgrade brand label value) + (-> (Policy brand value label) value)) + + (type: .public (Privilege brand label) + (Record + [#can_upgrade (Can_Upgrade brand label) + #can_downgrade (Can_Downgrade brand label)])) + + (type: .public (Delegation brand from to) + (All (_ value) + (-> (Policy brand value from) + (Policy brand value to)))) + + (def: .public (delegation downgrade upgrade) + (All (_ brand from to) + (-> (Can_Downgrade brand from) (Can_Upgrade brand to) + (Delegation brand from to))) + (|>> downgrade upgrade)) + + (type: .public (Context brand scope label) + (-> (Privilege brand label) + (scope label))) + + (def: privilege + Privilege + [#can_upgrade (|>> :abstraction) + #can_downgrade (|>> :representation)]) + + (def: .public (with_policy context) + (All (_ brand scope) + (Ex (_ label) + (-> (Context brand scope label) + (scope label)))) + (context ..privilege)) + + (def: (of_policy constructor) + (-> Type Type) + (type (All (_ brand label) + (constructor (All (_ value) (Policy brand value label)))))) + + (implementation: .public functor + (:~ (..of_policy Functor)) + + (def: (each f fa) + (|> fa :representation f :abstraction))) + + (implementation: .public apply + (:~ (..of_policy Apply)) + + (def: &functor ..functor) + + (def: (on fa ff) + (:abstraction ((:representation ff) (:representation fa))))) + + (implementation: .public monad + (:~ (..of_policy Monad)) + + (def: &functor ..functor) + (def: in (|>> :abstraction)) + (def: conjoint (|>> :representation)))] ) (template [ ] [(abstract: .public - {} - Any - (type: .public - (Policy )) - - (type: .public - (Can_Upgrade )) - - (type: .public - (Can_Downgrade )) + [(type: .public + (Policy )) + + (type: .public + (Can_Upgrade )) + + (type: .public + (Can_Downgrade ))] )] [Privacy Private Can_Conceal Can_Reveal] diff --git a/stdlib/source/library/lux/control/thread.lux b/stdlib/source/library/lux/control/thread.lux index c583a4709..b2945a7a0 100644 --- a/stdlib/source/library/lux/control/thread.lux +++ b/stdlib/source/library/lux/control/thread.lux @@ -18,42 +18,40 @@ (-> ! a)) (abstract: .public (Box t v) - {} - (Array v) - (def: .public (box init) - (All (_ a) (-> a (All (_ !) (Thread ! (Box ! a))))) - (function (_ !) - (|> (array.empty 1) - (array.write! 0 init) - :abstraction))) - - (def: .public (read! box) - (All (_ ! a) (-> (Box ! a) (Thread ! a))) - (function (_ !) - (for {@.old - ("jvm aaload" (:representation box) 0) - - @.jvm - ("jvm array read object" - (|> 0 - (:as (primitive "java.lang.Long")) - "jvm object cast" - "jvm conversion long-to-int") - (:representation box)) - - @.js ("js array read" 0 (:representation box)) - @.python ("python array read" 0 (:representation box)) - @.lua ("lua array read" 0 (:representation box)) - @.ruby ("ruby array read" 0 (:representation box)) - @.php ("php array read" 0 (:representation box)) - @.scheme ("scheme array read" 0 (:representation box))}))) - - (def: .public (write! value box) - (All (_ a) (-> a (All (_ !) (-> (Box ! a) (Thread ! Any))))) - (function (_ !) - (|> box :representation (array.write! 0 value) :abstraction))) + [(def: .public (box init) + (All (_ a) (-> a (All (_ !) (Thread ! (Box ! a))))) + (function (_ !) + (|> (array.empty 1) + (array.write! 0 init) + :abstraction))) + + (def: .public (read! box) + (All (_ ! a) (-> (Box ! a) (Thread ! a))) + (function (_ !) + (for {@.old + ("jvm aaload" (:representation box) 0) + + @.jvm + ("jvm array read object" + (|> 0 + (:as (primitive "java.lang.Long")) + "jvm object cast" + "jvm conversion long-to-int") + (:representation box)) + + @.js ("js array read" 0 (:representation box)) + @.python ("python array read" 0 (:representation box)) + @.lua ("lua array read" 0 (:representation box)) + @.ruby ("ruby array read" 0 (:representation box)) + @.php ("php array read" 0 (:representation box)) + @.scheme ("scheme array read" 0 (:representation box))}))) + + (def: .public (write! value box) + (All (_ a) (-> a (All (_ !) (-> (Box ! a) (Thread ! Any))))) + (function (_ !) + (|> box :representation (array.write! 0 value) :abstraction)))] ) (def: .public (result thread) diff --git a/stdlib/source/library/lux/data/collection/queue/priority.lux b/stdlib/source/library/lux/data/collection/queue/priority.lux index f6fc98d98..28f1f135f 100644 --- a/stdlib/source/library/lux/data/collection/queue/priority.lux +++ b/stdlib/source/library/lux/data/collection/queue/priority.lux @@ -38,90 +38,88 @@ @)) (abstract: .public (Queue a) - {} - (Maybe (Tree :@: Priority a)) - (def: .public empty - Queue - (:abstraction #.None)) - - (def: .public (front queue) - (All (_ a) (-> (Queue a) (Maybe a))) - (do maybe.monad - [tree (:representation queue)] - (tree.one (n.= (tree.tag tree)) - tree))) - - (def: .public (size queue) - (All (_ a) (-> (Queue a) Nat)) - (case (:representation queue) - #.None - 0 - - (#.Some tree) - (loop [node tree] - (case (tree.root node) - (0 #0 _) - 1 - - (0 #1 [left right]) - (n.+ (recur left) (recur right)))))) - - (def: .public (member? equivalence queue member) - (All (_ a) (-> (Equivalence a) (Queue a) a Bit)) - (case (:representation queue) - #.None - false - - (#.Some tree) - (loop [node tree] - (case (tree.root node) - (0 #0 reference) - (\ equivalence = reference member) - - (0 #1 [left right]) - (or (recur left) - (recur right)))))) - - (def: .public (next queue) - (All (_ a) (-> (Queue a) (Queue a))) - (:abstraction + [(def: .public empty + Queue + (:abstraction #.None)) + + (def: .public (front queue) + (All (_ a) (-> (Queue a) (Maybe a))) (do maybe.monad - [tree (:representation queue) - .let [highest_priority (tree.tag tree)]] + [tree (:representation queue)] + (tree.one (n.= (tree.tag tree)) + tree))) + + (def: .public (size queue) + (All (_ a) (-> (Queue a) Nat)) + (case (:representation queue) + #.None + 0 + + (#.Some tree) + (loop [node tree] + (case (tree.root node) + (0 #0 _) + 1 + + (0 #1 [left right]) + (n.+ (recur left) (recur right)))))) + + (def: .public (member? equivalence queue member) + (All (_ a) (-> (Equivalence a) (Queue a) a Bit)) + (case (:representation queue) + #.None + false + + (#.Some tree) (loop [node tree] (case (tree.root node) (0 #0 reference) - (if (n.= highest_priority (tree.tag node)) - #.None - (#.Some node)) - - (0 #1 left right) - (if (n.= highest_priority (tree.tag left)) - (case (recur left) - #.None - (#.Some right) - - (#.Some =left) - (#.Some (\ ..builder branch =left right))) - (case (recur right) - #.None - (#.Some left) - - (#.Some =right) - (#.Some (\ ..builder branch left =right))))))))) - - (def: .public (end priority value queue) - (All (_ a) (-> Priority a (Queue a) (Queue a))) - (let [addition (\ ..builder leaf priority value)] - (:abstraction - (case (:representation queue) - #.None - (#.Some addition) - - (#.Some tree) - (#.Some (\ ..builder branch tree addition)))))) + (\ equivalence = reference member) + + (0 #1 [left right]) + (or (recur left) + (recur right)))))) + + (def: .public (next queue) + (All (_ a) (-> (Queue a) (Queue a))) + (:abstraction + (do maybe.monad + [tree (:representation queue) + .let [highest_priority (tree.tag tree)]] + (loop [node tree] + (case (tree.root node) + (0 #0 reference) + (if (n.= highest_priority (tree.tag node)) + #.None + (#.Some node)) + + (0 #1 left right) + (if (n.= highest_priority (tree.tag left)) + (case (recur left) + #.None + (#.Some right) + + (#.Some =left) + (#.Some (\ ..builder branch =left right))) + (case (recur right) + #.None + (#.Some left) + + (#.Some =right) + (#.Some (\ ..builder branch left =right))))))))) + + (def: .public (end priority value queue) + (All (_ a) (-> Priority a (Queue a) (Queue a))) + (let [addition (\ ..builder leaf priority value)] + (:abstraction + (case (:representation queue) + #.None + (#.Some addition) + + (#.Some tree) + (#.Some (\ ..builder branch tree addition))))))] ) (def: .public empty? diff --git a/stdlib/source/library/lux/data/collection/set/multi.lux b/stdlib/source/library/lux/data/collection/set/multi.lux index f3df37d57..cd36648eb 100644 --- a/stdlib/source/library/lux/data/collection/set/multi.lux +++ b/stdlib/source/library/lux/data/collection/set/multi.lux @@ -19,122 +19,120 @@ ["[0]" dictionary {"+" [Dictionary]}]]]) (abstract: .public (Set a) - {} - (Dictionary a Nat) - (def: .public empty - (All (_ a) (-> (Hash a) (Set a))) - (|>> dictionary.empty :abstraction)) - - (def: .public size - (All (_ a) (-> (Set a) Nat)) - (|>> :representation dictionary.values (list\mix n.+ 0))) - - (def: .public (has multiplicity elem set) - (All (_ a) (-> Nat a (Set a) (Set a))) - (case multiplicity - 0 set - _ (|> set - :representation - (dictionary.revised' elem 0 (n.+ multiplicity)) - :abstraction))) - - (def: .public (lacks multiplicity elem set) - (All (_ a) (-> Nat a (Set a) (Set a))) - (case multiplicity - 0 set - _ (case (dictionary.value elem (:representation set)) - (#.Some current) - (:abstraction - (if (n.> multiplicity current) - (dictionary.revised elem (n.- multiplicity) (:representation set)) - (dictionary.lacks elem (:representation set)))) - - #.None - set))) - - (def: .public (multiplicity set elem) - (All (_ a) (-> (Set a) a Nat)) - (|> set :representation (dictionary.value elem) (maybe.else 0))) - - (def: .public list - (All (_ a) (-> (Set a) (List a))) - (|>> :representation + [(def: .public empty + (All (_ a) (-> (Hash a) (Set a))) + (|>> dictionary.empty :abstraction)) + + (def: .public size + (All (_ a) (-> (Set a) Nat)) + (|>> :representation dictionary.values (list\mix n.+ 0))) + + (def: .public (has multiplicity elem set) + (All (_ a) (-> Nat a (Set a) (Set a))) + (case multiplicity + 0 set + _ (|> set + :representation + (dictionary.revised' elem 0 (n.+ multiplicity)) + :abstraction))) + + (def: .public (lacks multiplicity elem set) + (All (_ a) (-> Nat a (Set a) (Set a))) + (case multiplicity + 0 set + _ (case (dictionary.value elem (:representation set)) + (#.Some current) + (:abstraction + (if (n.> multiplicity current) + (dictionary.revised elem (n.- multiplicity) (:representation set)) + (dictionary.lacks elem (:representation set)))) + + #.None + set))) + + (def: .public (multiplicity set elem) + (All (_ a) (-> (Set a) a Nat)) + (|> set :representation (dictionary.value elem) (maybe.else 0))) + + (def: .public list + (All (_ a) (-> (Set a) (List a))) + (|>> :representation + dictionary.entries + (list\mix (function (_ [elem multiplicity] output) + (list\composite (list.repeated multiplicity elem) output)) + #.End))) + + (template [ ] + [(def: .public ( parameter subject) + (All (_ a) (-> (Set a) (Set a) (Set a))) + (:abstraction (dictionary.merged_with (:representation parameter) (:representation subject))))] + + [union n.max] + [sum n.+] + ) + + (def: .public (intersection parameter (^:representation subject)) + (All (_ a) (-> (Set a) (Set a) (Set a))) + (list\mix (function (_ [elem multiplicity] output) + (..has (n.min (..multiplicity parameter elem) + multiplicity) + elem + output)) + (..empty (dictionary.key_hash subject)) + (dictionary.entries subject))) + + (def: .public (difference parameter subject) + (All (_ a) (-> (Set a) (Set a) (Set a))) + (|> parameter + :representation dictionary.entries (list\mix (function (_ [elem multiplicity] output) - (list\composite (list.repeated multiplicity elem) output)) - #.End))) - - (template [ ] - [(def: .public ( parameter subject) - (All (_ a) (-> (Set a) (Set a) (Set a))) - (:abstraction (dictionary.merged_with (:representation parameter) (:representation subject))))] - - [union n.max] - [sum n.+] - ) - - (def: .public (intersection parameter (^:representation subject)) - (All (_ a) (-> (Set a) (Set a) (Set a))) - (list\mix (function (_ [elem multiplicity] output) - (..has (n.min (..multiplicity parameter elem) - multiplicity) - elem - output)) - (..empty (dictionary.key_hash subject)) - (dictionary.entries subject))) - - (def: .public (difference parameter subject) - (All (_ a) (-> (Set a) (Set a) (Set a))) - (|> parameter - :representation - dictionary.entries - (list\mix (function (_ [elem multiplicity] output) - (..lacks multiplicity elem output)) - subject))) - - (def: .public (sub? reference subject) - (All (_ a) (-> (Set a) (Set a) Bit)) - (|> subject - :representation - dictionary.entries - (list.every? (function (_ [elem multiplicity]) - (|> elem - (..multiplicity reference) - (n.>= multiplicity)))))) - - (def: .public (support set) - (All (_ a) (-> (Set a) (//.Set a))) - (let [(^@ set [hash _]) (:representation set)] - (|> set - dictionary.keys - (//.of_list hash)))) - - (implementation: .public equivalence - (All (_ a) (Equivalence (Set a))) - - (def: (= (^:representation reference) sample) - (and (n.= (dictionary.size reference) - (dictionary.size (:representation sample))) - (|> reference - dictionary.entries - (list.every? (function (_ [elem multiplicity]) - (|> elem - (..multiplicity sample) - (n.= multiplicity)))))))) - - (implementation: .public hash - (All (_ a) (Hash (Set a))) - - (def: &equivalence ..equivalence) - - (def: (hash (^:representation set)) - (let [[hash _] set] - (list\mix (function (_ [elem multiplicity] acc) - (|> elem (\ hash hash) (n.* multiplicity) (n.+ acc))) - 0 - (dictionary.entries set))))) + (..lacks multiplicity elem output)) + subject))) + + (def: .public (sub? reference subject) + (All (_ a) (-> (Set a) (Set a) Bit)) + (|> subject + :representation + dictionary.entries + (list.every? (function (_ [elem multiplicity]) + (|> elem + (..multiplicity reference) + (n.>= multiplicity)))))) + + (def: .public (support set) + (All (_ a) (-> (Set a) (//.Set a))) + (let [(^@ set [hash _]) (:representation set)] + (|> set + dictionary.keys + (//.of_list hash)))) + + (implementation: .public equivalence + (All (_ a) (Equivalence (Set a))) + + (def: (= (^:representation reference) sample) + (and (n.= (dictionary.size reference) + (dictionary.size (:representation sample))) + (|> reference + dictionary.entries + (list.every? (function (_ [elem multiplicity]) + (|> elem + (..multiplicity sample) + (n.= multiplicity)))))))) + + (implementation: .public hash + (All (_ a) (Hash (Set a))) + + (def: &equivalence ..equivalence) + + (def: (hash (^:representation set)) + (let [[hash _] set] + (list\mix (function (_ [elem multiplicity] acc) + (|> elem (\ hash hash) (n.* multiplicity) (n.+ acc))) + 0 + (dictionary.entries set)))))] ) (def: .public (member? set elem) diff --git a/stdlib/source/library/lux/data/collection/set/ordered.lux b/stdlib/source/library/lux/data/collection/set/ordered.lux index 91edd4642..a3bd77830 100644 --- a/stdlib/source/library/lux/data/collection/set/ordered.lux +++ b/stdlib/source/library/lux/data/collection/set/ordered.lux @@ -13,67 +13,65 @@ abstract]]]) (abstract: .public (Set a) - {} - (/.Dictionary a a) - (def: .public empty - (All (_ a) (-> (Order a) (Set a))) - (|>> /.empty :abstraction)) - - (def: .public (member? set elem) - (All (_ a) (-> (Set a) a Bit)) - (/.key? (:representation set) elem)) - - (template [ ] - [(def: .public - (All (_ a) (-> (Set a) )) - (|>> :representation ))] - - [(Maybe a) min /.min] - [(Maybe a) max /.max] - [Nat size /.size] - [Bit empty? /.empty?] - ) - - (def: .public (has elem set) - (All (_ a) (-> a (Set a) (Set a))) - (|> set :representation (/.has elem elem) :abstraction)) - - (def: .public (lacks elem set) - (All (_ a) (-> a (Set a) (Set a))) - (|> set :representation (/.lacks elem) :abstraction)) - - (def: .public list - (All (_ a) (-> (Set a) (List a))) - (|>> :representation /.keys)) - - (def: .public (of_list &order list) - (All (_ a) (-> (Order a) (List a) (Set a))) - (list\mix has (..empty &order) list)) - - (def: .public (union left right) - (All (_ a) (-> (Set a) (Set a) (Set a))) - (list\mix ..has right (..list left))) - - (def: .public (intersection left right) - (All (_ a) (-> (Set a) (Set a) (Set a))) - (|> (..list right) - (list.only (..member? left)) - (..of_list (value@ #/.&order (:representation right))))) - - (def: .public (difference param subject) - (All (_ a) (-> (Set a) (Set a) (Set a))) - (|> (..list subject) - (list.only (|>> (..member? param) not)) - (..of_list (value@ #/.&order (:representation subject))))) - - (implementation: .public equivalence - (All (_ a) (Equivalence (Set a))) - - (def: (= reference sample) - (\ (list.equivalence (\ (:representation reference) &equivalence)) - = (..list reference) (..list sample)))) + [(def: .public empty + (All (_ a) (-> (Order a) (Set a))) + (|>> /.empty :abstraction)) + + (def: .public (member? set elem) + (All (_ a) (-> (Set a) a Bit)) + (/.key? (:representation set) elem)) + + (template [ ] + [(def: .public + (All (_ a) (-> (Set a) )) + (|>> :representation ))] + + [(Maybe a) min /.min] + [(Maybe a) max /.max] + [Nat size /.size] + [Bit empty? /.empty?] + ) + + (def: .public (has elem set) + (All (_ a) (-> a (Set a) (Set a))) + (|> set :representation (/.has elem elem) :abstraction)) + + (def: .public (lacks elem set) + (All (_ a) (-> a (Set a) (Set a))) + (|> set :representation (/.lacks elem) :abstraction)) + + (def: .public list + (All (_ a) (-> (Set a) (List a))) + (|>> :representation /.keys)) + + (def: .public (of_list &order list) + (All (_ a) (-> (Order a) (List a) (Set a))) + (list\mix has (..empty &order) list)) + + (def: .public (union left right) + (All (_ a) (-> (Set a) (Set a) (Set a))) + (list\mix ..has right (..list left))) + + (def: .public (intersection left right) + (All (_ a) (-> (Set a) (Set a) (Set a))) + (|> (..list right) + (list.only (..member? left)) + (..of_list (value@ #/.&order (:representation right))))) + + (def: .public (difference param subject) + (All (_ a) (-> (Set a) (Set a) (Set a))) + (|> (..list subject) + (list.only (|>> (..member? param) not)) + (..of_list (value@ #/.&order (:representation subject))))) + + (implementation: .public equivalence + (All (_ a) (Equivalence (Set a))) + + (def: (= reference sample) + (\ (list.equivalence (\ (:representation reference) &equivalence)) + = (..list reference) (..list sample))))] ) (def: .public (sub? super sub) diff --git a/stdlib/source/library/lux/data/collection/stack.lux b/stdlib/source/library/lux/data/collection/stack.lux index f8ed6aab6..feb2d2805 100644 --- a/stdlib/source/library/lux/data/collection/stack.lux +++ b/stdlib/source/library/lux/data/collection/stack.lux @@ -11,58 +11,56 @@ abstract]]]) (abstract: .public (Stack a) - {} - (List a) - (def: .public empty - Stack - (:abstraction (list))) + [(def: .public empty + Stack + (:abstraction (list))) - (def: .public size - (All (_ a) (-> (Stack a) Nat)) - (|>> :representation //.size)) + (def: .public size + (All (_ a) (-> (Stack a) Nat)) + (|>> :representation //.size)) - (def: .public empty? - (All (_ a) (-> (Stack a) Bit)) - (|>> :representation //.empty?)) + (def: .public empty? + (All (_ a) (-> (Stack a) Bit)) + (|>> :representation //.empty?)) - (def: .public (value stack) - (All (_ a) (-> (Stack a) (Maybe a))) - (case (:representation stack) - #.End - #.None - - (#.Item value _) - (#.Some value))) + (def: .public (value stack) + (All (_ a) (-> (Stack a) (Maybe a))) + (case (:representation stack) + #.End + #.None + + (#.Item value _) + (#.Some value))) - (def: .public (next stack) - (All (_ a) (-> (Stack a) (Maybe [a (Stack a)]))) - (case (:representation stack) - #.End - #.None - - (#.Item top stack') - (#.Some [top (:abstraction stack')]))) + (def: .public (next stack) + (All (_ a) (-> (Stack a) (Maybe [a (Stack a)]))) + (case (:representation stack) + #.End + #.None + + (#.Item top stack') + (#.Some [top (:abstraction stack')]))) - (def: .public (top value stack) - (All (_ a) (-> a (Stack a) (Stack a))) - (:abstraction (#.Item value (:representation stack)))) + (def: .public (top value stack) + (All (_ a) (-> a (Stack a) (Stack a))) + (:abstraction (#.Item value (:representation stack)))) - (implementation: .public (equivalence super) - (All (_ a) - (-> (Equivalence a) - (Equivalence (Stack a)))) + (implementation: .public (equivalence super) + (All (_ a) + (-> (Equivalence a) + (Equivalence (Stack a)))) - (def: (= reference subject) - (\ (//.equivalence super) = (:representation reference) (:representation subject)))) + (def: (= reference subject) + (\ (//.equivalence super) = (:representation reference) (:representation subject)))) - (implementation: .public functor - (Functor Stack) - - (def: (each f value) - (|> value - :representation - (\ //.functor each f) - :abstraction))) + (implementation: .public functor + (Functor Stack) + + (def: (each f value) + (|> value + :representation + (\ //.functor each f) + :abstraction)))] ) diff --git a/stdlib/source/library/lux/data/collection/tree/finger.lux b/stdlib/source/library/lux/data/collection/tree/finger.lux index 998ccde41..b4e042069 100644 --- a/stdlib/source/library/lux/data/collection/tree/finger.lux +++ b/stdlib/source/library/lux/data/collection/tree/finger.lux @@ -12,95 +12,93 @@ ... https://en.wikipedia.org/wiki/Finger_tree (abstract: .public (Tree @ t v) - {} - (Record [#monoid (Monoid t) #tag t #root (Or v [(Tree @ t v) (Tree @ t v)])]) - (type: .public (Builder @ t) - (Interface - (: (All (_ v) - (-> t v (Tree @ t v))) - leaf) - (: (All (_ v) - (-> (Tree @ t v) - (Tree @ t v) - (Tree @ t v))) - branch))) - - (template [ ] - [(def: .public - (All (_ @ t v) (-> (Tree @ t v) )) - (|>> :representation (value@ )))] - - [tag #tag t] - [root #root (Either v [(Tree @ t v) (Tree @ t v)])] - ) - - (implementation: .public (builder monoid) - (All (_ t) (Ex (_ @) (-> (Monoid t) (Builder @ t)))) - - (def: (leaf tag value) - (:abstraction - [#monoid monoid - #tag tag - #root (0 #0 value)])) - - (def: (branch left right) - (:abstraction - [#monoid monoid - #tag (\ monoid composite (..tag left) (..tag right)) - #root (0 #1 [left right])]))) - - (def: .public (value tree) - (All (_ @ t v) (-> (Tree @ t v) v)) - (case (value@ #root (:representation tree)) - (0 #0 value) - value - - (0 #1 [left right]) - (value left))) - - (def: .public (tags tree) - (All (_ @ t v) (-> (Tree @ t v) (List t))) - (case (value@ #root (:representation tree)) - (0 #0 value) - (list (value@ #tag (:representation tree))) - - (0 #1 [left right]) - (list\composite (tags left) - (tags right)))) - - (def: .public (values tree) - (All (_ @ t v) (-> (Tree @ t v) (List v))) - (case (value@ #root (:representation tree)) - (0 #0 value) - (list value) - - (0 #1 [left right]) - (list\composite (values left) - (values right)))) - - (def: .public (one predicate tree) - (All (_ @ t v) (-> (Predicate t) (Tree @ t v) (Maybe v))) - (let [[monoid tag root] (:representation tree)] - (if (predicate tag) - (let [(^open "tag//[0]") monoid] - (loop [_tag tag//identity - _node root] - (case _node - (0 #0 value) - (#.Some value) - - (0 #1 [left right]) - (let [shifted_tag (tag//composite _tag (..tag left))] - (if (predicate shifted_tag) - (recur _tag (value@ #root (:representation left))) - (recur shifted_tag (value@ #root (:representation right)))))))) - #.None))) + [(type: .public (Builder @ t) + (Interface + (: (All (_ v) + (-> t v (Tree @ t v))) + leaf) + (: (All (_ v) + (-> (Tree @ t v) + (Tree @ t v) + (Tree @ t v))) + branch))) + + (template [ ] + [(def: .public + (All (_ @ t v) (-> (Tree @ t v) )) + (|>> :representation (value@ )))] + + [tag #tag t] + [root #root (Either v [(Tree @ t v) (Tree @ t v)])] + ) + + (implementation: .public (builder monoid) + (All (_ t) (Ex (_ @) (-> (Monoid t) (Builder @ t)))) + + (def: (leaf tag value) + (:abstraction + [#monoid monoid + #tag tag + #root (0 #0 value)])) + + (def: (branch left right) + (:abstraction + [#monoid monoid + #tag (\ monoid composite (..tag left) (..tag right)) + #root (0 #1 [left right])]))) + + (def: .public (value tree) + (All (_ @ t v) (-> (Tree @ t v) v)) + (case (value@ #root (:representation tree)) + (0 #0 value) + value + + (0 #1 [left right]) + (value left))) + + (def: .public (tags tree) + (All (_ @ t v) (-> (Tree @ t v) (List t))) + (case (value@ #root (:representation tree)) + (0 #0 value) + (list (value@ #tag (:representation tree))) + + (0 #1 [left right]) + (list\composite (tags left) + (tags right)))) + + (def: .public (values tree) + (All (_ @ t v) (-> (Tree @ t v) (List v))) + (case (value@ #root (:representation tree)) + (0 #0 value) + (list value) + + (0 #1 [left right]) + (list\composite (values left) + (values right)))) + + (def: .public (one predicate tree) + (All (_ @ t v) (-> (Predicate t) (Tree @ t v) (Maybe v))) + (let [[monoid tag root] (:representation tree)] + (if (predicate tag) + (let [(^open "tag//[0]") monoid] + (loop [_tag tag//identity + _node root] + (case _node + (0 #0 value) + (#.Some value) + + (0 #1 [left right]) + (let [shifted_tag (tag//composite _tag (..tag left))] + (if (predicate shifted_tag) + (recur _tag (value@ #root (:representation left))) + (recur shifted_tag (value@ #root (:representation right)))))))) + #.None)))] ) (def: .public (exists? predicate tree) diff --git a/stdlib/source/library/lux/data/color.lux b/stdlib/source/library/lux/data/color.lux index 82a44b4cb..f396b712a 100644 --- a/stdlib/source/library/lux/data/color.lux +++ b/stdlib/source/library/lux/data/color.lux @@ -55,88 +55,86 @@ [Frac Frac Frac]) (abstract: .public Color - {} - RGB - (def: .public (of_rgb [red green blue]) - (-> RGB Color) - (:abstraction [#red (n.% ..rgb_limit red) - #green (n.% ..rgb_limit green) - #blue (n.% ..rgb_limit blue)])) - - (def: .public rgb - (-> Color RGB) - (|>> :representation)) - - (implementation: .public equivalence - (Equivalence Color) - - (def: (= reference sample) - (let [[rR gR bR] (:representation reference) - [rS gS bS] (:representation sample)] - (and (n.= rR rS) - (n.= gR gS) - (n.= bR bS))))) - - (implementation: .public hash - (Hash Color) - - (def: &equivalence ..equivalence) - - (def: (hash value) - (let [[r g b] (:representation value)] - ($_ i64.or - (i64.left_shifted 16 r) - (i64.left_shifted 8 g) - b)))) - - (def: .public black - Color - (..of_rgb [#red 0 - #green 0 - #blue 0])) - - (def: .public white - Color - (..of_rgb [#red ..top - #green ..top - #blue ..top])) - - (implementation: .public addition - (Monoid Color) - - (def: identity ..black) - - (def: (composite left right) - (let [[lR lG lB] (:representation left) - [rR rG rB] (:representation right)] - (:abstraction [#red (n.max lR rR) - #green (n.max lG rG) - #blue (n.max lB rB)])))) - - (def: (opposite_intensity value) - (-> Nat Nat) - (|> ..top (n.- value))) - - (def: .public (complement color) - (-> Color Color) - (let [[red green blue] (:representation color)] - (:abstraction [#red (opposite_intensity red) - #green (opposite_intensity green) - #blue (opposite_intensity blue)]))) - - (implementation: .public subtraction - (Monoid Color) - - (def: identity ..white) - - (def: (composite left right) - (let [[lR lG lB] (:representation (..complement left)) - [rR rG rB] (:representation right)] - (:abstraction [#red (n.min lR rR) - #green (n.min lG rG) - #blue (n.min lB rB)])))) + [(def: .public (of_rgb [red green blue]) + (-> RGB Color) + (:abstraction [#red (n.% ..rgb_limit red) + #green (n.% ..rgb_limit green) + #blue (n.% ..rgb_limit blue)])) + + (def: .public rgb + (-> Color RGB) + (|>> :representation)) + + (implementation: .public equivalence + (Equivalence Color) + + (def: (= reference sample) + (let [[rR gR bR] (:representation reference) + [rS gS bS] (:representation sample)] + (and (n.= rR rS) + (n.= gR gS) + (n.= bR bS))))) + + (implementation: .public hash + (Hash Color) + + (def: &equivalence ..equivalence) + + (def: (hash value) + (let [[r g b] (:representation value)] + ($_ i64.or + (i64.left_shifted 16 r) + (i64.left_shifted 8 g) + b)))) + + (def: .public black + Color + (..of_rgb [#red 0 + #green 0 + #blue 0])) + + (def: .public white + Color + (..of_rgb [#red ..top + #green ..top + #blue ..top])) + + (implementation: .public addition + (Monoid Color) + + (def: identity ..black) + + (def: (composite left right) + (let [[lR lG lB] (:representation left) + [rR rG rB] (:representation right)] + (:abstraction [#red (n.max lR rR) + #green (n.max lG rG) + #blue (n.max lB rB)])))) + + (def: (opposite_intensity value) + (-> Nat Nat) + (|> ..top (n.- value))) + + (def: .public (complement color) + (-> Color Color) + (let [[red green blue] (:representation color)] + (:abstraction [#red (opposite_intensity red) + #green (opposite_intensity green) + #blue (opposite_intensity blue)]))) + + (implementation: .public subtraction + (Monoid Color) + + (def: identity ..white) + + (def: (composite left right) + (let [[lR lG lB] (:representation (..complement left)) + [rR rG rB] (:representation right)] + (:abstraction [#red (n.min lR rR) + #green (n.min lG rG) + #blue (n.min lB rB)]))))] ) (def: .public (hsl color) diff --git a/stdlib/source/library/lux/data/format/css.lux b/stdlib/source/library/lux/data/format/css.lux index 8f0cc2f06..a0d849ccf 100644 --- a/stdlib/source/library/lux/data/format/css.lux +++ b/stdlib/source/library/lux/data/format/css.lux @@ -22,114 +22,112 @@ ["[1][0]" style {"+" [Style]}] ["[1][0]" query {"+" [Query]}]]) -(abstract: .public Common {} Any) -(abstract: .public Special {} Any) +(abstract: .public Common Any []) +(abstract: .public Special Any []) (abstract: .public (CSS brand) - {} - Text - (def: .public css - (-> (CSS Any) Text) - (|>> :representation)) - - (def: .public empty - (CSS Common) - (:abstraction "")) + [(def: .public css + (-> (CSS Any) Text) + (|>> :representation)) + + (def: .public empty + (CSS Common) + (:abstraction "")) + + (def: .public (rule selector style) + (-> (Selector Any) Style (CSS Common)) + (:abstraction (format (/selector.selector selector) "{" (/style.inline style) "}"))) + + (def: .public char_set + (-> Encoding (CSS Special)) + (|>> encoding.name + %.text + (text.enclosed ["@charset " ";"]) + :abstraction)) + + (def: .public (font font) + (-> Font (CSS Special)) + (let [with_unicode (case (value@ #/font.unicode_range font) + (#.Some unicode_range) + (let [unicode_range' (format "U+" (\ nat.hex encoded (value@ #/font.start unicode_range)) + "-" (\ nat.hex encoded (value@ #/font.end unicode_range)))] + (list ["unicode-range" unicode_range'])) + + #.None + (list))] + (|> (list& ["font-family" (value@ #/font.family font)] + ["src" (format "url(" (value@ #/font.source font) ")")] + ["font-stretch" (|> font (value@ #/font.stretch) (maybe.else /value.normal_stretch) /value.value)] + ["font-style" (|> font (value@ #/font.style) (maybe.else /value.normal_style) /value.value)] + ["font-weight" (|> font (value@ #/font.weight) (maybe.else /value.normal_weight) /value.value)] + with_unicode) + (list\each (function (_ [property value]) + (format property ": " value ";"))) + (text.interposed /style.separator) + (text.enclosed ["{" "}"]) + (format "@font-face") + :abstraction))) + + (def: .public (import url query) + (-> URL (Maybe Query) (CSS Special)) + (:abstraction (format (format "@import url(" (%.text url) ")") + (case query + (#.Some query) + (format " " (/query.query query)) + + #.None + "") + ";"))) + + (def: css_separator + text.new_line) + + (type: .public Frame + (Record + [#when Percentage + #what Style])) + + (def: .public (key_frames animation frames) + (-> (Value Animation) (List Frame) (CSS Special)) + (:abstraction (format "@keyframes " (/value.value animation) " {" + (|> frames + (list\each (function (_ frame) + (format (/value.percentage (value@ #when frame)) " {" + (/style.inline (value@ #what frame)) + "}"))) + (text.interposed ..css_separator)) + "}"))) + + (template: (!composite
 )
+     (:abstraction (format (:representation 
) ..css_separator
+                           (:representation ))))
+   
+   (def: .public (and pre post)
+     (-> (CSS Any) (CSS Any) (CSS Any))
+     (!composite pre post))
+
+   (def: .public (alter combinator selector css)
+     (-> Combinator (Selector Any) (CSS Common) (CSS Common))
+     (|> css
+         :representation
+         (text.all_split_by ..css_separator)
+         (list\each (|>> (format (/selector.selector (|> selector (combinator (/selector.tag "")))))))
+         (text.interposed ..css_separator)
+         :abstraction))
 
-  (def: .public (rule selector style)
-    (-> (Selector Any) Style (CSS Common))
-    (:abstraction (format (/selector.selector selector) "{" (/style.inline style) "}")))
+   (def: .public (dependent combinator selector style inner)
+     (-> Combinator (Selector Any) Style (CSS Common) (CSS Common))
+     (!composite (..rule selector style)
+                 (..alter combinator selector inner)))
 
-  (def: .public char_set
-    (-> Encoding (CSS Special))
-    (|>> encoding.name
-         %.text
-         (text.enclosed ["@charset " ";"])
-         :abstraction))
+   (template [ ]
+     [(def: .public 
+        (-> (Selector Any) Style (CSS Common) (CSS Common))
+        (..dependent ))]
 
-  (def: .public (font font)
-    (-> Font (CSS Special))
-    (let [with_unicode (case (value@ #/font.unicode_range font)
-                         (#.Some unicode_range)
-                         (let [unicode_range' (format "U+" (\ nat.hex encoded (value@ #/font.start unicode_range))
-                                                      "-" (\ nat.hex encoded (value@ #/font.end unicode_range)))]
-                           (list ["unicode-range" unicode_range']))
-                         
-                         #.None
-                         (list))]
-      (|> (list& ["font-family" (value@ #/font.family font)]
-                 ["src" (format "url(" (value@ #/font.source font) ")")]
-                 ["font-stretch" (|> font (value@ #/font.stretch) (maybe.else /value.normal_stretch) /value.value)]
-                 ["font-style" (|> font (value@ #/font.style) (maybe.else /value.normal_style) /value.value)]
-                 ["font-weight" (|> font (value@ #/font.weight) (maybe.else /value.normal_weight) /value.value)]
-                 with_unicode)
-          (list\each (function (_ [property value])
-                       (format property ": " value ";")))
-          (text.interposed /style.separator)
-          (text.enclosed ["{" "}"])
-          (format "@font-face")
-          :abstraction)))
-
-  (def: .public (import url query)
-    (-> URL (Maybe Query) (CSS Special))
-    (:abstraction (format (format "@import url(" (%.text url) ")")
-                          (case query
-                            (#.Some query)
-                            (format " " (/query.query query))
-                            
-                            #.None
-                            "")
-                          ";")))
-
-  (def: css_separator
-    text.new_line)
-
-  (type: .public Frame
-    (Record
-     [#when Percentage
-      #what Style]))
-
-  (def: .public (key_frames animation frames)
-    (-> (Value Animation) (List Frame) (CSS Special))
-    (:abstraction (format "@keyframes " (/value.value animation) " {"
-                          (|> frames
-                              (list\each (function (_ frame)
-                                           (format (/value.percentage (value@ #when frame)) " {"
-                                                   (/style.inline (value@ #what frame))
-                                                   "}")))
-                              (text.interposed ..css_separator))
-                          "}")))
-
-  (template: (!composite 
 )
-    (:abstraction (format (:representation 
) ..css_separator
-                          (:representation ))))
-  
-  (def: .public (and pre post)
-    (-> (CSS Any) (CSS Any) (CSS Any))
-    (!composite pre post))
-
-  (def: .public (alter combinator selector css)
-    (-> Combinator (Selector Any) (CSS Common) (CSS Common))
-    (|> css
-        :representation
-        (text.all_split_by ..css_separator)
-        (list\each (|>> (format (/selector.selector (|> selector (combinator (/selector.tag "")))))))
-        (text.interposed ..css_separator)
-        :abstraction))
-
-  (def: .public (dependent combinator selector style inner)
-    (-> Combinator (Selector Any) Style (CSS Common) (CSS Common))
-    (!composite (..rule selector style)
-                (..alter combinator selector inner)))
-
-  (template [ ]
-    [(def: .public 
-       (-> (Selector Any) Style (CSS Common) (CSS Common))
-       (..dependent ))]
-
-    [with_descendants /selector.in]
-    [with_children /selector.sub]
-    )
+     [with_descendants /selector.in]
+     [with_children /selector.sub]
+     )]
   )
diff --git a/stdlib/source/library/lux/data/format/css/property.lux b/stdlib/source/library/lux/data/format/css/property.lux
index 19b11209c..27c5a880c 100644
--- a/stdlib/source/library/lux/data/format/css/property.lux
+++ b/stdlib/source/library/lux/data/format/css/property.lux
@@ -56,450 +56,448 @@
   (in (list (code.local_identifier (text.replaced "-" "_" identifier)))))
 
 (abstract: .public (Property brand)
-  {}
-  
   Text
 
-  (def: .public name
-    (-> (Property Any) Text)
-    (|>> :representation))
-
-  (template [ + +]
-    [(`` (template [ ]
-           [(def: .public 
-              (Property )
-              (:abstraction ))]
-
-           (~~ (template.spliced +))))
-
-     (with_expansions [ (template.spliced +)]
-       (template []
-         [(`` (def: .public (~~ (text_identifier ))
-                (Property )
-                (:abstraction )))]
-         
-         ))]
-
-    [All
-     []
-     [["all"]]]
-
-    [Length
-     []
-     [["border-image-outset"]
-      ["border-image-width"]
-      ["bottom"]
-      ["column-gap"]
-      ["column-width"]
-      ["flex-basis"]
-      ["grid-column-gap"]
-      ["grid-gap"]
-      ["grid-row-gap"]
-      ["height"]
-      ["left"]
-      ["letter-spacing"]
-      ["line-height"]
-      ["margin"]
-      ["margin-bottom"]
-      ["margin-left"]
-      ["margin-right"]
-      ["margin-top"]
-      ["max-height"]
-      ["max-width"]
-      ["min-height"]
-      ["min-width"]
-      ["outline-offset"]
-      ["padding"]
-      ["padding-bottom"]
-      ["padding-left"]
-      ["padding-right"]
-      ["padding-top"]
-      ["perspective"]
-      ["right"]
-      ["text-indent"]
-      ["top"]
-      ["width"]
-      ["word-spacing"]]]
-
-    [Time
-     []
-     [["animation-delay"]
-      ["animation-duration"]
-      ["transition-delay"]
-      ["transition-duration"]]]
-
-    [Slice
-     []
-     [["border-image-slice"]]]
-
-    [Color
-     [[text_color "color"]]
-     [["background-color"]
-      ["border-color"]
-      ["border-bottom-color"]
-      ["border-left-color"]
-      ["border-right-color"]
-      ["border-top-color"]
-      ["caret-color"]
-      ["column-rule-color"]
-      ["outline-color"]
-      ["text-decoration-color"]]]
-
-    [Alignment
-     []
-     [["align-content"]
-      ["align-items"]
-      ["align-self"]
-      ["justify-content"]]]
-
-    [Animation
-     []
-     [["animation-name"]]]
-
-    [Animation_Direction
-     []
-     [["animation-direction"]]]
-
-    [Animation_Fill
-     []
-     [["animation-fill-mode"]]]
-
-    [Column_Fill
-     []
-     [["column-fill"]]]
-
-    [Column_Span
-     []
-     [["column-span"]]]
-
-    [Iteration
-     []
-     [["animation-iteration-count"]]]
-
-    [Count
-     []
-     [["column-count"]
-      ["flex-grow"]
-      ["flex-shrink"]
-      ["order"]
-      ["tab-size"]]]
-
-    [Play
-     []
-     [["animation-play-state"]]]
-
-    [Timing
-     []
-     [["animation-timing-function"]
-      ["transition-timing-function"]]]
-
-    [Visibility
-     []
-     [["backface-visibility"]
-      ["visibility"]]]
-
-    [Attachment
-     []
-     [["background-attachment"]]]
-
-    [Blend
-     []
-     [["background-blend-mode"]
-      ["mix-blend-mode"]]]
-
-    [Image
-     []
-     [["background-image"]
-      ["border-image-source"]
-      ["list-style-image"]]]
-
-    [Span
-     []
-     [["background-clip"]
-      ["background-origin"]
-      ["box-sizing"]]]
-
-    [Location
-     []
-     [["background-position"]
-      ["object-position"]
-      ["perspective-origin"]]]
-
-    [Repeat
-     []
-     [["background-repeat"]
-      ["border-image-repeat"]]]
-
-    [Fit
-     []
-     [["background-size"]
-      ["border-radius"]
-      ["border-bottom-left-radius"]
-      ["border-bottom-right-radius"]
-      ["border-top-left-radius"]
-      ["border-top-right-radius"]
-      ["border-spacing"]
-      ["object-fit"]]]
-
-    [Border
-     []
-     [["border-style"]
-      ["border-bottom-style"]
-      ["border-left-style"]
-      ["border-right-style"]
-      ["border-top-style"]
-      ["column-rule-style"]
-      ["outline-style"]]]
-
-    [Thickness
-     []
-     [["border-width"]
-      ["border-bottom-width"]
-      ["border-left-width"]
-      ["border-right-width"]
-      ["border-top-width"]
-      ["column-rule-width"]
-      ["outline-width"]]]
-
-    [Collapse
-     []
-     [["border-collapse"]]]
-
-    [Box_Decoration_Break
-     []
-     [["box-decoration-break"]]]
-
-    [Caption
-     []
-     [["caption-side"]]]
-
-    [Clear
-     []
-     [["clear"]]]
-
-    [Shadow
-     []
-     [["box-shadow"]
-      ["text-shadow"]]]
-    
-    [Clip
-     []
-     [["clip"]]]
-
-    [Content
-     []
-     [["counter-reset"]
-      ["counter-increment"]]]
-
-    [Cursor
-     []
-     [["cursor"]]]
-
-    [Text_Direction
-     [[text_direction "direction"]]
-     []]
-
-    [Display
-     []
-     [["display"]]]
-
-    [Empty
-     []
-     [["empty-cells"]]]
-
-    [Filter
-     []
-     [["filter"]]]
-
-    [Flex_Direction
-     []
-     [["flex-direction"]]]
-
-    [Flex_Wrap
-     []
-     [["flex-wrap"]]]
-
-    [Float
-     []
-     [["float"]]]
-
-    [Font
-     []
-     [["font-family"]]]
-
-    [Font_Kerning
-     []
-     [["font-kerning"]]]
-
-    [Font_Size
-     []
-     [["font-size"]]]
-
-    [Number
-     []
-     [["font-size-adjust"]
-      ["opacity"]]]
-
-    [Font_Variant
-     []
-     [["font-variant"]]]
-
-    [Grid
-     []
-     [["grid-area"]]]
-
-    [Grid_Content
-     []
-     [["grid-auto-columns"]
-      ["grid-auto-rows"]
-      ["grid-template-columns"]
-      ["grid-template-rows"]]]
-
-    [Grid_Flow
-     []
-     [["grid-auto-flow"]]]
-
-    [Grid_Span
-     []
-     [["grid-column-end"]
-      ["grid-column-start"]
-      ["grid-row-end"]
-      ["grid-row-start"]]]
-
-    [Grid_Template
-     []
-     [["grid-template-areas"]]]
-
-    [Hanging_Punctuation
-     []
-     [["hanging-punctuation"]]]
-
-    [Hyphens
-     []
-     [["hyphens"]]]
-
-    [Isolation
-     []
-     [["isolation"]]]
-
-    [List_Style_Position
-     []
-     [["list-style-position"]]]
-
-    [List_Style_Type
-     []
-     [["list-style-type"]]]
-
-    [Overflow
-     []
-     [["overflow"]
-      ["overflow-x"]
-      ["overflow-y"]]]
-
-    [Page_Break
-     []
-     [["page-break-after"]
-      ["page-break-before"]
-      ["page-break-inside"]]]
-
-    [Pointer_Events
-     []
-     [["pointer-events"]]]
-
-    [Position
-     []
-     [["position"]]]
-
-    [Quotes
-     []
-     [["quotes"]]]
-
-    [Resize
-     []
-     [["resize"]]]
-
-    [Scroll_Behavior
-     []
-     [["scroll-behavior"]]]
-
-    [Table_Layout
-     []
-     [["table-layout"]]]
-
-    [Text_Align
-     []
-     [["text-align"]]]
-
-    [Text_Align_Last
-     []
-     [["text-align-last"]]]
-
-    [Text_Decoration_Line
-     []
-     [["text-decoration-line"]]]
-
-    [Text_Decoration_Style
-     []
-     [["text-decoration-style"]]]
-
-    [Text_Justification
-     []
-     [["text-justify"]]]
-
-    [Text_Overflow
-     []
-     [["text-overflow"]]]
-
-    [Text_Transform
-     []
-     [["text-transform"]]]
-
-    [Transform
-     []
-     [["transform"]]]
-
-    [Transform_Origin
-     []
-     [["transform-origin"]]]
-
-    [Transform_Style
-     []
-     [["transform-style"]]]
-
-    [Transition
-     []
-     [["transition-property"]]]
-
-    [Bidi
-     []
-     [["unicode-bidi"]]]
-
-    [User_Select
-     []
-     [["user-select"]]]
-
-    [Vertical_Align
-     []
-     [["vertical-align"]]]
-
-    [White_Space
-     []
-     [["white-space"]]]
-
-    [Word_Break
-     []
-     [["word-break"]]]
-
-    [Word_Wrap
-     []
-     [["word-wrap"]]]
-
-    [Writing_Mode
-     []
-     [["writing-mode"]]]
-
-    [Z_Index
-     []
-     [["z-index"]]]
-    )
+  [(def: .public name
+     (-> (Property Any) Text)
+     (|>> :representation))
+
+   (template [ + +]
+     [(`` (template [ ]
+            [(def: .public 
+               (Property )
+               (:abstraction ))]
+
+            (~~ (template.spliced +))))
+
+      (with_expansions [ (template.spliced +)]
+        (template []
+          [(`` (def: .public (~~ (text_identifier ))
+                 (Property )
+                 (:abstraction )))]
+          
+          ))]
+
+     [All
+      []
+      [["all"]]]
+
+     [Length
+      []
+      [["border-image-outset"]
+       ["border-image-width"]
+       ["bottom"]
+       ["column-gap"]
+       ["column-width"]
+       ["flex-basis"]
+       ["grid-column-gap"]
+       ["grid-gap"]
+       ["grid-row-gap"]
+       ["height"]
+       ["left"]
+       ["letter-spacing"]
+       ["line-height"]
+       ["margin"]
+       ["margin-bottom"]
+       ["margin-left"]
+       ["margin-right"]
+       ["margin-top"]
+       ["max-height"]
+       ["max-width"]
+       ["min-height"]
+       ["min-width"]
+       ["outline-offset"]
+       ["padding"]
+       ["padding-bottom"]
+       ["padding-left"]
+       ["padding-right"]
+       ["padding-top"]
+       ["perspective"]
+       ["right"]
+       ["text-indent"]
+       ["top"]
+       ["width"]
+       ["word-spacing"]]]
+
+     [Time
+      []
+      [["animation-delay"]
+       ["animation-duration"]
+       ["transition-delay"]
+       ["transition-duration"]]]
+
+     [Slice
+      []
+      [["border-image-slice"]]]
+
+     [Color
+      [[text_color "color"]]
+      [["background-color"]
+       ["border-color"]
+       ["border-bottom-color"]
+       ["border-left-color"]
+       ["border-right-color"]
+       ["border-top-color"]
+       ["caret-color"]
+       ["column-rule-color"]
+       ["outline-color"]
+       ["text-decoration-color"]]]
+
+     [Alignment
+      []
+      [["align-content"]
+       ["align-items"]
+       ["align-self"]
+       ["justify-content"]]]
+
+     [Animation
+      []
+      [["animation-name"]]]
+
+     [Animation_Direction
+      []
+      [["animation-direction"]]]
+
+     [Animation_Fill
+      []
+      [["animation-fill-mode"]]]
+
+     [Column_Fill
+      []
+      [["column-fill"]]]
+
+     [Column_Span
+      []
+      [["column-span"]]]
+
+     [Iteration
+      []
+      [["animation-iteration-count"]]]
+
+     [Count
+      []
+      [["column-count"]
+       ["flex-grow"]
+       ["flex-shrink"]
+       ["order"]
+       ["tab-size"]]]
+
+     [Play
+      []
+      [["animation-play-state"]]]
+
+     [Timing
+      []
+      [["animation-timing-function"]
+       ["transition-timing-function"]]]
+
+     [Visibility
+      []
+      [["backface-visibility"]
+       ["visibility"]]]
+
+     [Attachment
+      []
+      [["background-attachment"]]]
+
+     [Blend
+      []
+      [["background-blend-mode"]
+       ["mix-blend-mode"]]]
+
+     [Image
+      []
+      [["background-image"]
+       ["border-image-source"]
+       ["list-style-image"]]]
+
+     [Span
+      []
+      [["background-clip"]
+       ["background-origin"]
+       ["box-sizing"]]]
+
+     [Location
+      []
+      [["background-position"]
+       ["object-position"]
+       ["perspective-origin"]]]
+
+     [Repeat
+      []
+      [["background-repeat"]
+       ["border-image-repeat"]]]
+
+     [Fit
+      []
+      [["background-size"]
+       ["border-radius"]
+       ["border-bottom-left-radius"]
+       ["border-bottom-right-radius"]
+       ["border-top-left-radius"]
+       ["border-top-right-radius"]
+       ["border-spacing"]
+       ["object-fit"]]]
+
+     [Border
+      []
+      [["border-style"]
+       ["border-bottom-style"]
+       ["border-left-style"]
+       ["border-right-style"]
+       ["border-top-style"]
+       ["column-rule-style"]
+       ["outline-style"]]]
+
+     [Thickness
+      []
+      [["border-width"]
+       ["border-bottom-width"]
+       ["border-left-width"]
+       ["border-right-width"]
+       ["border-top-width"]
+       ["column-rule-width"]
+       ["outline-width"]]]
+
+     [Collapse
+      []
+      [["border-collapse"]]]
+
+     [Box_Decoration_Break
+      []
+      [["box-decoration-break"]]]
+
+     [Caption
+      []
+      [["caption-side"]]]
+
+     [Clear
+      []
+      [["clear"]]]
+
+     [Shadow
+      []
+      [["box-shadow"]
+       ["text-shadow"]]]
+     
+     [Clip
+      []
+      [["clip"]]]
+
+     [Content
+      []
+      [["counter-reset"]
+       ["counter-increment"]]]
+
+     [Cursor
+      []
+      [["cursor"]]]
+
+     [Text_Direction
+      [[text_direction "direction"]]
+      []]
+
+     [Display
+      []
+      [["display"]]]
+
+     [Empty
+      []
+      [["empty-cells"]]]
+
+     [Filter
+      []
+      [["filter"]]]
+
+     [Flex_Direction
+      []
+      [["flex-direction"]]]
+
+     [Flex_Wrap
+      []
+      [["flex-wrap"]]]
+
+     [Float
+      []
+      [["float"]]]
+
+     [Font
+      []
+      [["font-family"]]]
+
+     [Font_Kerning
+      []
+      [["font-kerning"]]]
+
+     [Font_Size
+      []
+      [["font-size"]]]
+
+     [Number
+      []
+      [["font-size-adjust"]
+       ["opacity"]]]
+
+     [Font_Variant
+      []
+      [["font-variant"]]]
+
+     [Grid
+      []
+      [["grid-area"]]]
+
+     [Grid_Content
+      []
+      [["grid-auto-columns"]
+       ["grid-auto-rows"]
+       ["grid-template-columns"]
+       ["grid-template-rows"]]]
+
+     [Grid_Flow
+      []
+      [["grid-auto-flow"]]]
+
+     [Grid_Span
+      []
+      [["grid-column-end"]
+       ["grid-column-start"]
+       ["grid-row-end"]
+       ["grid-row-start"]]]
+
+     [Grid_Template
+      []
+      [["grid-template-areas"]]]
+
+     [Hanging_Punctuation
+      []
+      [["hanging-punctuation"]]]
+
+     [Hyphens
+      []
+      [["hyphens"]]]
+
+     [Isolation
+      []
+      [["isolation"]]]
+
+     [List_Style_Position
+      []
+      [["list-style-position"]]]
+
+     [List_Style_Type
+      []
+      [["list-style-type"]]]
+
+     [Overflow
+      []
+      [["overflow"]
+       ["overflow-x"]
+       ["overflow-y"]]]
+
+     [Page_Break
+      []
+      [["page-break-after"]
+       ["page-break-before"]
+       ["page-break-inside"]]]
+
+     [Pointer_Events
+      []
+      [["pointer-events"]]]
+
+     [Position
+      []
+      [["position"]]]
+
+     [Quotes
+      []
+      [["quotes"]]]
+
+     [Resize
+      []
+      [["resize"]]]
+
+     [Scroll_Behavior
+      []
+      [["scroll-behavior"]]]
+
+     [Table_Layout
+      []
+      [["table-layout"]]]
+
+     [Text_Align
+      []
+      [["text-align"]]]
+
+     [Text_Align_Last
+      []
+      [["text-align-last"]]]
+
+     [Text_Decoration_Line
+      []
+      [["text-decoration-line"]]]
+
+     [Text_Decoration_Style
+      []
+      [["text-decoration-style"]]]
+
+     [Text_Justification
+      []
+      [["text-justify"]]]
+
+     [Text_Overflow
+      []
+      [["text-overflow"]]]
+
+     [Text_Transform
+      []
+      [["text-transform"]]]
+
+     [Transform
+      []
+      [["transform"]]]
+
+     [Transform_Origin
+      []
+      [["transform-origin"]]]
+
+     [Transform_Style
+      []
+      [["transform-style"]]]
+
+     [Transition
+      []
+      [["transition-property"]]]
+
+     [Bidi
+      []
+      [["unicode-bidi"]]]
+
+     [User_Select
+      []
+      [["user-select"]]]
+
+     [Vertical_Align
+      []
+      [["vertical-align"]]]
+
+     [White_Space
+      []
+      [["white-space"]]]
+
+     [Word_Break
+      []
+      [["word-break"]]]
+
+     [Word_Wrap
+      []
+      [["word-wrap"]]]
+
+     [Writing_Mode
+      []
+      [["writing-mode"]]]
+
+     [Z_Index
+      []
+      [["z-index"]]]
+     )]
   )
diff --git a/stdlib/source/library/lux/data/format/css/query.lux b/stdlib/source/library/lux/data/format/css/query.lux
index adaed39ab..fe4c8f7d4 100644
--- a/stdlib/source/library/lux/data/format/css/query.lux
+++ b/stdlib/source/library/lux/data/format/css/query.lux
@@ -25,117 +25,111 @@
   (in (list (code.local_identifier (text.replaced "-" "_" identifier)))))
 
 (abstract: .public Media
-  {}
-  
   Text
 
-  (def: .public media
-    (-> Media Text)
-    (|>> :representation))
+  [(def: .public media
+     (-> Media Text)
+     (|>> :representation))
 
-  (template []
-    [(`` (def: .public (~~ (text_identifier ))
-           Media
-           (:abstraction )))]
+   (template []
+     [(`` (def: .public (~~ (text_identifier ))
+            Media
+            (:abstraction )))]
 
-    ["all"]
-    ["print"]
-    ["screen"]
-    ["speech"]
-    ))
+     ["all"]
+     ["print"]
+     ["screen"]
+     ["speech"]
+     )])
 
 (abstract: .public Feature
-  {}
-  
   Text
 
-  (def: .public feature
-    (-> Feature Text)
-    (|>> :representation))
-
-  (template [ ]
-    [(`` (def: .public ((~~ (text_identifier )) input)
-           (-> (Value ) Feature)
-           (:abstraction (format "("  ": " (//value.value input) ")"))))]
-
-    ["min-color" Count]
-    ["color" Count]
-    ["max-color" Count]
-
-    ["min-color-index" Count]
-    ["color-index" Count]
-    ["max-color-index" Count]
-
-    ["min-monochrome" Count]
-    ["monochrome" Count]
-    ["max-monochrome" Count]
-
-    ["min-height" Length]
-    ["height" Length]
-    ["max-height" Length]
-
-    ["min-width" Length]
-    ["width" Length]
-    ["max-width" Length]
-
-    ["min-resolution" Resolution]
-    ["resolution" Resolution]
-    ["max-resolution" Resolution]
-
-    ["aspect-ratio" Ratio]
-    ["max-aspect-ratio" Ratio]
-    ["min-aspect-ratio" Ratio]
-
-    ["display-mode" Display_Mode]
-    ["color-gamut" Color_Gamut]
-    ["grid" Boolean]
-    ["orientation" Orientation]
-    ["overflow-block" Block_Overflow]
-    ["overflow-inline" Inline_Overflow]
-    ["scan" Scan]
-    ["update" Update]
-    ["inverted-colors" Inverted_Colors]
-    ["pointer" Pointer]
-    ["any-pointer" Pointer]
-    ["hover" Hover]
-    ["any-hover" Hover]
-    ["light-level" Light]
-    ["scripting" Scripting]
-    ["prefers-reduced-motion" Motion]
-    ["prefers-color-scheme" Color_Scheme]
-    )
+  [(def: .public feature
+     (-> Feature Text)
+     (|>> :representation))
+
+   (template [ ]
+     [(`` (def: .public ((~~ (text_identifier )) input)
+            (-> (Value ) Feature)
+            (:abstraction (format "("  ": " (//value.value input) ")"))))]
+
+     ["min-color" Count]
+     ["color" Count]
+     ["max-color" Count]
+
+     ["min-color-index" Count]
+     ["color-index" Count]
+     ["max-color-index" Count]
+
+     ["min-monochrome" Count]
+     ["monochrome" Count]
+     ["max-monochrome" Count]
+
+     ["min-height" Length]
+     ["height" Length]
+     ["max-height" Length]
+
+     ["min-width" Length]
+     ["width" Length]
+     ["max-width" Length]
+
+     ["min-resolution" Resolution]
+     ["resolution" Resolution]
+     ["max-resolution" Resolution]
+
+     ["aspect-ratio" Ratio]
+     ["max-aspect-ratio" Ratio]
+     ["min-aspect-ratio" Ratio]
+
+     ["display-mode" Display_Mode]
+     ["color-gamut" Color_Gamut]
+     ["grid" Boolean]
+     ["orientation" Orientation]
+     ["overflow-block" Block_Overflow]
+     ["overflow-inline" Inline_Overflow]
+     ["scan" Scan]
+     ["update" Update]
+     ["inverted-colors" Inverted_Colors]
+     ["pointer" Pointer]
+     ["any-pointer" Pointer]
+     ["hover" Hover]
+     ["any-hover" Hover]
+     ["light-level" Light]
+     ["scripting" Scripting]
+     ["prefers-reduced-motion" Motion]
+     ["prefers-color-scheme" Color_Scheme]
+     )]
   )
 
 (abstract: .public Query
-  {}
-  
   Text
 
-  (def: .public query
-    (-> Query Text)
-    (|>> :representation))
-
-  (template [ ]
-    [(def: .public 
-       (-> Media Query)
-       (|>> ..media (format ) :abstraction))]
-
-    [except "not "]
-    [only "only "]
-    )
-
-  (def: .public not
-    (-> Feature Query)
-    (|>> ..feature (format "not ") :abstraction))
-
-  (template [ ]
-    [(def: .public ( left right)
-       (-> Query Query Query)
-       (:abstraction (format (:representation left)
-                             
-                             (:representation right))))]
-
-    [and " and "]
-    [or " or "]
-    )
+  [(def: .public query
+     (-> Query Text)
+     (|>> :representation))
+
+   (template [ ]
+     [(def: .public 
+        (-> Media Query)
+        (|>> ..media (format ) :abstraction))]
+
+     [except "not "]
+     [only "only "]
+     )
+
+   (def: .public not
+     (-> Feature Query)
+     (|>> ..feature (format "not ") :abstraction))
+
+   (template [ ]
+     [(def: .public ( left right)
+        (-> Query Query Query)
+        (:abstraction (format (:representation left)
+                              
+                              (:representation right))))]
+
+     [and " and "]
+     [or " or "]
+     )]
   )
diff --git a/stdlib/source/library/lux/data/format/css/selector.lux b/stdlib/source/library/lux/data/format/css/selector.lux
index c2742f93a..38eda4881 100644
--- a/stdlib/source/library/lux/data/format/css/selector.lux
+++ b/stdlib/source/library/lux/data/format/css/selector.lux
@@ -19,192 +19,188 @@
 (type: .public Class Label)
 (type: .public Attribute Label)
 
-(abstract: .public (Generic brand) {} Any)
+(abstract: .public (Generic brand) Any [])
 
 (template [ ]
-  [(abstract:  {} Any)
+  [(abstract:  Any [])
    (type: .public  (Generic ))]
 
   [Can_Chain Can_Chain']
   [Cannot_Chain Cannot_Chain']
   )
 
-(abstract: .public Unique {} Any)
-(abstract: .public Specific {} Any)
-(abstract: .public Composite {} Any)
+(abstract: .public Unique Any [])
+(abstract: .public Specific Any [])
+(abstract: .public Composite Any [])
 
 (abstract: .public (Selector kind)
-  {}
-  
   Text
 
-  (def: .public selector
-    (-> (Selector Any) Text)
-    (|>> :representation))
-
-  (def: .public any
-    (Selector Cannot_Chain)
-    (:abstraction "*"))
-
-  (def: .public tag
-    (-> Tag (Selector Cannot_Chain))
-    (|>> :abstraction))
-
-  (template [   ]
-    [(def: .public 
-       (->  (Selector ))
-       (|>> (format ) :abstraction))]
-
-    [id ID "#" Unique]
-    [class Class "." Can_Chain]
-    )
-
-  (template [   +]
-    [(`` (template [ ]
-           [(def: .public ( right left)
-              (-> (Selector ) (Selector ) (Selector ))
-              (:abstraction (format (:representation left)
-                                    
-                                    (:representation right))))]
-
-           (~~ (template.spliced +))))]
-
-    [Can_Chain (Generic Any) Can_Chain
-     [["" and]]]
-    [Unique (Generic Any) Composite
-     [["" for]]]
-    [Specific (Generic Any) Composite
-     [["" at]]]
-    [Any Any Composite
-     [["," or]
-      [" " in]
-      [">" sub]
-      ["+" next]
-      ["~" later]]]
-    )
-
-  (type: .public Combinator
-    (-> (Selector Any) (Selector Any) (Selector Composite)))
-
-  (def: .public (with? attribute)
-    (-> Attribute (Selector Can_Chain))
-    (:abstraction (format "[" attribute "]")))
-
-  (template [ ]
-    [(def: .public ( attribute value)
-       (-> Attribute Text (Selector Can_Chain))
-       (:abstraction (format "[" attribute  value "]")))]
-
-    ["=" same?]
-    ["~=" has?]
-    ["|=" has_start?]
-    ["^=" starts?]
-    ["$=" ends?]
-    ["*=" contains?]
-    )
-
-  (template [ +]
-    [(`` (template [ ]
-           [(def: .public 
-              (Selector Can_Chain)
-              (:abstraction ))]
-
-           (~~ (template.spliced +))))]
-
-    [Can_Chain
-     [[active ":active"]
-      [checked ":checked"]
-      [default ":default"]
-      [disabled ":disabled"]
-      [empty ":empty"]
-      [enabled ":enabled"]
-      [first_child ":first-child"]
-      [first_of_type ":first-of-type"]
-      [focused ":focus"]
-      [hovered ":hover"]
-      [in_range ":in-range"]
-      [indeterminate ":indeterminate"]
-      [invalid ":invalid"]
-      [last_child ":last-child"]
-      [last_of_type ":last-of-type"]
-      [link ":link"]
-      [only_of_type ":only-of-type"]
-      [only_child ":only-child"]
-      [optional ":optional"]
-      [out_of_range ":out-of-range"]
-      [read_only ":read-only"]
-      [read_write ":read-write"]
-      [required ":required"]
-      [root ":root"]
-      [target ":target"]
-      [valid ":valid"]
-      [visited ":visited"]]]
-    
-    [Specific
-     [[after "::after"]
-      [before "::before"]
-      [first_letter "::first-letter"]
-      [first_line "::first-line"]
-      [placeholder "::placeholder"]
-      [selection "::selection"]]]
-    )
-
-  (def: .public (language locale)
-    (-> Locale (Selector Can_Chain))
-    (|> locale
-        locale.code
-        (text.enclosed ["(" ")"])
-        (format ":lang")
-        :abstraction))
-
-  (def: .public not
-    (-> (Selector Any) (Selector Can_Chain))
-    (|>> :representation
+  [(def: .public selector
+     (-> (Selector Any) Text)
+     (|>> :representation))
+
+   (def: .public any
+     (Selector Cannot_Chain)
+     (:abstraction "*"))
+
+   (def: .public tag
+     (-> Tag (Selector Cannot_Chain))
+     (|>> :abstraction))
+
+   (template [   ]
+     [(def: .public 
+        (->  (Selector ))
+        (|>> (format ) :abstraction))]
+
+     [id ID "#" Unique]
+     [class Class "." Can_Chain]
+     )
+
+   (template [   +]
+     [(`` (template [ ]
+            [(def: .public ( right left)
+               (-> (Selector ) (Selector ) (Selector ))
+               (:abstraction (format (:representation left)
+                                     
+                                     (:representation right))))]
+
+            (~~ (template.spliced +))))]
+
+     [Can_Chain (Generic Any) Can_Chain
+      [["" and]]]
+     [Unique (Generic Any) Composite
+      [["" for]]]
+     [Specific (Generic Any) Composite
+      [["" at]]]
+     [Any Any Composite
+      [["," or]
+       [" " in]
+       [">" sub]
+       ["+" next]
+       ["~" later]]]
+     )
+
+   (type: .public Combinator
+     (-> (Selector Any) (Selector Any) (Selector Composite)))
+
+   (def: .public (with? attribute)
+     (-> Attribute (Selector Can_Chain))
+     (:abstraction (format "[" attribute "]")))
+
+   (template [ ]
+     [(def: .public ( attribute value)
+        (-> Attribute Text (Selector Can_Chain))
+        (:abstraction (format "[" attribute  value "]")))]
+
+     ["=" same?]
+     ["~=" has?]
+     ["|=" has_start?]
+     ["^=" starts?]
+     ["$=" ends?]
+     ["*=" contains?]
+     )
+
+   (template [ +]
+     [(`` (template [ ]
+            [(def: .public 
+               (Selector Can_Chain)
+               (:abstraction ))]
+
+            (~~ (template.spliced +))))]
+
+     [Can_Chain
+      [[active ":active"]
+       [checked ":checked"]
+       [default ":default"]
+       [disabled ":disabled"]
+       [empty ":empty"]
+       [enabled ":enabled"]
+       [first_child ":first-child"]
+       [first_of_type ":first-of-type"]
+       [focused ":focus"]
+       [hovered ":hover"]
+       [in_range ":in-range"]
+       [indeterminate ":indeterminate"]
+       [invalid ":invalid"]
+       [last_child ":last-child"]
+       [last_of_type ":last-of-type"]
+       [link ":link"]
+       [only_of_type ":only-of-type"]
+       [only_child ":only-child"]
+       [optional ":optional"]
+       [out_of_range ":out-of-range"]
+       [read_only ":read-only"]
+       [read_write ":read-write"]
+       [required ":required"]
+       [root ":root"]
+       [target ":target"]
+       [valid ":valid"]
+       [visited ":visited"]]]
+     
+     [Specific
+      [[after "::after"]
+       [before "::before"]
+       [first_letter "::first-letter"]
+       [first_line "::first-line"]
+       [placeholder "::placeholder"]
+       [selection "::selection"]]]
+     )
+
+   (def: .public (language locale)
+     (-> Locale (Selector Can_Chain))
+     (|> locale
+         locale.code
          (text.enclosed ["(" ")"])
-         (format ":not")
+         (format ":lang")
          :abstraction))
 
-  (abstract: .public Index
-    {}
-    
-    Text
-
-    (def: .public index
-      (-> Nat Index)
-      (|>> %.nat :abstraction))
-
-    (template [ ]
-      [(def: .public  Index (:abstraction ))]
+   (def: .public not
+     (-> (Selector Any) (Selector Can_Chain))
+     (|>> :representation
+          (text.enclosed ["(" ")"])
+          (format ":not")
+          :abstraction))
+
+   (abstract: .public Index
+     Text
+
+     [(def: .public index
+        (-> Nat Index)
+        (|>> %.nat :abstraction))
+
+      (template [ ]
+        [(def: .public  Index (:abstraction ))]
+        
+        [odd "odd"]
+        [even "even"]
+        )
+
+      (type: .public Formula
+        (Record
+         [#constant Int
+          #variable Int]))
+
+      (def: .public (formula input)
+        (-> Formula Index)
+        (let [(^slots [#constant #variable]) input]
+          (:abstraction (format (if (i.< +0 variable)
+                                  (%.int variable)
+                                  (%.nat (.nat variable)))
+                                (%.int constant)))))
       
-      [odd "odd"]
-      [even "even"]
-      )
-
-    (type: .public Formula
-      (Record
-       [#constant Int
-        #variable Int]))
-
-    (def: .public (formula input)
-      (-> Formula Index)
-      (let [(^slots [#constant #variable]) input]
-        (:abstraction (format (if (i.< +0 variable)
-                                (%.int variable)
-                                (%.nat (.nat variable)))
-                              (%.int constant)))))
-    
-    (template [ ]
-      [(def: .public ( index)
-         (-> Index (Selector Can_Chain))
-         (|> (:representation index)
-             (text.enclosed ["(" ")"])
-             (format )
-             (:abstraction Selector)))]
-
-      [nth_child ":nth-child"]
-      [nth_last_child ":nth-last-child"]
-      [nth_last_of_type ":nth-last-of-type"]
-      [nth_of_type ":nth-of-type"]
-      )
-    )
+      (template [ ]
+        [(def: .public ( index)
+           (-> Index (Selector Can_Chain))
+           (|> (:representation index)
+               (text.enclosed ["(" ")"])
+               (format )
+               (:abstraction Selector)))]
+
+        [nth_child ":nth-child"]
+        [nth_last_child ":nth-last-child"]
+        [nth_last_of_type ":nth-last-of-type"]
+        [nth_of_type ":nth-of-type"]
+        )]
+     )]
   )
diff --git a/stdlib/source/library/lux/data/format/css/style.lux b/stdlib/source/library/lux/data/format/css/style.lux
index 8fe761893..37b80b4ce 100644
--- a/stdlib/source/library/lux/data/format/css/style.lux
+++ b/stdlib/source/library/lux/data/format/css/style.lux
@@ -11,26 +11,24 @@
    ["[1][0]" property {"+" [Property]}]])
 
 (abstract: .public Style
-  {#.doc "The style associated with a CSS selector."}
-
   Text
 
-  (def: .public empty
-    Style
-    (:abstraction ""))
+  [(def: .public empty
+     Style
+     (:abstraction ""))
 
-  (def: .public separator
-    " ")
+   (def: .public separator
+     " ")
 
-  (def: .public (with [property value])
-    (All (_ brand)
-      (-> [(Property brand) (Value brand)]
-          (-> Style Style)))
-    (|>> :representation
-         (format (//property.name property) ": " (//value.value value) ";" ..separator)
-         :abstraction))
+   (def: .public (with [property value])
+     (All (_ brand)
+       (-> [(Property brand) (Value brand)]
+           (-> Style Style)))
+     (|>> :representation
+          (format (//property.name property) ": " (//value.value value) ";" ..separator)
+          :abstraction))
 
-  (def: .public inline
-    (-> Style Text)
-    (|>> :representation))
+   (def: .public inline
+     (-> Style Text)
+     (|>> :representation))]
   )
diff --git a/stdlib/source/library/lux/data/format/css/value.lux b/stdlib/source/library/lux/data/format/css/value.lux
index 9569c445b..ae4393448 100644
--- a/stdlib/source/library/lux/data/format/css/value.lux
+++ b/stdlib/source/library/lux/data/format/css/value.lux
@@ -33,21 +33,19 @@
 
 (template: (enumeration:    + +)
   (abstract: .public 
-    {}
-    
     
 
-    (def: .public 
-      (->  )
-      (|>> :representation))
+    [(def: .public 
+       (->  )
+       (|>> :representation))
 
-    (`` (template [ ]
-          [(def: .public   (:abstraction ))]
+     (`` (template [ ]
+           [(def: .public   (:abstraction ))]
 
-          (~~ (template.spliced +))
-          ))
+           (~~ (template.spliced +))
+           ))
 
-    (template.spliced +)))
+     (template.spliced +)]))
 
 (template: (multi:   )
   (def: .public ( pre post)
@@ -64,1281 +62,1271 @@
       (|> raw (text.split_at 1) maybe.trusted product.right))))
 
 (abstract: .public (Value brand)
-  {}
-  
   Text
 
-  (def: .public value
-    (-> (Value Any) Text)
-    (|>> :representation))
-
-  (template [ ]
-    [(def: .public  Value (:abstraction ))]
-
-    [initial "initial"]
-    [inherit "inherit"]
-    [unset "unset"]
-    )
-  
-  (template [ + +]
-    [(abstract: .public  {} Any)
-
-     (`` (template [ ]
-           [(def: .public 
-              (Value )
-              (:abstraction ))]
-           
-           (~~ (template.spliced +))))
-
-     (with_expansions [ (template.spliced +)]
-       (template []
-         [(`` (def: .public (~~ (..text_identifier ))
-                (Value )
-                (:abstraction )))]
-         
-         ))]
-
-    [All
-     []
-     []]
-
-    [Number
-     []
-     []]
-
-    [Length
-     []
-     []]
-
-    [Time
-     []
-     []]
-
-    [Thickness
-     []
-     [["medium"]
-      ["thin"]
-      ["thick"]]]
-
-    [Slice
-     [[full_slice "fill"]]
-     []]
-
-    [Alignment
-     [[auto_alignment "auto"]]
-     [["stretch"]
-      ["center"]
-      ["flex-start"]
-      ["flex-end"]
-      ["baseline"]
-      ["space-between"]
-      ["space-around"]]]
-
-    [Animation
-     []
-     []]
-
-    [Animation_Direction
-     [[normal_direction "normal"]]
-     [["reverse"]
-      ["alternate"]
-      ["alternate-reverse"]]]
-
-    [Animation_Fill
-     [[fill_forwards "forwards"]
-      [fill_backwards "backwards"]
-      [fill_both "both"]]
-     []]
-
-    [Column_Fill
-     []
-     [["balance"]
-      ["auto"]]]
-
-    [Column_Span
-     []
-     [["all"]]]
-
-    [Iteration
-     []
-     [["infinite"]]]
-
-    [Count
-     []
-     []]
-
-    [Play
-     []
-     [["paused"]
-      ["running"]]]
-
-    [Timing
-     []
-     [["linear"]
-      ["ease"]
-      ["ease-in"]
-      ["ease-out"]
-      ["ease-in-out"]
-      ["step-start"]
-      ["step-end"]]]
-
-    [Visibility
-     [[invisible "hidden"]
-      [collapse_visibility "collapse"]]
-     [["visible"]]]
-
-    [Attachment
-     [[scroll_attachment "scroll"]
-      [fixed_attachment "fixed"]
-      [local_attachment "local"]]
-     []]
-
-    [Blend
-     [[normal_blend "normal"]]
-     [["multiply"]
-      ["screen"]
-      ["overlay"]
-      ["darken"]
-      ["lighten"]
-      ["color-dodge"]
-      ["color-burn"]
-      ["difference"]
-      ["exclusion"]
-      ["hue"]
-      ["saturation"]
-      ["color"]
-      ["luminosity"]]]
-
-    [Span
-     []
-     [["border-box"]
-      ["padding-box"]
-      ["content-box"]]]
-
-    [Image
-     [[no_image "none"]]
-     []]
-
-    [Repeat
-     [[stretch_repeat "stretch"]]
-     [["repeat"]
-      ["repeat-x"]
-      ["repeat-y"]
-      ["no-repeat"]
-      ["space"]
-      ["round"]]]
-
-    [Location
-     [[left_top "left top"]
-      [left_center "left center"]
-      [left_bottom "left bottom"]
-      [right_top "right top"]
-      [right_center "right center"]
-      [right_bottom "right bottom"]
-      [center_top "center top"]
-      [center_center "center center"]
-      [center_bottom "center bottom"]]
-     []]
-
-    [Fit
-     [[no_fit "none"]]
-     [["fill"]
-      ["cover"]
-      ["contain"]
-      ["scale-down"]]]
-
-    [Border
-     []
-     [["hidden"]
-      ["dotted"]
-      ["dashed"]
-      ["solid"]
-      ["double"]
-      ["groove"]
-      ["ridge"]
-      ["inset"]
-      ["outset"]]]
-
-    [Collapse
-     []
-     [["separate"]
-      ["collapse"]]]
-
-    [Box_Decoration_Break
-     []
-     [["slice"]
-      ["clone"]]]
-
-    [Caption
-     []
-     [["top"]
-      ["bottom"]]]
-
-    [Float
-     [[float_left "left"]
-      [float_right "right"]]
-     []]
-
-    [Clear
-     [[clear_left "left"]
-      [clear_right "right"]
-      [clear_both "both"]]
-     []]
-
-    [Counter
-     []
-     []]
-
-    [Content
-     []
-     [["open-quote"]
-      ["close-quote"]
-      ["no-open-quote"]
-      ["no-close-quote"]]]
-
-    [Cursor
-     [[horizontal_text "text"]
-      [no_cursor "none"]]
-     [["alias"]
-      ["all-scroll"]
-      ["cell"]
-      ["context-menu"]
-      ["col-resize"]
-      ["copy"]
-      ["crosshair"]
-      ["default"]
-      ["e-resize"]
-      ["ew-resize"]
-      ["grab"]
-      ["grabbing"]
-      ["help"]
-      ["move"]
-      ["n-resize"]
-      ["ne-resize"]
-      ["nesw-resize"]
-      ["ns-resize"]
-      ["nw-resize"]
-      ["nwse-resize"]
-      ["no-drop"]
-      ["not-allowed"]
-      ["pointer"]
-      ["progress"]
-      ["row-resize"]
-      ["s-resize"]
-      ["se-resize"]
-      ["sw-resize"]
-      ["vertical-text"]
-      ["w-resize"]
-      ["wait"]
-      ["zoom-in"]
-      ["zoom-out"]]]
-
-    [Shadow
-     []
-     []]
-
-    [Clip
-     []
-     []]
-
-    [Text_Direction
-     [[left_to_right "ltr"]
-      [right_to_left "rtl"]]
-     []]
-
-    [Display
-     [[grid_display "grid"]
-      [no_display "none"]]
-     [["inline"]
-      ["block"]
-      ["contents"]
-      ["flex"]
-      ["inline-block"]
-      ["inline-flex"]
-      ["inline-grid"]
-      ["inline-table"]
-      ["list-item"]
-      ["run-in"]
-      ["table"]
-      ["table-caption"]
-      ["table-column-group"]
-      ["table-header-group"]
-      ["table-footer-group"]
-      ["table-row-group"]
-      ["table-cell"]
-      ["table-column"]
-      ["table-row"]]]
-
-    [Empty
-     []
-     [["show"]
-      ["hide"]]]
-
-    [Filter
-     []
-     []]
-
-    [Flex_Direction
-     []
-     [["row"]
-      ["row-reverse"]
-      ["column"]
-      ["column-reverse"]]]
-
-    [Flex_Wrap
-     [[no_wrap "nowrap"]]
-     [["wrap"]
-      ["wrap_reverse"]]]
-
-    [Font_Kerning
-     [[auto_kerning "auto"]
-      [normal_kerning "normal"]
-      [no_kerning "none"]]
-     []]
-
-    [Font_Size
-     [[medium_size "medium"]
-      [xx_small_size "xx-small"]
-      [x_small_size "x-small"]
-      [small_size "small"]
-      [large_size "large"]
-      [x_large_size "x-large"]
-      [xx_large_size "xx-large"]
-      [smaller_size "smaller"]
-      [larger_size "larger"]]
-     []]
-
-    [Font_Stretch
-     [[normal_stretch "normal"]]
-     [["condensed"]
-      ["ultra-condensed"]
-      ["extra-condensed"]
-      ["semi-condensed"]
-      ["expanded"]
-      ["semi-expanded"]
-      ["extra-expanded"]
-      ["ultra-expanded"]]]
-
-    [Font_Style
-     [[normal_style "normal"]]
-     [["italic"]
-      ["oblique"]]]
-
-    [Font_Weight
-     [[normal_weight "normal"]
-      [weight_100 "100"]
-      [weight_200 "200"]
-      [weight_300 "300"]
-      [weight_400 "400"]
-      [weight_500 "500"]
-      [weight_600 "600"]
-      [weight_700 "700"]
-      [weight_800 "800"]
-      [weight_900 "900"]]
-     [["bold"]]]
-
-    [Font_Variant
-     [[normal_font "normal"]]
-     [["small-caps"]]]
-
-    [Grid
-     []
-     []]
-
-    [Grid_Content
-     [[auto_content "auto"]]
-     [["max-content"]
-      ["min-content"]]]
-
-    [Grid_Flow
-     [[row_flow "row"]
-      [column_flow "column"]
-      [dense_flow "dense"]
-      [row_dense_flow "row dense"]
-      [column_dense_flow "column dense"]]
-     []]
-
-    [Grid_Span
-     [[auto_span "auto"]]
-     []]
-
-    [Grid_Template
-     []
-     []]
-
-    [Hanging_Punctuation
-     [[no_hanging_punctuation "none"]]
-     [["first"]
-      ["last"]
-      ["allow-end"]
-      ["force-end"]]]
-
-    [Hyphens
-     [[no_hyphens "none"]
-      [manual_hyphens "manual"]
-      [auto_hyphens "auto"]]
-     []]
-
-    [Orientation
-     []
-     [["portrait"]
-      ["landscape"]]]
-
-    [Resolution
-     []
-     []]
-
-    [Scan
-     []
-     [["interlace"]
-      ["progressive"]]]
-
-    [Boolean
-     [[false "0"]
-      [true "1"]]
-     []]
-
-    [Update
-     [[no_update "none"]
-      [slow_update "slow"]
-      [fast_update "fast"]]
-     []]
-
-    [Block_Overflow
-     [[no_block_overflow "none"]
-      [scroll_block_overflow "scroll"]
-      [optional_paged_block_overflow "optional-paged"]
-      [paged_block_overflow "paged"]]
-     []]
-
-    [Inline_Overflow
-     [[no_inline_overflow "none"]
-      [scroll_inline_overflow "scroll"]]
-     []]
-
-    [Display_Mode
-     []
-     [["fullscreen"]
-      ["standalone"]
-      ["minimal-ui"]
-      ["browser"]]]
-
-    [Color_Gamut
-     []
-     [["srgb"]
-      ["p3"]
-      ["rec2020"]]]
-
-    [Inverted_Colors
-     [[no_inverted_colors "none"]
-      [inverted_colors "inverted"]]
-     []]
-
-    [Pointer
-     [[no_pointer "none"]
-      [coarse_pointer "coarse"]
-      [fine_pointer "fine"]]
-     []]
-
-    [Hover
-     [[no_hover "none"]]
-     [["hover"]]]
-
-    [Light
-     [[dim_light "dim"]
-      [normal_light "normal"]
-      [washed_light "washed"]]
-     []]
-
-    [Ratio
-     []
-     []]
-
-    [Scripting
-     [[no_scripting "none"]
-      [initial_scripting_only "initial-only"]
-      [scripting_enabled "enabled"]]
-     []]
-
-    [Motion
-     [[no_motion_preference "no-preference"]
-      [reduced_motion "reduce"]]
-     []]
-
-    [Color_Scheme
-     [[no_color_scheme_preference "no-preference"]
-      [light_color_scheme "light"]
-      [dark_color_scheme "dark"]]
-     []]
-
-    [Isolation
-     [[auto_isolation "auto"]]
-     [["isolate"]]]
-
-    [List_Style_Position
-     []
-     [["inside"]
-      ["outside"]]]
-
-    [List_Style_Type
-     [[no_list_style "none"]]
-     [["disc"]
-      ["armenian"]
-      ["circle"]
-      ["cjk-ideographic"]
-      ["decimal"]
-      ["decimal-leading-zero"]
-      ["georgian"]
-      ["hebrew"]
-      ["hiragana"]
-      ["hiragana-iroha"]
-      ["katakana"]
-      ["katakana-iroha"]
-      ["lower-alpha"]
-      ["lower-greek"]
-      ["lower-latin"]
-      ["lower-roman"]
-      ["square"]
-      ["upper-alpha"]
-      ["upper-greek"]
-      ["upper-latin"]
-      ["upper-roman"]]]
-
-    [Color
-     []
-     []]
-
-    [Overflow
-     [[visible_overflow "visible"]
-      [hidden_overflow "hidden"]
-      [scroll_overflow "scroll"]
-      [auto_overflow "auto"]]
-     []]
-
-    [Page_Break
-     [[auto_page_break "auto"]
-      [always_page_break "always"]
-      [avoid_page_break "avoid"]
-      [left_page_break "left"]
-      [right_page_break "right"]]
-     []]
-
-    [Pointer_Events
-     [[auto_pointer_events "auto"]
-      [no_pointer_events "none"]]
-     []]
-
-    [Position
-     []
-     [["static"]
-      ["absolute"]
-      ["fixed"]
-      ["relative"]
-      ["sticky"]]]
-
-    [Quotes
-     [[no_quotes "none"]]
-     []]
-
-    [Resize
-     [[resize_none "none"]
-      [resize_both "both"]
-      [resize_horizontal "horizontal"]
-      [resize_vertical "vertical"]]
-     []]
-
-    [Scroll_Behavior
-     [[auto_scroll_behavior "auto"]
-      [smooth_scroll_behavior "smooth"]]
-     []]
-
-    [Table_Layout
-     [[auto_table_layout "auto"]
-      [fixed_table_layout "fixed"]]
-     []]
-
-    [Text_Align
-     [[left_text_align "left"]
-      [right_text_align "right"]
-      [center_text_align "center"]
-      [justify_text_align "justify"]]
-     []]
-
-    [Text_Align_Last
-     [[auto_text_align_last "auto"]
-      [left_text_align_last "left"]
-      [right_text_align_last "right"]
-      [center_text_align_last "center"]
-      [justify_text_align_last "justify"]
-      [start_text_align_last "start"]
-      [end_text_align_last "end"]]
-     []]
-
-    [Text_Decoration_Line
-     [[no_text_decoration_line "none"]
-      [underline_text_decoration_line "underline"]
-      [overline_text_decoration_line "overline"]
-      [line_through_text_decoration_line "line-through"]]
-     []]
-
-    [Text_Decoration_Style
-     [[solid_text_decoration_style "solid"]
-      [double_text_decoration_style "double"]
-      [dotted_text_decoration_style "dotted"]
-      [dashed_text_decoration_style "dashed"]
-      [wavy_text_decoration_style "wavy"]]
-     []]
-
-    [Text_Justification
-     [[auto_text_justification "auto"]
-      [inter_word_text_justification "inter-word"]
-      [inter_character_text_justification "inter-character"]
-      [no_text_justification "none"]]
-     []]
-
-    [Text_Overflow
-     [[clip_text_overflow "clip"]
-      [ellipsis_text_overflow "ellipsis"]]
-     []]
-
-    [Text_Transform
-     [[no_text_transform "none"]]
-     [["capitalize"]
-      ["uppercase"]
-      ["lowercase"]]]
-
-    [Transform
-     [[no_transform "none"]]
-     []]
-
-    [Transform_Origin
-     []
-     []]
-
-    [Transform_Style
-     []
-     [["flat"]
-      ["preserve_3d"]]]
-
-    [Transition
-     [[transition_none "none"]
-      [transition_all "all"]]
-     []]
-
-    [Bidi
-     [[bidi_normal "normal"]
-      [bidi_embed "embed"]
-      [bidi_isolate "isolate"]
-      [bidi_isolate_override "isolate-override"]
-      [bidi_plaintext "plaintext"]]
-     [["bidi-override"]]]
-
-    [User_Select
-     [[user_select_auto "auto"]
-      [user_select_none "none"]
-      [user_select_text "text"]
-      [user_select_all "all"]]
-     []]
-
-    [Vertical_Align
-     [[vertical_align_baseline "baseline"]
-      [vertical_align_sub "sub"]
-      [vertical_align_super "super"]
-      [vertical_align_top "top"]
-      [vertical_align_text_top "text-top"]
-      [vertical_align_middle "middle"]
-      [vertical_align_bottom "bottom"]
-      [vertical_align_text_bottom "text-bottom"]]
-     []]
-
-    [White_Space
-     [[normal_white_space "normal"]
-      [no_wrap_white_space "nowrap"]
-      [pre_white_space "pre"]
-      [pre_line_white_space "pre-line"]
-      [pre_wrap_white_space "pre-wrap"]]
-     []]
-
-    [Word_Break
-     [[normal_word_break "normal"]]
-     [["break-all"]
-      ["keep-all"]
-      ["break-word"]]]
-
-    [Word_Wrap
-     [[normal_word_wrap "normal"]
-      [break_word_word_wrap "break-word"]]
-     []]
-
-    [Writing_Mode
-     [[top_to_bottom_writing_mode "horizontal-tb"]
-      [left_to_right_writing_mode "vertical-rl"]
-      [right_to_left_writing_mode "vertical-lr"]]
-     []]
-
-    [Z_Index
-     []
-     []]
-    )
-
-  (def: value_separator ",")
-
-  (def: (apply name inputs)
-    (-> Text (List Text) Value)
-    (|> inputs
-        (text.interposed ..value_separator)
-        (text.enclosed ["(" ")"])
-        (format name)
-        :abstraction))
-
-  (enumeration: Step Text
-    step
-    [[start "start"]
-     [end "end"]]
-    [])
-
-  (def: .public (steps intervals step)
-    (-> Nat Step (Value Timing))
-    (..apply "steps" (list (%.nat intervals) (..step step))))
-
-  (def: .public (cubic_bezier p0 p1 p2 p3)
-    (-> Frac Frac Frac Frac (Value Timing))
-    (|> (list p0 p1 p2 p3)
-        (list\each %number)
-        (..apply "cubic-bezier")))
-
-  (template [ ]
-    [(def: .public 
-       (-> Nat (Value ))
-       (|>> %.nat :abstraction))]
-
-    [iteration Iteration]
-    [count Count]
-    [slice_number/1 Slice]
-    [span_line Grid_Span]
-    )
-
-  (def: .public animation
-    (-> Label (Value Animation))
-    (|>> :abstraction))
-
-  (def: .public (rgb color)
-    (-> color.Color (Value Color))
-    (let [[red green blue] (color.rgb color)]
-      (..apply "rgb" (list (%.nat red)
-                           (%.nat green)
-                           (%.nat blue)))))
-
-  (def: .public (rgba pigment)
-    (-> color.Pigment (Value Color))
-    (let [(^slots [#color.color #color.alpha]) pigment
-          [red green blue] (color.rgb color)]
-      (..apply "rgba" (list (%.nat red)
-                            (%.nat green)
-                            (%.nat blue)
-                            (if (r.= (\ r.interval top) alpha)
-                              "1.0"
-                              (format "0" (%.rev alpha)))))))
-
-  (template [ ]
-    [(def: .public ( value)
-       (-> Frac (Value Length))
-       (:abstraction (format (%number value) )))]
-
-    [em "em"]
-    [ex "ex"]
-    [rem "rem"]
-    [ch "ch"]
-    [vw "vw"]
-    [vh "vh"]
-    [vmin "vmin"]
-    [vmax "vmax"]
-    [% "%"]
-    [cm "cm"]
-    [mm "mm"]
-    [in "in"]
-    [px "px"]
-    [pt "pt"]
-    [pc "pc"]
-    [fr "fr"]
-    )
-
-  (def: (%int value)
-    (Format Int)
-    (if (i.< +0 value)
-      (%.int value)
-      (%.nat (.nat value))))
-
-  (template [ ]
-    [(def: .public ( value)
-       (-> Int (Value Time))
-       (:abstraction (format (if (i.< +0 value)
-                               (%.int value)
-                               (%.nat (.nat value)))
-                             )))]
-
-    
-    [seconds "s"]
-    [milli_seconds "ms"]
-    )
-
-  (def: .public thickness
-    (-> (Value Length) (Value Thickness))
-    (|>> :transmutation))
-
-  (def: slice_separator " ")
-
-  (def: .public (slice_number/2 horizontal vertical)
-    (-> Nat Nat (Value Slice))
-    (:abstraction (format (%.nat horizontal) ..slice_separator
-                          (%.nat vertical))))
-
-  (abstract: .public Stop
-    {}
-    
-    Text
-
-    (def: .public stop
-      (-> (Value Color) Stop)
-      (|>> (:representation Value) (:abstraction Stop)))
-
-    (def: stop_separator " ")
-
-    (def: .public (single_stop length color)
-      (-> (Value Length) (Value Color) Stop)
-      (:abstraction (format (:representation Value color) ..stop_separator
-                            (:representation Value length))))
-
-    (def: .public (double_stop start end color)
-      (-> (Value Length) (Value Length) (Value Color) Stop)
-      (:abstraction (format (:representation Value color) ..stop_separator
-                            (:representation Value start) ..stop_separator
-                            (:representation Value end))))
-
-    (abstract: .public Hint
-      {}
-      
-      Text
-
-      (def: .public hint
-        (-> (Value Length) Hint)
-        (|>> (:representation Value) (:abstraction Hint)))
-
-      (def: (with_hint [hint stop])
-        (-> [(Maybe Hint) Stop] Text)
-        (case hint
-          #.None
-          (:representation Stop stop)
+  [(def: .public value
+     (-> (Value Any) Text)
+     (|>> :representation))
+
+   (template [ ]
+     [(def: .public  Value (:abstraction ))]
+
+     [initial "initial"]
+     [inherit "inherit"]
+     [unset "unset"]
+     )
+   
+   (template [ + +]
+     [(abstract: .public  Any [])
+
+      (`` (template [ ]
+            [(def: .public 
+               (Value )
+               (:abstraction ))]
+            
+            (~~ (template.spliced +))))
+
+      (with_expansions [ (template.spliced +)]
+        (template []
+          [(`` (def: .public (~~ (..text_identifier ))
+                 (Value )
+                 (:abstraction )))]
           
-          (#.Some hint)
-          (format (:representation Hint hint) ..value_separator (:representation Stop stop))))))
-
-  (type: .public (List/1 a)
-    [a (List a)])
-
-  (abstract: .public Angle
-    {}
-    
-    Text
-
-    (def: .public angle
-      (-> Angle Text)
-      (|>> :representation))
-
-    (def: .public (turn value)
-      (-> Rev Angle)
-      (:abstraction (format (%.rev value) "turn")))
-
-    (def: degree_limit Nat 360)
-    
-    (def: .public (degree value)
-      (-> Nat Angle)
-      (:abstraction (format (%.nat (n.% ..degree_limit value)) "deg")))
-
-    (template [ ]
-      [(def: .public 
-         Angle
-         (..degree ))]
+          ))]
+
+     [All
+      []
+      []]
+
+     [Number
+      []
+      []]
+
+     [Length
+      []
+      []]
+
+     [Time
+      []
+      []]
+
+     [Thickness
+      []
+      [["medium"]
+       ["thin"]
+       ["thick"]]]
+
+     [Slice
+      [[full_slice "fill"]]
+      []]
+
+     [Alignment
+      [[auto_alignment "auto"]]
+      [["stretch"]
+       ["center"]
+       ["flex-start"]
+       ["flex-end"]
+       ["baseline"]
+       ["space-between"]
+       ["space-around"]]]
+
+     [Animation
+      []
+      []]
+
+     [Animation_Direction
+      [[normal_direction "normal"]]
+      [["reverse"]
+       ["alternate"]
+       ["alternate-reverse"]]]
+
+     [Animation_Fill
+      [[fill_forwards "forwards"]
+       [fill_backwards "backwards"]
+       [fill_both "both"]]
+      []]
+
+     [Column_Fill
+      []
+      [["balance"]
+       ["auto"]]]
+
+     [Column_Span
+      []
+      [["all"]]]
+
+     [Iteration
+      []
+      [["infinite"]]]
+
+     [Count
+      []
+      []]
+
+     [Play
+      []
+      [["paused"]
+       ["running"]]]
+
+     [Timing
+      []
+      [["linear"]
+       ["ease"]
+       ["ease-in"]
+       ["ease-out"]
+       ["ease-in-out"]
+       ["step-start"]
+       ["step-end"]]]
+
+     [Visibility
+      [[invisible "hidden"]
+       [collapse_visibility "collapse"]]
+      [["visible"]]]
+
+     [Attachment
+      [[scroll_attachment "scroll"]
+       [fixed_attachment "fixed"]
+       [local_attachment "local"]]
+      []]
+
+     [Blend
+      [[normal_blend "normal"]]
+      [["multiply"]
+       ["screen"]
+       ["overlay"]
+       ["darken"]
+       ["lighten"]
+       ["color-dodge"]
+       ["color-burn"]
+       ["difference"]
+       ["exclusion"]
+       ["hue"]
+       ["saturation"]
+       ["color"]
+       ["luminosity"]]]
+
+     [Span
+      []
+      [["border-box"]
+       ["padding-box"]
+       ["content-box"]]]
+
+     [Image
+      [[no_image "none"]]
+      []]
+
+     [Repeat
+      [[stretch_repeat "stretch"]]
+      [["repeat"]
+       ["repeat-x"]
+       ["repeat-y"]
+       ["no-repeat"]
+       ["space"]
+       ["round"]]]
+
+     [Location
+      [[left_top "left top"]
+       [left_center "left center"]
+       [left_bottom "left bottom"]
+       [right_top "right top"]
+       [right_center "right center"]
+       [right_bottom "right bottom"]
+       [center_top "center top"]
+       [center_center "center center"]
+       [center_bottom "center bottom"]]
+      []]
+
+     [Fit
+      [[no_fit "none"]]
+      [["fill"]
+       ["cover"]
+       ["contain"]
+       ["scale-down"]]]
+
+     [Border
+      []
+      [["hidden"]
+       ["dotted"]
+       ["dashed"]
+       ["solid"]
+       ["double"]
+       ["groove"]
+       ["ridge"]
+       ["inset"]
+       ["outset"]]]
+
+     [Collapse
+      []
+      [["separate"]
+       ["collapse"]]]
+
+     [Box_Decoration_Break
+      []
+      [["slice"]
+       ["clone"]]]
+
+     [Caption
+      []
+      [["top"]
+       ["bottom"]]]
+
+     [Float
+      [[float_left "left"]
+       [float_right "right"]]
+      []]
+
+     [Clear
+      [[clear_left "left"]
+       [clear_right "right"]
+       [clear_both "both"]]
+      []]
+
+     [Counter
+      []
+      []]
+
+     [Content
+      []
+      [["open-quote"]
+       ["close-quote"]
+       ["no-open-quote"]
+       ["no-close-quote"]]]
+
+     [Cursor
+      [[horizontal_text "text"]
+       [no_cursor "none"]]
+      [["alias"]
+       ["all-scroll"]
+       ["cell"]
+       ["context-menu"]
+       ["col-resize"]
+       ["copy"]
+       ["crosshair"]
+       ["default"]
+       ["e-resize"]
+       ["ew-resize"]
+       ["grab"]
+       ["grabbing"]
+       ["help"]
+       ["move"]
+       ["n-resize"]
+       ["ne-resize"]
+       ["nesw-resize"]
+       ["ns-resize"]
+       ["nw-resize"]
+       ["nwse-resize"]
+       ["no-drop"]
+       ["not-allowed"]
+       ["pointer"]
+       ["progress"]
+       ["row-resize"]
+       ["s-resize"]
+       ["se-resize"]
+       ["sw-resize"]
+       ["vertical-text"]
+       ["w-resize"]
+       ["wait"]
+       ["zoom-in"]
+       ["zoom-out"]]]
+
+     [Shadow
+      []
+      []]
+
+     [Clip
+      []
+      []]
+
+     [Text_Direction
+      [[left_to_right "ltr"]
+       [right_to_left "rtl"]]
+      []]
+
+     [Display
+      [[grid_display "grid"]
+       [no_display "none"]]
+      [["inline"]
+       ["block"]
+       ["contents"]
+       ["flex"]
+       ["inline-block"]
+       ["inline-flex"]
+       ["inline-grid"]
+       ["inline-table"]
+       ["list-item"]
+       ["run-in"]
+       ["table"]
+       ["table-caption"]
+       ["table-column-group"]
+       ["table-header-group"]
+       ["table-footer-group"]
+       ["table-row-group"]
+       ["table-cell"]
+       ["table-column"]
+       ["table-row"]]]
+
+     [Empty
+      []
+      [["show"]
+       ["hide"]]]
+
+     [Filter
+      []
+      []]
+
+     [Flex_Direction
+      []
+      [["row"]
+       ["row-reverse"]
+       ["column"]
+       ["column-reverse"]]]
+
+     [Flex_Wrap
+      [[no_wrap "nowrap"]]
+      [["wrap"]
+       ["wrap_reverse"]]]
+
+     [Font_Kerning
+      [[auto_kerning "auto"]
+       [normal_kerning "normal"]
+       [no_kerning "none"]]
+      []]
+
+     [Font_Size
+      [[medium_size "medium"]
+       [xx_small_size "xx-small"]
+       [x_small_size "x-small"]
+       [small_size "small"]
+       [large_size "large"]
+       [x_large_size "x-large"]
+       [xx_large_size "xx-large"]
+       [smaller_size "smaller"]
+       [larger_size "larger"]]
+      []]
+
+     [Font_Stretch
+      [[normal_stretch "normal"]]
+      [["condensed"]
+       ["ultra-condensed"]
+       ["extra-condensed"]
+       ["semi-condensed"]
+       ["expanded"]
+       ["semi-expanded"]
+       ["extra-expanded"]
+       ["ultra-expanded"]]]
+
+     [Font_Style
+      [[normal_style "normal"]]
+      [["italic"]
+       ["oblique"]]]
+
+     [Font_Weight
+      [[normal_weight "normal"]
+       [weight_100 "100"]
+       [weight_200 "200"]
+       [weight_300 "300"]
+       [weight_400 "400"]
+       [weight_500 "500"]
+       [weight_600 "600"]
+       [weight_700 "700"]
+       [weight_800 "800"]
+       [weight_900 "900"]]
+      [["bold"]]]
+
+     [Font_Variant
+      [[normal_font "normal"]]
+      [["small-caps"]]]
+
+     [Grid
+      []
+      []]
+
+     [Grid_Content
+      [[auto_content "auto"]]
+      [["max-content"]
+       ["min-content"]]]
+
+     [Grid_Flow
+      [[row_flow "row"]
+       [column_flow "column"]
+       [dense_flow "dense"]
+       [row_dense_flow "row dense"]
+       [column_dense_flow "column dense"]]
+      []]
+
+     [Grid_Span
+      [[auto_span "auto"]]
+      []]
+
+     [Grid_Template
+      []
+      []]
+
+     [Hanging_Punctuation
+      [[no_hanging_punctuation "none"]]
+      [["first"]
+       ["last"]
+       ["allow-end"]
+       ["force-end"]]]
+
+     [Hyphens
+      [[no_hyphens "none"]
+       [manual_hyphens "manual"]
+       [auto_hyphens "auto"]]
+      []]
+
+     [Orientation
+      []
+      [["portrait"]
+       ["landscape"]]]
+
+     [Resolution
+      []
+      []]
+
+     [Scan
+      []
+      [["interlace"]
+       ["progressive"]]]
+
+     [Boolean
+      [[false "0"]
+       [true "1"]]
+      []]
+
+     [Update
+      [[no_update "none"]
+       [slow_update "slow"]
+       [fast_update "fast"]]
+      []]
+
+     [Block_Overflow
+      [[no_block_overflow "none"]
+       [scroll_block_overflow "scroll"]
+       [optional_paged_block_overflow "optional-paged"]
+       [paged_block_overflow "paged"]]
+      []]
+
+     [Inline_Overflow
+      [[no_inline_overflow "none"]
+       [scroll_inline_overflow "scroll"]]
+      []]
+
+     [Display_Mode
+      []
+      [["fullscreen"]
+       ["standalone"]
+       ["minimal-ui"]
+       ["browser"]]]
+
+     [Color_Gamut
+      []
+      [["srgb"]
+       ["p3"]
+       ["rec2020"]]]
+
+     [Inverted_Colors
+      [[no_inverted_colors "none"]
+       [inverted_colors "inverted"]]
+      []]
+
+     [Pointer
+      [[no_pointer "none"]
+       [coarse_pointer "coarse"]
+       [fine_pointer "fine"]]
+      []]
+
+     [Hover
+      [[no_hover "none"]]
+      [["hover"]]]
+
+     [Light
+      [[dim_light "dim"]
+       [normal_light "normal"]
+       [washed_light "washed"]]
+      []]
+
+     [Ratio
+      []
+      []]
+
+     [Scripting
+      [[no_scripting "none"]
+       [initial_scripting_only "initial-only"]
+       [scripting_enabled "enabled"]]
+      []]
+
+     [Motion
+      [[no_motion_preference "no-preference"]
+       [reduced_motion "reduce"]]
+      []]
+
+     [Color_Scheme
+      [[no_color_scheme_preference "no-preference"]
+       [light_color_scheme "light"]
+       [dark_color_scheme "dark"]]
+      []]
+
+     [Isolation
+      [[auto_isolation "auto"]]
+      [["isolate"]]]
+
+     [List_Style_Position
+      []
+      [["inside"]
+       ["outside"]]]
+
+     [List_Style_Type
+      [[no_list_style "none"]]
+      [["disc"]
+       ["armenian"]
+       ["circle"]
+       ["cjk-ideographic"]
+       ["decimal"]
+       ["decimal-leading-zero"]
+       ["georgian"]
+       ["hebrew"]
+       ["hiragana"]
+       ["hiragana-iroha"]
+       ["katakana"]
+       ["katakana-iroha"]
+       ["lower-alpha"]
+       ["lower-greek"]
+       ["lower-latin"]
+       ["lower-roman"]
+       ["square"]
+       ["upper-alpha"]
+       ["upper-greek"]
+       ["upper-latin"]
+       ["upper-roman"]]]
+
+     [Color
+      []
+      []]
+
+     [Overflow
+      [[visible_overflow "visible"]
+       [hidden_overflow "hidden"]
+       [scroll_overflow "scroll"]
+       [auto_overflow "auto"]]
+      []]
+
+     [Page_Break
+      [[auto_page_break "auto"]
+       [always_page_break "always"]
+       [avoid_page_break "avoid"]
+       [left_page_break "left"]
+       [right_page_break "right"]]
+      []]
+
+     [Pointer_Events
+      [[auto_pointer_events "auto"]
+       [no_pointer_events "none"]]
+      []]
+
+     [Position
+      []
+      [["static"]
+       ["absolute"]
+       ["fixed"]
+       ["relative"]
+       ["sticky"]]]
+
+     [Quotes
+      [[no_quotes "none"]]
+      []]
+
+     [Resize
+      [[resize_none "none"]
+       [resize_both "both"]
+       [resize_horizontal "horizontal"]
+       [resize_vertical "vertical"]]
+      []]
+
+     [Scroll_Behavior
+      [[auto_scroll_behavior "auto"]
+       [smooth_scroll_behavior "smooth"]]
+      []]
+
+     [Table_Layout
+      [[auto_table_layout "auto"]
+       [fixed_table_layout "fixed"]]
+      []]
+
+     [Text_Align
+      [[left_text_align "left"]
+       [right_text_align "right"]
+       [center_text_align "center"]
+       [justify_text_align "justify"]]
+      []]
+
+     [Text_Align_Last
+      [[auto_text_align_last "auto"]
+       [left_text_align_last "left"]
+       [right_text_align_last "right"]
+       [center_text_align_last "center"]
+       [justify_text_align_last "justify"]
+       [start_text_align_last "start"]
+       [end_text_align_last "end"]]
+      []]
+
+     [Text_Decoration_Line
+      [[no_text_decoration_line "none"]
+       [underline_text_decoration_line "underline"]
+       [overline_text_decoration_line "overline"]
+       [line_through_text_decoration_line "line-through"]]
+      []]
+
+     [Text_Decoration_Style
+      [[solid_text_decoration_style "solid"]
+       [double_text_decoration_style "double"]
+       [dotted_text_decoration_style "dotted"]
+       [dashed_text_decoration_style "dashed"]
+       [wavy_text_decoration_style "wavy"]]
+      []]
+
+     [Text_Justification
+      [[auto_text_justification "auto"]
+       [inter_word_text_justification "inter-word"]
+       [inter_character_text_justification "inter-character"]
+       [no_text_justification "none"]]
+      []]
+
+     [Text_Overflow
+      [[clip_text_overflow "clip"]
+       [ellipsis_text_overflow "ellipsis"]]
+      []]
+
+     [Text_Transform
+      [[no_text_transform "none"]]
+      [["capitalize"]
+       ["uppercase"]
+       ["lowercase"]]]
+
+     [Transform
+      [[no_transform "none"]]
+      []]
+
+     [Transform_Origin
+      []
+      []]
+
+     [Transform_Style
+      []
+      [["flat"]
+       ["preserve_3d"]]]
+
+     [Transition
+      [[transition_none "none"]
+       [transition_all "all"]]
+      []]
+
+     [Bidi
+      [[bidi_normal "normal"]
+       [bidi_embed "embed"]
+       [bidi_isolate "isolate"]
+       [bidi_isolate_override "isolate-override"]
+       [bidi_plaintext "plaintext"]]
+      [["bidi-override"]]]
+
+     [User_Select
+      [[user_select_auto "auto"]
+       [user_select_none "none"]
+       [user_select_text "text"]
+       [user_select_all "all"]]
+      []]
+
+     [Vertical_Align
+      [[vertical_align_baseline "baseline"]
+       [vertical_align_sub "sub"]
+       [vertical_align_super "super"]
+       [vertical_align_top "top"]
+       [vertical_align_text_top "text-top"]
+       [vertical_align_middle "middle"]
+       [vertical_align_bottom "bottom"]
+       [vertical_align_text_bottom "text-bottom"]]
+      []]
+
+     [White_Space
+      [[normal_white_space "normal"]
+       [no_wrap_white_space "nowrap"]
+       [pre_white_space "pre"]
+       [pre_line_white_space "pre-line"]
+       [pre_wrap_white_space "pre-wrap"]]
+      []]
+
+     [Word_Break
+      [[normal_word_break "normal"]]
+      [["break-all"]
+       ["keep-all"]
+       ["break-word"]]]
+
+     [Word_Wrap
+      [[normal_word_wrap "normal"]
+       [break_word_word_wrap "break-word"]]
+      []]
+
+     [Writing_Mode
+      [[top_to_bottom_writing_mode "horizontal-tb"]
+       [left_to_right_writing_mode "vertical-rl"]
+       [right_to_left_writing_mode "vertical-lr"]]
+      []]
+
+     [Z_Index
+      []
+      []]
+     )
+
+   (def: value_separator ",")
+
+   (def: (apply name inputs)
+     (-> Text (List Text) Value)
+     (|> inputs
+         (text.interposed ..value_separator)
+         (text.enclosed ["(" ")"])
+         (format name)
+         :abstraction))
+
+   (enumeration: Step Text
+     step
+     [[start "start"]
+      [end "end"]]
+     [])
+
+   (def: .public (steps intervals step)
+     (-> Nat Step (Value Timing))
+     (..apply "steps" (list (%.nat intervals) (..step step))))
+
+   (def: .public (cubic_bezier p0 p1 p2 p3)
+     (-> Frac Frac Frac Frac (Value Timing))
+     (|> (list p0 p1 p2 p3)
+         (list\each %number)
+         (..apply "cubic-bezier")))
+
+   (template [ ]
+     [(def: .public 
+        (-> Nat (Value ))
+        (|>> %.nat :abstraction))]
+
+     [iteration Iteration]
+     [count Count]
+     [slice_number/1 Slice]
+     [span_line Grid_Span]
+     )
+
+   (def: .public animation
+     (-> Label (Value Animation))
+     (|>> :abstraction))
+
+   (def: .public (rgb color)
+     (-> color.Color (Value Color))
+     (let [[red green blue] (color.rgb color)]
+       (..apply "rgb" (list (%.nat red)
+                            (%.nat green)
+                            (%.nat blue)))))
+
+   (def: .public (rgba pigment)
+     (-> color.Pigment (Value Color))
+     (let [(^slots [#color.color #color.alpha]) pigment
+           [red green blue] (color.rgb color)]
+       (..apply "rgba" (list (%.nat red)
+                             (%.nat green)
+                             (%.nat blue)
+                             (if (r.= (\ r.interval top) alpha)
+                               "1.0"
+                               (format "0" (%.rev alpha)))))))
+
+   (template [ ]
+     [(def: .public ( value)
+        (-> Frac (Value Length))
+        (:abstraction (format (%number value) )))]
+
+     [em "em"]
+     [ex "ex"]
+     [rem "rem"]
+     [ch "ch"]
+     [vw "vw"]
+     [vh "vh"]
+     [vmin "vmin"]
+     [vmax "vmax"]
+     [% "%"]
+     [cm "cm"]
+     [mm "mm"]
+     [in "in"]
+     [px "px"]
+     [pt "pt"]
+     [pc "pc"]
+     [fr "fr"]
+     )
+
+   (def: (%int value)
+     (Format Int)
+     (if (i.< +0 value)
+       (%.int value)
+       (%.nat (.nat value))))
+
+   (template [ ]
+     [(def: .public ( value)
+        (-> Int (Value Time))
+        (:abstraction (format (if (i.< +0 value)
+                                (%.int value)
+                                (%.nat (.nat value)))
+                              )))]
+
+     
+     [seconds "s"]
+     [milli_seconds "ms"]
+     )
+
+   (def: .public thickness
+     (-> (Value Length) (Value Thickness))
+     (|>> :transmutation))
+
+   (def: slice_separator " ")
+
+   (def: .public (slice_number/2 horizontal vertical)
+     (-> Nat Nat (Value Slice))
+     (:abstraction (format (%.nat horizontal) ..slice_separator
+                           (%.nat vertical))))
+
+   (abstract: .public Stop
+     Text
+
+     [(def: .public stop
+        (-> (Value Color) Stop)
+        (|>> (:representation Value) (:abstraction Stop)))
+
+      (def: stop_separator " ")
+
+      (def: .public (single_stop length color)
+        (-> (Value Length) (Value Color) Stop)
+        (:abstraction (format (:representation Value color) ..stop_separator
+                              (:representation Value length))))
+
+      (def: .public (double_stop start end color)
+        (-> (Value Length) (Value Length) (Value Color) Stop)
+        (:abstraction (format (:representation Value color) ..stop_separator
+                              (:representation Value start) ..stop_separator
+                              (:representation Value end))))
+
+      (abstract: .public Hint
+        Text
+
+        [(def: .public hint
+           (-> (Value Length) Hint)
+           (|>> (:representation Value) (:abstraction Hint)))
+
+         (def: (with_hint [hint stop])
+           (-> [(Maybe Hint) Stop] Text)
+           (case hint
+             #.None
+             (:representation Stop stop)
+             
+             (#.Some hint)
+             (format (:representation Hint hint) ..value_separator (:representation Stop stop))))])])
+
+   (type: .public (List/1 a)
+     [a (List a)])
+
+   (abstract: .public Angle
+     Text
+
+     [(def: .public angle
+        (-> Angle Text)
+        (|>> :representation))
+
+      (def: .public (turn value)
+        (-> Rev Angle)
+        (:abstraction (format (%.rev value) "turn")))
+
+      (def: degree_limit Nat 360)
       
-      [000 to_top]
-      [090 to_right]
-      [180 to_bottom]
-      [270 to_left]
-      )
-
-    (template [ ]
-      [(def: .public ( angle start next)
-         (-> Angle Stop (List/1 [(Maybe Hint) Stop]) (Value Image))
-         (let [[now after] next]
-           (..apply  (list& (:representation Angle angle)
-                                      (with_hint now)
-                                      (list\each with_hint after)))))]
-
-      [linear_gradient "linear-gradient"]
-      [repeating_linear_gradient "repeating-linear-gradient"]
-      )
-    )
-
-  (abstract: .public Percentage
-    {}
-    
-    Text
-
-    (def: .public percentage
-      (-> Percentage Text)
-      (|>> :representation))
-
-    (def: percentage_limit Nat (.++ 100))
-
-    (def: .public (%% value)
-      (-> Nat Percentage)
-      (:abstraction (format (%.nat (n.% percentage_limit value)) "%")))
-
-    (def: .public slice_percent/1
-      (-> Percentage (Value Slice))
-      (|>> :representation (:abstraction Value)))
-
-    (def: .public (slice_percent/2 horizontal vertical)
-      (-> Percentage Percentage (Value Slice))
-      (:abstraction Value (format (:representation horizontal) ..slice_separator
-                                  (:representation vertical))))
-
-    (template [ 
 +]
-      [(`` (template [ ]
-             [(def: .public 
-                (->  (Value Filter))
-                (|>> 
 (list) (..apply )))]
-
-             (~~ (template.spliced +))))]
-
-      [Nat (<| (:representation Value) ..px n.frac)
-       [[blur "blur"]]]
-      [Nat (<| ..angle ..degree)
-       [[hue_rotate "hue-rotate"]]]
-      [Percentage (:representation Percentage)
-       [[brightness "brightness"]
-        [contrast "contrast"]
-        [grayscale "grayscale"]
-        [invert "invert"]
-        [opacity "opacity"]
-        [saturate "saturate"]
-        [sepia "sepia"]]]
-      )
-    )
-
-  (def: .public svg_filter
-    (-> URL (Value Filter))
-    (|>> (list) (..apply "url")))
-
-  (def: default_shadow_length (px +0.0))
-
-  (def: .public (drop_shadow horizontal vertical blur spread color)
-    (-> (Value Length) (Value Length)
-        (Maybe (Value Length)) (Maybe (Value Length))
-        (Value Color)
-        (Value Filter))
-    (|> (list (:representation horizontal)
-              (:representation vertical)
-              (|> blur (maybe.else ..default_shadow_length) :representation)
-              (|> spread (maybe.else ..default_shadow_length) :representation)
-              (:representation color))
-        (text.interposed " ")
-        (list)
-        (..apply "drop-shadow")))
-
-  (def: length_separator " ")
-
-  (template [ ]
-    [(def: .public ( horizontal vertical)
-       (-> (Value Length) (Value Length) (Value ))
-       (:abstraction (format (:representation horizontal)
-                             ..length_separator
-                             (:representation vertical))))]
-
-    [location Location]
-    [fit Fit]
-    )
-
-  (def: .public (fit/1 length)
-    (-> (Value Length) (Value Fit))
-    (..fit length length))
-
-  (def: .public image
-    (-> URL (Value Image))
-    (|>> %.text
+      (def: .public (degree value)
+        (-> Nat Angle)
+        (:abstraction (format (%.nat (n.% ..degree_limit value)) "deg")))
+
+      (template [ ]
+        [(def: .public 
+           Angle
+           (..degree ))]
+        
+        [000 to_top]
+        [090 to_right]
+        [180 to_bottom]
+        [270 to_left]
+        )
+
+      (template [ ]
+        [(def: .public ( angle start next)
+           (-> Angle Stop (List/1 [(Maybe Hint) Stop]) (Value Image))
+           (let [[now after] next]
+             (..apply  (list& (:representation Angle angle)
+                                        (with_hint now)
+                                        (list\each with_hint after)))))]
+
+        [linear_gradient "linear-gradient"]
+        [repeating_linear_gradient "repeating-linear-gradient"]
+        )]
+     )
+
+   (abstract: .public Percentage
+     Text
+
+     [(def: .public percentage
+        (-> Percentage Text)
+        (|>> :representation))
+
+      (def: percentage_limit Nat (.++ 100))
+
+      (def: .public (%% value)
+        (-> Nat Percentage)
+        (:abstraction (format (%.nat (n.% percentage_limit value)) "%")))
+
+      (def: .public slice_percent/1
+        (-> Percentage (Value Slice))
+        (|>> :representation (:abstraction Value)))
+
+      (def: .public (slice_percent/2 horizontal vertical)
+        (-> Percentage Percentage (Value Slice))
+        (:abstraction Value (format (:representation horizontal) ..slice_separator
+                                    (:representation vertical))))
+
+      (template [ 
 +]
+        [(`` (template [ ]
+               [(def: .public 
+                  (->  (Value Filter))
+                  (|>> 
 (list) (..apply )))]
+
+               (~~ (template.spliced +))))]
+
+        [Nat (<| (:representation Value) ..px n.frac)
+         [[blur "blur"]]]
+        [Nat (<| ..angle ..degree)
+         [[hue_rotate "hue-rotate"]]]
+        [Percentage (:representation Percentage)
+         [[brightness "brightness"]
+          [contrast "contrast"]
+          [grayscale "grayscale"]
+          [invert "invert"]
+          [opacity "opacity"]
+          [saturate "saturate"]
+          [sepia "sepia"]]]
+        )]
+     )
+
+   (def: .public svg_filter
+     (-> URL (Value Filter))
+     (|>> (list) (..apply "url")))
+
+   (def: default_shadow_length (px +0.0))
+
+   (def: .public (drop_shadow horizontal vertical blur spread color)
+     (-> (Value Length) (Value Length)
+         (Maybe (Value Length)) (Maybe (Value Length))
+         (Value Color)
+         (Value Filter))
+     (|> (list (:representation horizontal)
+               (:representation vertical)
+               (|> blur (maybe.else ..default_shadow_length) :representation)
+               (|> spread (maybe.else ..default_shadow_length) :representation)
+               (:representation color))
+         (text.interposed " ")
          (list)
-         (..apply "url")))
-
-  (enumeration: Shape Text
-    shape
-    [[ellipse_shape "ellipse"]
-     [circle_shape "circle"]]
-    [])
-
-  (enumeration: Extent Text
-    extent
-    [[closest_side "closest-side"]
-     [closest_corner "closest-corner"]
-     [farthest_side "farthest-side"]
-     [farthest_corner "farthest-corner"]]
-    [])
-
-  (template [ ]
-    [(def: .public ( shape extent location start next)
-       (-> Shape (Maybe Extent) (Value Location)
-           Stop (List/1 [(Maybe Hint) Stop])
-           (Value Image))
-       (let [after_extent (format "at " (:representation location))
-             with_extent (case extent
-                           (#.Some extent)
-                           (format (..extent extent) " " after_extent)
-                           
-                           #.None
-                           after_extent)
-             where (format (..shape shape) " " with_extent)
-             [now after] next]
-         (..apply  (list& (..shape shape)
-                                    (with_hint now)
-                                    (list\each with_hint after)))))]
-    
-    [radial_gradient "radial-gradient"]
-    [repeating_radial_gradient "repeating-radial-gradient"]
-    )
-
-  (def: .public (shadow horizontal vertical blur spread color inset?)
-    (-> (Value Length) (Value Length)
-        (Maybe (Value Length)) (Maybe (Value Length))
-        (Value Color) Bit
-        (Value Shadow))
-    (let [with_inset (if inset?
-                       (list "inset")
-                       (list))]
-      (|> (list& (:representation horizontal)
-                 (:representation vertical)
-                 (|> blur (maybe.else ..default_shadow_length) :representation)
-                 (|> spread (maybe.else ..default_shadow_length) :representation)
-                 (:representation color)
-                 with_inset)
-          (text.interposed " ")
-          :abstraction)))
-
-  (type: .public Rectangle
-    (Record
-     [#top (Value Length)
-      #right (Value Length)
-      #bottom (Value Length)
-      #left (Value Length)]))
-
-  (def: .public (clip rectangle)
-    (-> Rectangle (Value Clip))
-    (`` (..apply "rect" (list (~~ (template []
-                                    [(:representation (value@  rectangle))]
-
-                                    [#top] [#right] [#bottom] [#left]))))))
-
-  (def: .public counter
-    (-> Label (Value Counter))
-    (|>> :abstraction))
-
-  (def: .public current_count
-    (-> (Value Counter) (Value Content))
-    (|>> :representation (list) (..apply "counter")))
-
-  (def: .public text
-    (-> Text (Value Content))
-    (|>> %.text :abstraction))
-
-  (def: .public attribute
-    (-> Label (Value Content))
-    (|>> (list) (..apply "attr")))
-
-  (def: .public media
-    (-> URL (Value Content))
-    (|>> (list) (..apply "url")))
-
-  (enumeration: Font Text
-    font_name
-    [[serif "serif"]
-     [sans_serif "sans-serif"]
-     [cursive "cursive"]
-     [fantasy "fantasy"]
-     [monospace "monospace"]]
-    [(def: .public font
-       (-> Text Font)
-       (|>> %.text :abstraction))
-
-     (def: .public (font_family options)
-       (-> (List Font) (Value Font))
-       (case options
-         (#.Item _)
-         (|> options
-             (list\each ..font_name)
-             (text.interposed ",")
-             (:abstraction Value))
-         
-         #.End
-         ..initial))])
-
-  (def: .public font_size
-    (-> (Value Length) (Value Font_Size))
-    (|>> :transmutation))
-
-  (def: .public number
-    (-> Frac (Value Number))
-    (|>> %number :abstraction))
-
-  (def: .public grid
-    (-> Label (Value Grid))
-    (|>> :abstraction))
-
-  (def: .public fit_content
-    (-> (Value Length) (Value Grid_Content))
-    (|>> :representation (list) (..apply "fit-content")))
-
-  (def: .public (min_max min max)
-    (-> (Value Grid_Content) (Value Grid_Content) (Value Grid_Content))
-    (..apply "minmax" (list (:representation min)
-                            (:representation max))))
-
-  (def: .public grid_span
-    (-> Nat (Value Grid_Span))
-    (|>> %.nat (format "span ") :abstraction))
-
-  (def: grid_column_separator " ")
-  (def: grid_row_separator " ")
-
-  (def: .public grid_template
-    (-> (List (List (Maybe (Value Grid)))) (Value Grid_Template))
-    (let [empty (: (Value Grid)
-                   (:abstraction "."))]
-      (|>> (list\each (|>> (list\each (|>> (maybe.else empty)
-                                           :representation))
-                           (text.interposed ..grid_column_separator)
-                           (text.enclosed ["'" "'"])))
-           (text.interposed ..grid_row_separator)
+         (..apply "drop-shadow")))
+
+   (def: length_separator " ")
+
+   (template [ ]
+     [(def: .public ( horizontal vertical)
+        (-> (Value Length) (Value Length) (Value ))
+        (:abstraction (format (:representation horizontal)
+                              ..length_separator
+                              (:representation vertical))))]
+
+     [location Location]
+     [fit Fit]
+     )
+
+   (def: .public (fit/1 length)
+     (-> (Value Length) (Value Fit))
+     (..fit length length))
+
+   (def: .public image
+     (-> URL (Value Image))
+     (|>> %.text
+          (list)
+          (..apply "url")))
+
+   (enumeration: Shape Text
+     shape
+     [[ellipse_shape "ellipse"]
+      [circle_shape "circle"]]
+     [])
+
+   (enumeration: Extent Text
+     extent
+     [[closest_side "closest-side"]
+      [closest_corner "closest-corner"]
+      [farthest_side "farthest-side"]
+      [farthest_corner "farthest-corner"]]
+     [])
+
+   (template [ ]
+     [(def: .public ( shape extent location start next)
+        (-> Shape (Maybe Extent) (Value Location)
+            Stop (List/1 [(Maybe Hint) Stop])
+            (Value Image))
+        (let [after_extent (format "at " (:representation location))
+              with_extent (case extent
+                            (#.Some extent)
+                            (format (..extent extent) " " after_extent)
+                            
+                            #.None
+                            after_extent)
+              where (format (..shape shape) " " with_extent)
+              [now after] next]
+          (..apply  (list& (..shape shape)
+                                     (with_hint now)
+                                     (list\each with_hint after)))))]
+     
+     [radial_gradient "radial-gradient"]
+     [repeating_radial_gradient "repeating-radial-gradient"]
+     )
+
+   (def: .public (shadow horizontal vertical blur spread color inset?)
+     (-> (Value Length) (Value Length)
+         (Maybe (Value Length)) (Maybe (Value Length))
+         (Value Color) Bit
+         (Value Shadow))
+     (let [with_inset (if inset?
+                        (list "inset")
+                        (list))]
+       (|> (list& (:representation horizontal)
+                  (:representation vertical)
+                  (|> blur (maybe.else ..default_shadow_length) :representation)
+                  (|> spread (maybe.else ..default_shadow_length) :representation)
+                  (:representation color)
+                  with_inset)
+           (text.interposed " ")
            :abstraction)))
 
-  (def: .public (resolution dpi)
-    (-> Nat (Value Resolution))
-    (:abstraction (format (%.nat dpi) "dpi")))
-
-  (def: .public (ratio numerator denominator)
-    (-> Nat Nat (Value Ratio))
-    (:abstraction (format (%.nat numerator) "/" (%.nat denominator))))
-
-  (enumeration: Quote Text
-    quote_text
-    [[double_quote "\0022"]
-     [single_quote "\0027"]
-     [single_left_angle_quote "\2039"]
-     [single_right_angle_quote "\203A"]
-     [double_left_angle_quote "\00AB"]
-     [double_right_angle_quote "\00BB"]
-     [single_left_quote "\2018"]
-     [single_right_quote "\2019"]
-     [double_left_quote "\201C"]
-     [double_right_quote "\201D"]
-     [low_double_quote "\201E"]]
-    [(def: .public quote
-       (-> Text Quote)
-       (|>> :abstraction))])
-
-  (def: quote_separator " ")
-
-  (def: .public (quotes [left0 right0] [left1 right1])
-    (-> [Quote Quote] [Quote Quote] (Value Quotes))
-    (|> (list left0 right0 left1 right1)
-        (list\each (|>> ..quote_text %.text))
-        (text.interposed ..quote_separator)
-        :abstraction))
-
-  (def: .public (matrix_2d [a b] [c d] [tx ty])
-    (-> [Frac Frac]
-        [Frac Frac]
-        [Frac Frac]
-        (Value Transform))
-    (|> (list a b c d tx ty)
-        (list\each %number)
-        (..apply "matrix")))
-
-  (def: .public (matrix_3d [a0 b0 c0 d0] [a1 b1 c1 d1] [a2 b2 c2 d2] [a3 b3 c3 d3])
-    (-> [Frac Frac Frac Frac]
-        [Frac Frac Frac Frac]
-        [Frac Frac Frac Frac]
-        [Frac Frac Frac Frac]
-        (Value Transform))
-    (|> (list a0 b0 c0 d0 a1 b1 c1 d1 a2 b2 c2 d2 a3 b3 c3 d3)
-        (list\each %number)
-        (..apply "matrix3d")))
-
-  (template [   ]
-    [(`` (def: .public ( [(~~ (template.spliced ))])
-           (-> [(~~ (template.spliced ))] (Value Transform))
-           (|> (list (~~ (template.spliced )))
-               (list\each %number)
-               (..apply ))))]
-
-    [translate_2d "translate" [Frac Frac] [x y]]
-    [translate_3d "translate3d" [Frac Frac Frac] [x y z]]
-    [translate_x "translateX" [Frac] [value]]
-    [translate_y "translateY" [Frac] [value]]
-    [translate_z "translateZ" [Frac] [value]]
-
-    [scale_2d "scale" [Frac Frac] [x y]]
-    [scale_3d "scale3d" [Frac Frac Frac] [x y z]]
-    [scale_x "scaleX" [Frac] [value]]
-    [scale_y "scaleY" [Frac] [value]]
-    [scale_z "scaleZ" [Frac] [value]]
-
-    [perspective "perspective" [Frac] [value]]
-    )
-
-  (template [   ]
-    [(`` (def: .public ( [(~~ (template.spliced ))])
-           (-> [(~~ (template.spliced ))] (Value Transform))
-           (|> (list (~~ (template.spliced )))
-               (list\each ..angle)
-               (..apply ))))]
-
-    [rotate_2d "rotate" [Angle] [angle]]
-    [rotate_x "rotateX" [Angle] [angle]]
-    [rotate_y "rotateY" [Angle] [angle]]
-    [rotate_z "rotateZ" [Angle] [angle]]
-
-    [skew "skew" [Angle Angle] [x_angle y_angle]]
-    [skew_x "skewX" [Angle] [angle]]
-    [skew_y "skewY" [Angle] [angle]]
-    )
-
-  (def: .public (rotate_3d [x y z angle])
-    (-> [Frac Frac Frac Angle] (Value Transform))
-    (..apply "rotate3d"
-             (list (%number x) (%number y) (%number z) (..angle angle))))
-
-  (def: origin_separator " ")
-
-  (def: .public (origin_2d x y)
-    (-> (Value Length) (Value Length) (Value Transform_Origin))
-    (:abstraction (format (:representation x) ..origin_separator
-                          (:representation y))))
-
-  (def: .public (origin_3d x y z)
-    (-> (Value Length) (Value Length) (Value Length) (Value Transform_Origin))
-    (:abstraction (format (:representation x) ..origin_separator
-                          (:representation y) ..origin_separator
-                          (:representation z))))
-
-  (def: .public vertical_align
-    (-> (Value Length) (Value Vertical_Align))
-    (|>> :transmutation))
-
-  (def: .public (z_index index)
-    (-> Int (Value Z_Index))
-    (:abstraction (if (i.< +0 index)
-                    (%.int index)
-                    (%.nat (.nat index)))))
-
-  (multi: multi_image Image ",")
-  (multi: multi_shadow Shadow ",")
-  (multi: multi_content Content " ")
+   (type: .public Rectangle
+     (Record
+      [#top (Value Length)
+       #right (Value Length)
+       #bottom (Value Length)
+       #left (Value Length)]))
+
+   (def: .public (clip rectangle)
+     (-> Rectangle (Value Clip))
+     (`` (..apply "rect" (list (~~ (template []
+                                     [(:representation (value@  rectangle))]
+
+                                     [#top] [#right] [#bottom] [#left]))))))
+
+   (def: .public counter
+     (-> Label (Value Counter))
+     (|>> :abstraction))
+
+   (def: .public current_count
+     (-> (Value Counter) (Value Content))
+     (|>> :representation (list) (..apply "counter")))
+
+   (def: .public text
+     (-> Text (Value Content))
+     (|>> %.text :abstraction))
+
+   (def: .public attribute
+     (-> Label (Value Content))
+     (|>> (list) (..apply "attr")))
+
+   (def: .public media
+     (-> URL (Value Content))
+     (|>> (list) (..apply "url")))
+
+   (enumeration: Font Text
+     font_name
+     [[serif "serif"]
+      [sans_serif "sans-serif"]
+      [cursive "cursive"]
+      [fantasy "fantasy"]
+      [monospace "monospace"]]
+     [(def: .public font
+        (-> Text Font)
+        (|>> %.text :abstraction))
+
+      (def: .public (font_family options)
+        (-> (List Font) (Value Font))
+        (case options
+          (#.Item _)
+          (|> options
+              (list\each ..font_name)
+              (text.interposed ",")
+              (:abstraction Value))
+          
+          #.End
+          ..initial))])
+
+   (def: .public font_size
+     (-> (Value Length) (Value Font_Size))
+     (|>> :transmutation))
+
+   (def: .public number
+     (-> Frac (Value Number))
+     (|>> %number :abstraction))
+
+   (def: .public grid
+     (-> Label (Value Grid))
+     (|>> :abstraction))
+
+   (def: .public fit_content
+     (-> (Value Length) (Value Grid_Content))
+     (|>> :representation (list) (..apply "fit-content")))
+
+   (def: .public (min_max min max)
+     (-> (Value Grid_Content) (Value Grid_Content) (Value Grid_Content))
+     (..apply "minmax" (list (:representation min)
+                             (:representation max))))
+
+   (def: .public grid_span
+     (-> Nat (Value Grid_Span))
+     (|>> %.nat (format "span ") :abstraction))
+
+   (def: grid_column_separator " ")
+   (def: grid_row_separator " ")
+
+   (def: .public grid_template
+     (-> (List (List (Maybe (Value Grid)))) (Value Grid_Template))
+     (let [empty (: (Value Grid)
+                    (:abstraction "."))]
+       (|>> (list\each (|>> (list\each (|>> (maybe.else empty)
+                                            :representation))
+                            (text.interposed ..grid_column_separator)
+                            (text.enclosed ["'" "'"])))
+            (text.interposed ..grid_row_separator)
+            :abstraction)))
+
+   (def: .public (resolution dpi)
+     (-> Nat (Value Resolution))
+     (:abstraction (format (%.nat dpi) "dpi")))
+
+   (def: .public (ratio numerator denominator)
+     (-> Nat Nat (Value Ratio))
+     (:abstraction (format (%.nat numerator) "/" (%.nat denominator))))
+
+   (enumeration: Quote Text
+     quote_text
+     [[double_quote "\0022"]
+      [single_quote "\0027"]
+      [single_left_angle_quote "\2039"]
+      [single_right_angle_quote "\203A"]
+      [double_left_angle_quote "\00AB"]
+      [double_right_angle_quote "\00BB"]
+      [single_left_quote "\2018"]
+      [single_right_quote "\2019"]
+      [double_left_quote "\201C"]
+      [double_right_quote "\201D"]
+      [low_double_quote "\201E"]]
+     [(def: .public quote
+        (-> Text Quote)
+        (|>> :abstraction))])
+
+   (def: quote_separator " ")
+
+   (def: .public (quotes [left0 right0] [left1 right1])
+     (-> [Quote Quote] [Quote Quote] (Value Quotes))
+     (|> (list left0 right0 left1 right1)
+         (list\each (|>> ..quote_text %.text))
+         (text.interposed ..quote_separator)
+         :abstraction))
+
+   (def: .public (matrix_2d [a b] [c d] [tx ty])
+     (-> [Frac Frac]
+         [Frac Frac]
+         [Frac Frac]
+         (Value Transform))
+     (|> (list a b c d tx ty)
+         (list\each %number)
+         (..apply "matrix")))
+
+   (def: .public (matrix_3d [a0 b0 c0 d0] [a1 b1 c1 d1] [a2 b2 c2 d2] [a3 b3 c3 d3])
+     (-> [Frac Frac Frac Frac]
+         [Frac Frac Frac Frac]
+         [Frac Frac Frac Frac]
+         [Frac Frac Frac Frac]
+         (Value Transform))
+     (|> (list a0 b0 c0 d0 a1 b1 c1 d1 a2 b2 c2 d2 a3 b3 c3 d3)
+         (list\each %number)
+         (..apply "matrix3d")))
+
+   (template [   ]
+     [(`` (def: .public ( [(~~ (template.spliced ))])
+            (-> [(~~ (template.spliced ))] (Value Transform))
+            (|> (list (~~ (template.spliced )))
+                (list\each %number)
+                (..apply ))))]
+
+     [translate_2d "translate" [Frac Frac] [x y]]
+     [translate_3d "translate3d" [Frac Frac Frac] [x y z]]
+     [translate_x "translateX" [Frac] [value]]
+     [translate_y "translateY" [Frac] [value]]
+     [translate_z "translateZ" [Frac] [value]]
+
+     [scale_2d "scale" [Frac Frac] [x y]]
+     [scale_3d "scale3d" [Frac Frac Frac] [x y z]]
+     [scale_x "scaleX" [Frac] [value]]
+     [scale_y "scaleY" [Frac] [value]]
+     [scale_z "scaleZ" [Frac] [value]]
+
+     [perspective "perspective" [Frac] [value]]
+     )
+
+   (template [   ]
+     [(`` (def: .public ( [(~~ (template.spliced ))])
+            (-> [(~~ (template.spliced ))] (Value Transform))
+            (|> (list (~~ (template.spliced )))
+                (list\each ..angle)
+                (..apply ))))]
+
+     [rotate_2d "rotate" [Angle] [angle]]
+     [rotate_x "rotateX" [Angle] [angle]]
+     [rotate_y "rotateY" [Angle] [angle]]
+     [rotate_z "rotateZ" [Angle] [angle]]
+
+     [skew "skew" [Angle Angle] [x_angle y_angle]]
+     [skew_x "skewX" [Angle] [angle]]
+     [skew_y "skewY" [Angle] [angle]]
+     )
+
+   (def: .public (rotate_3d [x y z angle])
+     (-> [Frac Frac Frac Angle] (Value Transform))
+     (..apply "rotate3d"
+              (list (%number x) (%number y) (%number z) (..angle angle))))
+
+   (def: origin_separator " ")
+
+   (def: .public (origin_2d x y)
+     (-> (Value Length) (Value Length) (Value Transform_Origin))
+     (:abstraction (format (:representation x) ..origin_separator
+                           (:representation y))))
+
+   (def: .public (origin_3d x y z)
+     (-> (Value Length) (Value Length) (Value Length) (Value Transform_Origin))
+     (:abstraction (format (:representation x) ..origin_separator
+                           (:representation y) ..origin_separator
+                           (:representation z))))
+
+   (def: .public vertical_align
+     (-> (Value Length) (Value Vertical_Align))
+     (|>> :transmutation))
+
+   (def: .public (z_index index)
+     (-> Int (Value Z_Index))
+     (:abstraction (if (i.< +0 index)
+                     (%.int index)
+                     (%.nat (.nat index)))))
+
+   (multi: multi_image Image ",")
+   (multi: multi_shadow Shadow ",")
+   (multi: multi_content Content " ")]
   )
diff --git a/stdlib/source/library/lux/data/format/html.lux b/stdlib/source/library/lux/data/format/html.lux
index 6b662a38d..5dfe95fce 100644
--- a/stdlib/source/library/lux/data/format/html.lux
+++ b/stdlib/source/library/lux/data/format/html.lux
@@ -80,496 +80,494 @@
   (text.enclosed [""]))
 
 (abstract: .public (HTML brand)
-  {}
-  
   Text
 
-  (template [ ]
-    [(abstract: .public  {} Any)
-     (type: .public  (HTML ))]
-
-    [Meta Meta']
-    [Head Head']
-    [Item Item']
-    [Option Option']
-    [Input Input']
-    [Cell Cell']
-    [Header Header']
-    [Row Row']
-    [Column Column']
-    [Parameter Parameter']
-    [Body Body']
-    [Document Document']
-    )
-
-  (template [  +]
-    [(abstract: .public ( brand) {} Any)
-     (type: .public  (HTML ( Any)))
-
-     (`` (template [ ]
-           [(abstract: .public  {} Any)
-            (type: .public  (HTML ( )))]
-
-           (~~ (template.spliced +))))]
-
-    [Element Element'
-     [[Content Content']
-      [Image Image']]]
-
-    [Media Media'
-     [[Source Source']
-      [Track Track']]]
-    )
-
-  (def: .public html
-    (-> Document Text)
-    (|>> :representation))
-
-  (def: .public (and pre post)
-    (All (_ brand) (-> (HTML brand) (HTML brand) (HTML brand)))
-    (:abstraction (format (:representation pre) (:representation post))))
-
-  (def: .public (comment content node)
-    (All (_ brand) (-> Text (HTML brand) (HTML brand)))
-    (:abstraction
-     (format (text.enclosed [""] content)
-             (:representation node))))
-
-  (def: (empty name attributes)
-    (-> Tag Attributes HTML)
-    (:abstraction
-     (format (..open name attributes)
-             (..close name))))
-
-  (def: (simple tag attributes)
-    (-> Tag Attributes HTML)
-    (|> attributes
-        (..open tag)
-        :abstraction))
-
-  (def: (tag name attributes content)
-    (-> Tag Attributes (HTML Any) HTML)
-    (:abstraction
-     (format (..open name attributes)
-             (:representation content)
-             (..close name))))
-
-  (def: (raw tag attributes content)
-    (-> Text Attributes Text HTML)
-    (:abstraction
-     (format (..open tag attributes)
-             content
-             (..close tag))))
-
-  (template [  ]
-    [(def: .public 
-       (-> Attributes )
-       (..simple ))]
-
-    [link "link" Meta]
-    [meta "meta" Meta]
-    [input "input" Input]
-    [embedded "embed" Element]
-    [column "col" Column]
-    [parameter "param" Parameter]
-    )
-
-  (def: .public (base href target)
-    (-> URL (Maybe Target) Meta)
-    (let [partial (list ["href" href])
-          full (case target
-                 (#.Some target)
-                 (list& ["target" (..target target)] partial)
-                 
-                 #.None
-                 partial)]
-      (..simple "base" full)))
-
-  (def: .public style
-    (-> Style Meta)
-    (|>> style.inline (..raw "style" (list))))
-
-  (def: .public (script attributes inline)
-    (-> Attributes (Maybe Script) Meta)
-    (|> inline
-        (maybe\each js.code)
-        (maybe.else "")
-        (..raw "script" attributes)))
-
-  (def: .public text
-    (-> Text Content)
-    (|>> ..safe
+  [(template [ ]
+     [(abstract: .public  Any [])
+      (type: .public  (HTML ))]
+
+     [Meta Meta']
+     [Head Head']
+     [Item Item']
+     [Option Option']
+     [Input Input']
+     [Cell Cell']
+     [Header Header']
+     [Row Row']
+     [Column Column']
+     [Parameter Parameter']
+     [Body Body']
+     [Document Document']
+     )
+
+   (template [  +]
+     [(abstract: .public ( brand) Any [])
+      (type: .public  (HTML ( Any)))
+
+      (`` (template [ ]
+            [(abstract: .public  Any [])
+             (type: .public  (HTML ( )))]
+
+            (~~ (template.spliced +))))]
+
+     [Element Element'
+      [[Content Content']
+       [Image Image']]]
+
+     [Media Media'
+      [[Source Source']
+       [Track Track']]]
+     )
+
+   (def: .public html
+     (-> Document Text)
+     (|>> :representation))
+
+   (def: .public (and pre post)
+     (All (_ brand) (-> (HTML brand) (HTML brand) (HTML brand)))
+     (:abstraction (format (:representation pre) (:representation post))))
+
+   (def: .public (comment content node)
+     (All (_ brand) (-> Text (HTML brand) (HTML brand)))
+     (:abstraction
+      (format (text.enclosed [""] content)
+              (:representation node))))
+
+   (def: (empty name attributes)
+     (-> Tag Attributes HTML)
+     (:abstraction
+      (format (..open name attributes)
+              (..close name))))
+
+   (def: (simple tag attributes)
+     (-> Tag Attributes HTML)
+     (|> attributes
+         (..open tag)
          :abstraction))
 
-  (template [  ]
-    [(def: .public 
-       Element
-       (..simple  (list)))
-
-     (def: .public  )]
-    ["br"  br  line_break]
-    ["wbr" wbr word_break]
-    ["hr"  hr  separator]
-    )
-
-  (def: .public (image source attributes)
-    (-> URL Attributes Image)
-    (|> attributes
-        (#.Item ["src" source])
-        (..simple "img")))
-
-  (def: .public (svg attributes content)
-    (-> Attributes XML Element)
-    (|> content
-        (\ xml.codec encoded)
-        (..raw "svg" attributes)))
-
-  (type: .public Coord
-    (Record
-     [#horizontal Nat
-      #vertical Nat]))
-
-  (def: metric_separator ",")
-  (def: coord_separator ",")
-
-  (def: (%coord [horizontal vertical])
-    (Format Coord)
-    (format (%.nat horizontal) ..metric_separator (%.nat vertical)))
-  
-  (type: .public Rectangle
-    (Record
-     [#start Coord
-      #end Coord]))
-
-  (type: .public Circle
-    (Record
-     [#center Coord
-      #radius Nat]))
-
-  (type: .public Polygon
-    (Record
-     [#first Coord
-      #second Coord
-      #third Coord
-      #extra (List Coord)]))
-
-  (def: (%rectangle [start end])
-    (Format Rectangle)
-    (format (%coord start) ..coord_separator (%coord end)))
-
-  (def: (%circle [center radius])
-    (Format Circle)
-    (format (%coord center) ..metric_separator (%.nat radius)))
-
-  (def: (%polygon [first second third extra])
-    (Format Polygon)
-    (|> (list& first second third extra)
-        (list\each %coord)
-        (text.interposed ..coord_separator)))
-  
-  (type: .public Shape
-    (Variant
-     (#Rectangle Rectangle)
-     (#Circle Circle)
-     (#Polygon Polygon)))
-
-  (template [   ]
-    [(def: ( attributes shape)
-       (-> Attributes  (HTML Any))
-       (..simple "area" (list& ["shape" ]
-                               ["coords" ( shape)]
-                               attributes)))]
-
-    [rectangle "rect" Rectangle ..%rectangle]
-    [circle "circle" Circle ..%circle]
-    [polygon "poly" Polygon ..%polygon]
-    )
-  
-  (def: (area attributes shape)
-    (-> Attributes Shape (HTML Any))
-    (case shape
-      (#Rectangle rectangle)
-      (..rectangle attributes rectangle)
-      
-      (#Circle circle)
-      (..circle attributes circle)
-      
-      (#Polygon polygon)
-      (..polygon attributes polygon)))
-
-  (def: .public (each attributes areas for)
-    (-> Attributes (List [Attributes Shape]) Image Image)
-    ($_ ..and
-        for
-        (case (list\each (product.uncurried ..area) areas)
-          #.End
-          (..empty "map" attributes)
-          
-          (#.Item head tail)
-          (..tag "map" attributes
-                 (list\mix (function.flipped ..and) head tail)))))
-
-  (template [  ]
-    [(def: .public 
-       (-> Attributes )
-       (..empty ))]
-
-    [canvas "canvas" Element]
-    [progress "progress" Element]
-    [output "output" Input]
-    [source "source" Source]
-    [track "track" Track]
-    )
-
-  (template [ ]
-    [(def: .public ( attributes media on_unsupported)
-       (-> Attributes Media (Maybe Content) Element)
-       (..tag  attributes
-              (|> on_unsupported
-                  (maybe.else (..text ""))
-                  (..and media))))]
-
-    [audio "audio"]
-    [video "video"]
-    )
-
-  (def: .public (picture attributes sources image)
-    (-> Attributes Source Image Element)
-    (..tag "picture" attributes (..and sources image)))
-
-  (def: .public (anchor href attributes content)
-    (-> URL Attributes Element Element)
-    (..tag "a" (list& ["href" href] attributes) content))
-
-  (def: .public label
-    (-> ID Input)
-    (|>> ["for"] list (..empty "label")))
-
-  (template [   ]
-    [(def: .public ( description attributes content)
-       (-> (Maybe Content) Attributes  )
-       (..tag  attributes
-              (case description
-                (#.Some description)
-                ($_ ..and
-                    (..tag  (list) description)
-                    content)
-                
-                #.None
-                content)))]
-
-    [details "details" "summary" Element]
-    [field_set "fieldset" "legend" Input]
-    [figure "figure" "figcaption" Element]
-    )
-
-  (template [  ]
-    [(def: .public ( attributes content)
-       (-> Attributes (Maybe Content) )
-       (|> content
-           (maybe.else (..text ""))
-           (..tag  attributes)))]
-
-    [text_area "textarea" Input]
-    [iframe "iframe" Element]
-    )
-
-  (type: .public Phrase
-    (-> Attributes Content Element))
-
-  (template [ ]
-    [(def: .public 
-       Phrase
-       (..tag ))]
-
-    [abbrebiation "abbr"]
-    [block_quote "blockquote"]
-    [bold "b"]
-    [cite "cite"]
-    [code "code"]
-    [definition "dfn"]
-    [deleted "del"]
-    [emphasized "em"]
-    [h1 "h1"]
-    [h2 "h2"]
-    [h3 "h3"]
-    [h4 "h4"]
-    [h5 "h5"]
-    [h6 "h6"]
-    [inserted "ins"]
-    [italic "i"]
-    [keyboard "kbd"]
-    [marked "mark"]
-    [meter "meter"]
-    [pre "pre"]
-    [quote "q"]
-    [sample "samp"]
-    [struck "s"]
-    [small "small"]
-    [sub "sub"]
-    [super "sup"]
-    [strong "strong"]
-    [time "time"]
-    [underlined "u"]
-    [variable "var"]
-    )
-
-  (def: .public incorrect ..struck)
-
-  (def: (ruby_pronunciation pronunciation)
-    (-> Content (HTML Any))
-    (..tag "rt" (list)
-           ($_ ..and
-               (..tag "rp" (list) (..text "("))
-               pronunciation
-               (..tag "rp" (list) (..text ")")))))
-
-  (def: .public (ruby attributes content pronunciation)
-    (-> Attributes Content Content Element)
-    (..tag "ruby" attributes
-           ($_ ..and
-               content
-               (ruby_pronunciation pronunciation))))
-
-  (type: .public Composite
-    (-> Attributes Element Element))
-
-  (template [ ]
-    [(def: .public 
-       Composite
-       (..tag ))]
-
-    [article "article"]
-    [aside "aside"]
-    [dialog "dialog"]
-    [div "div"]
-    [footer "footer"]
-    [header "header"]
-    [main "main"]
-    [navigation "nav"]
-    [paragraph "p"]
-    [section "section"]
-    [span "span"]
-    )
-
-  (template [  ]
-    [(def: 
-       (->  (HTML Any))
-       (..tag  (list)))]
-
-    ["dt" term Content]
-    ["dd" description Element]
-    )
-
-  (def: .public (description_list attributes descriptions)
-    (-> Attributes (List [Content Element]) Element)
-    (case (list\each (function (_ [term description])
-                       ($_ ..and
-                           (..term term)
-                           (..description description)))
-                     descriptions)
-      #.End
-      (..empty "dl" attributes)
-      
-      (#.Item head tail)
-      (..tag "dl" attributes
-             (list\mix (function.flipped ..and) head tail))))
-
-  (def: .public p ..paragraph)
-
-  (template [   ]
-    [(def: .public 
-       (-> Attributes  )
-       (..tag ))]
-
-    [button "button" Element Input]
-    [item "li" Element Item]
-    [ordered_list "ol" Item Element]
-    [unordered_list "ul" Item Element]
-    [option "option" Content Option]
-    [option_group "optgroup" Option Option]
-    [data_list "datalist" Option Element]
-    [select "select" Option Input]
-    [address "address" Element Element]
-    [form "form" Input Element]
-    [data "data" Element Element]
-    [object "object" Parameter Element]
-    )
-
-  (template [   ]
-    [(def: .public 
-       (->  )
-       (..tag  (list)))]
-
-    [title "title" Content Meta]
-    [no_script "noscript" Content Meta]
-    [template "template" (HTML Any) (HTML Nothing)]
-    [table_header "th" Element Header]
-    [table_cell "td" Element Cell]
-    [head "head" Meta Head]
-    [body "body" Element Body]
-    )
-
-  (template [   ]
-    [(def: 
-       (->  )
-       (..tag  (list)))]
-
-    [table_row "tr" (HTML Any) Row]
-    [table_head "thead" Row HTML]
-    [table_body "tbody" Row HTML]
-    [table_foot "tfoot" Row HTML]
-    [columns_group "colgroup" Column HTML]
-    )
-
-  (def: .public (table attributes caption columns headers rows footer)
-    (-> Attributes (Maybe Content) (Maybe Column) Header (List Cell) (Maybe Cell) Element)
-    (let [head (..table_head (..table_row headers))
-          content (case (list\each table_row rows)
-                    #.End
-                    head
-
-                    (#.Item first rest)
-                    (..and head
-                           (..table_body
-                            (list\mix (function.flipped ..and) first rest))))
-          content (case footer
-                    #.None
-                    content
-                    
-                    (#.Some footer)
-                    (..and content
-                           (..table_foot (..table_row footer))))
-          content (case columns
-                    #.None
-                    content
-                    
-                    (#.Some columns)
-                    (..and (..columns_group columns)
-                           content))
-          content (case caption
-                    #.None
-                    content
-
-                    (#.Some caption)
-                    (..and (:as HTML caption)
-                           content))]
-      (..tag "table" attributes
-             content)))
-
-  (template [ ]
-    [(def: .public 
-       (-> Head Body Document)
-       (let [doc_type ]
-         (function (_ head body)
-           (|> (..tag "html" (list) (..and head body))
-               :representation
-               (format doc_type)
-               :abstraction))))]
-
-    [html/5    ""]
-    [html/4_01 (format "")]
-    [xhtml/1_0 (format "")]
-    [xhtml/1_1 (format "")]
-    )
+   (def: (tag name attributes content)
+     (-> Tag Attributes (HTML Any) HTML)
+     (:abstraction
+      (format (..open name attributes)
+              (:representation content)
+              (..close name))))
+
+   (def: (raw tag attributes content)
+     (-> Text Attributes Text HTML)
+     (:abstraction
+      (format (..open tag attributes)
+              content
+              (..close tag))))
+
+   (template [  ]
+     [(def: .public 
+        (-> Attributes )
+        (..simple ))]
+
+     [link "link" Meta]
+     [meta "meta" Meta]
+     [input "input" Input]
+     [embedded "embed" Element]
+     [column "col" Column]
+     [parameter "param" Parameter]
+     )
+
+   (def: .public (base href target)
+     (-> URL (Maybe Target) Meta)
+     (let [partial (list ["href" href])
+           full (case target
+                  (#.Some target)
+                  (list& ["target" (..target target)] partial)
+                  
+                  #.None
+                  partial)]
+       (..simple "base" full)))
+
+   (def: .public style
+     (-> Style Meta)
+     (|>> style.inline (..raw "style" (list))))
+
+   (def: .public (script attributes inline)
+     (-> Attributes (Maybe Script) Meta)
+     (|> inline
+         (maybe\each js.code)
+         (maybe.else "")
+         (..raw "script" attributes)))
+
+   (def: .public text
+     (-> Text Content)
+     (|>> ..safe
+          :abstraction))
+
+   (template [  ]
+     [(def: .public 
+        Element
+        (..simple  (list)))
+
+      (def: .public  )]
+     ["br"  br  line_break]
+     ["wbr" wbr word_break]
+     ["hr"  hr  separator]
+     )
+
+   (def: .public (image source attributes)
+     (-> URL Attributes Image)
+     (|> attributes
+         (#.Item ["src" source])
+         (..simple "img")))
+
+   (def: .public (svg attributes content)
+     (-> Attributes XML Element)
+     (|> content
+         (\ xml.codec encoded)
+         (..raw "svg" attributes)))
+
+   (type: .public Coord
+     (Record
+      [#horizontal Nat
+       #vertical Nat]))
+
+   (def: metric_separator ",")
+   (def: coord_separator ",")
+
+   (def: (%coord [horizontal vertical])
+     (Format Coord)
+     (format (%.nat horizontal) ..metric_separator (%.nat vertical)))
+   
+   (type: .public Rectangle
+     (Record
+      [#start Coord
+       #end Coord]))
+
+   (type: .public Circle
+     (Record
+      [#center Coord
+       #radius Nat]))
+
+   (type: .public Polygon
+     (Record
+      [#first Coord
+       #second Coord
+       #third Coord
+       #extra (List Coord)]))
+
+   (def: (%rectangle [start end])
+     (Format Rectangle)
+     (format (%coord start) ..coord_separator (%coord end)))
+
+   (def: (%circle [center radius])
+     (Format Circle)
+     (format (%coord center) ..metric_separator (%.nat radius)))
+
+   (def: (%polygon [first second third extra])
+     (Format Polygon)
+     (|> (list& first second third extra)
+         (list\each %coord)
+         (text.interposed ..coord_separator)))
+   
+   (type: .public Shape
+     (Variant
+      (#Rectangle Rectangle)
+      (#Circle Circle)
+      (#Polygon Polygon)))
+
+   (template [   ]
+     [(def: ( attributes shape)
+        (-> Attributes  (HTML Any))
+        (..simple "area" (list& ["shape" ]
+                                ["coords" ( shape)]
+                                attributes)))]
+
+     [rectangle "rect" Rectangle ..%rectangle]
+     [circle "circle" Circle ..%circle]
+     [polygon "poly" Polygon ..%polygon]
+     )
+   
+   (def: (area attributes shape)
+     (-> Attributes Shape (HTML Any))
+     (case shape
+       (#Rectangle rectangle)
+       (..rectangle attributes rectangle)
+       
+       (#Circle circle)
+       (..circle attributes circle)
+       
+       (#Polygon polygon)
+       (..polygon attributes polygon)))
+
+   (def: .public (each attributes areas for)
+     (-> Attributes (List [Attributes Shape]) Image Image)
+     ($_ ..and
+         for
+         (case (list\each (product.uncurried ..area) areas)
+           #.End
+           (..empty "map" attributes)
+           
+           (#.Item head tail)
+           (..tag "map" attributes
+                  (list\mix (function.flipped ..and) head tail)))))
+
+   (template [  ]
+     [(def: .public 
+        (-> Attributes )
+        (..empty ))]
+
+     [canvas "canvas" Element]
+     [progress "progress" Element]
+     [output "output" Input]
+     [source "source" Source]
+     [track "track" Track]
+     )
+
+   (template [ ]
+     [(def: .public ( attributes media on_unsupported)
+        (-> Attributes Media (Maybe Content) Element)
+        (..tag  attributes
+               (|> on_unsupported
+                   (maybe.else (..text ""))
+                   (..and media))))]
+
+     [audio "audio"]
+     [video "video"]
+     )
+
+   (def: .public (picture attributes sources image)
+     (-> Attributes Source Image Element)
+     (..tag "picture" attributes (..and sources image)))
+
+   (def: .public (anchor href attributes content)
+     (-> URL Attributes Element Element)
+     (..tag "a" (list& ["href" href] attributes) content))
+
+   (def: .public label
+     (-> ID Input)
+     (|>> ["for"] list (..empty "label")))
+
+   (template [   ]
+     [(def: .public ( description attributes content)
+        (-> (Maybe Content) Attributes  )
+        (..tag  attributes
+               (case description
+                 (#.Some description)
+                 ($_ ..and
+                     (..tag  (list) description)
+                     content)
+                 
+                 #.None
+                 content)))]
+
+     [details "details" "summary" Element]
+     [field_set "fieldset" "legend" Input]
+     [figure "figure" "figcaption" Element]
+     )
+
+   (template [  ]
+     [(def: .public ( attributes content)
+        (-> Attributes (Maybe Content) )
+        (|> content
+            (maybe.else (..text ""))
+            (..tag  attributes)))]
+
+     [text_area "textarea" Input]
+     [iframe "iframe" Element]
+     )
+
+   (type: .public Phrase
+     (-> Attributes Content Element))
+
+   (template [ ]
+     [(def: .public 
+        Phrase
+        (..tag ))]
+
+     [abbrebiation "abbr"]
+     [block_quote "blockquote"]
+     [bold "b"]
+     [cite "cite"]
+     [code "code"]
+     [definition "dfn"]
+     [deleted "del"]
+     [emphasized "em"]
+     [h1 "h1"]
+     [h2 "h2"]
+     [h3 "h3"]
+     [h4 "h4"]
+     [h5 "h5"]
+     [h6 "h6"]
+     [inserted "ins"]
+     [italic "i"]
+     [keyboard "kbd"]
+     [marked "mark"]
+     [meter "meter"]
+     [pre "pre"]
+     [quote "q"]
+     [sample "samp"]
+     [struck "s"]
+     [small "small"]
+     [sub "sub"]
+     [super "sup"]
+     [strong "strong"]
+     [time "time"]
+     [underlined "u"]
+     [variable "var"]
+     )
+
+   (def: .public incorrect ..struck)
+
+   (def: (ruby_pronunciation pronunciation)
+     (-> Content (HTML Any))
+     (..tag "rt" (list)
+            ($_ ..and
+                (..tag "rp" (list) (..text "("))
+                pronunciation
+                (..tag "rp" (list) (..text ")")))))
+
+   (def: .public (ruby attributes content pronunciation)
+     (-> Attributes Content Content Element)
+     (..tag "ruby" attributes
+            ($_ ..and
+                content
+                (ruby_pronunciation pronunciation))))
+
+   (type: .public Composite
+     (-> Attributes Element Element))
+
+   (template [ ]
+     [(def: .public 
+        Composite
+        (..tag ))]
+
+     [article "article"]
+     [aside "aside"]
+     [dialog "dialog"]
+     [div "div"]
+     [footer "footer"]
+     [header "header"]
+     [main "main"]
+     [navigation "nav"]
+     [paragraph "p"]
+     [section "section"]
+     [span "span"]
+     )
+
+   (template [  ]
+     [(def: 
+        (->  (HTML Any))
+        (..tag  (list)))]
+
+     ["dt" term Content]
+     ["dd" description Element]
+     )
+
+   (def: .public (description_list attributes descriptions)
+     (-> Attributes (List [Content Element]) Element)
+     (case (list\each (function (_ [term description])
+                        ($_ ..and
+                            (..term term)
+                            (..description description)))
+                      descriptions)
+       #.End
+       (..empty "dl" attributes)
+       
+       (#.Item head tail)
+       (..tag "dl" attributes
+              (list\mix (function.flipped ..and) head tail))))
+
+   (def: .public p ..paragraph)
+
+   (template [   ]
+     [(def: .public 
+        (-> Attributes  )
+        (..tag ))]
+
+     [button "button" Element Input]
+     [item "li" Element Item]
+     [ordered_list "ol" Item Element]
+     [unordered_list "ul" Item Element]
+     [option "option" Content Option]
+     [option_group "optgroup" Option Option]
+     [data_list "datalist" Option Element]
+     [select "select" Option Input]
+     [address "address" Element Element]
+     [form "form" Input Element]
+     [data "data" Element Element]
+     [object "object" Parameter Element]
+     )
+
+   (template [   ]
+     [(def: .public 
+        (->  )
+        (..tag  (list)))]
+
+     [title "title" Content Meta]
+     [no_script "noscript" Content Meta]
+     [template "template" (HTML Any) (HTML Nothing)]
+     [table_header "th" Element Header]
+     [table_cell "td" Element Cell]
+     [head "head" Meta Head]
+     [body "body" Element Body]
+     )
+
+   (template [   ]
+     [(def: 
+        (->  )
+        (..tag  (list)))]
+
+     [table_row "tr" (HTML Any) Row]
+     [table_head "thead" Row HTML]
+     [table_body "tbody" Row HTML]
+     [table_foot "tfoot" Row HTML]
+     [columns_group "colgroup" Column HTML]
+     )
+
+   (def: .public (table attributes caption columns headers rows footer)
+     (-> Attributes (Maybe Content) (Maybe Column) Header (List Cell) (Maybe Cell) Element)
+     (let [head (..table_head (..table_row headers))
+           content (case (list\each table_row rows)
+                     #.End
+                     head
+
+                     (#.Item first rest)
+                     (..and head
+                            (..table_body
+                             (list\mix (function.flipped ..and) first rest))))
+           content (case footer
+                     #.None
+                     content
+                     
+                     (#.Some footer)
+                     (..and content
+                            (..table_foot (..table_row footer))))
+           content (case columns
+                     #.None
+                     content
+                     
+                     (#.Some columns)
+                     (..and (..columns_group columns)
+                            content))
+           content (case caption
+                     #.None
+                     content
+
+                     (#.Some caption)
+                     (..and (:as HTML caption)
+                            content))]
+       (..tag "table" attributes
+              content)))
+
+   (template [ ]
+     [(def: .public 
+        (-> Head Body Document)
+        (let [doc_type ]
+          (function (_ head body)
+            (|> (..tag "html" (list) (..and head body))
+                :representation
+                (format doc_type)
+                :abstraction))))]
+
+     [html/5    ""]
+     [html/4_01 (format "")]
+     [xhtml/1_0 (format "")]
+     [xhtml/1_1 (format "")]
+     )]
   )
diff --git a/stdlib/source/library/lux/data/format/markdown.lux b/stdlib/source/library/lux/data/format/markdown.lux
index da6a5d7c6..93ec06334 100644
--- a/stdlib/source/library/lux/data/format/markdown.lux
+++ b/stdlib/source/library/lux/data/format/markdown.lux
@@ -31,172 +31,170 @@
        (text.replaced "." "\.")
        (text.replaced "!" "\!")))
 
-(abstract: .public Span {} Any)
-(abstract: .public Block {} Any)
+(abstract: .public Span Any [])
+(abstract: .public Block Any [])
 
 (abstract: .public (Markdown brand)
-  {}
-  
   Text
 
-  (def: .public empty
-    Markdown
-    (:abstraction ""))
-
-  (def: .public text
-    (-> Text (Markdown Span))
-    (|>> ..safe :abstraction))
-
-  (def: blank_line
-    (format text.new_line text.new_line))
-
-  (template [ ]
-    [(def: .public ( content)
-       (-> Text (Markdown Block))
-       (:abstraction (format  " " (..safe content) ..blank_line)))]
-
-    [heading/1 "#"]
-    [heading/2 "##"]
-    [heading/3 "###"]
-    [heading/4 "####"]
-    [heading/5 "#####"]
-    [heading/6 "######"]
-    )
-
-  (def: (block content)
-    (-> Text (Markdown Block))
-    (:abstraction (format content ..blank_line)))
-
-  (def: .public paragraph
-    (-> (Markdown Span) (Markdown Block))
-    (|>> :representation ..block))
-
-  (def: .public break
-    (Markdown Span)
-    (:abstraction (format "  " text.new_line)))
-
-  (template [ ]
-    [(def: .public 
-       (-> (Markdown Span) (Markdown Span))
-       (|>> :representation
-            (text.enclosed [ ])
-            :abstraction))]
-
-    [bold "**"]
-    [italic "_"]
-    )
-
-  (def: (prefix with)
-    (-> Text (-> Text Text))
-    (|>> (text.all_split_by text.new_line)
-         (list\each (function (_ line)
-                      (if (text.empty? line)
-                        line
-                        (format with line))))
-         (text.interposed text.new_line)))
-
-  (def: indent
-    (-> Text Text)
-    (..prefix text.tab))
-
-  (def: .public quote
-    (-> (Markdown Block) (Markdown Block))
-    (|>> :representation
-         (..prefix "> ")
-         :abstraction))
-
-  (def: .public numbered_list
-    (-> (List [(Markdown Span) (Maybe (Markdown Block))])
-        (Markdown Block))
-    (|>> list.enumeration
-         (list\each (function (_ [idx [summary detail]])
-                      (format "1. " (:representation summary)
-                              (case detail
-                                (#.Some detail)
-                                (|> detail
-                                    :representation
-                                    ..indent
-                                    (text.enclosed [text.new_line text.new_line])
-                                    (format text.new_line))
-                                
-                                #.None
-                                ""))))
-         (text.interposed text.new_line)
-         ..block))
-
-  (def: .public bullet_list
-    (-> (List [(Markdown Span) (Maybe (Markdown Block))])
-        (Markdown Block))
-    (|>> (list\each (function (_ [summary detail])
-                      (format "* " (:representation summary)
-                              (case detail
-                                (#.Some detail)
-                                (|> detail
-                                    :representation
-                                    ..indent
-                                    (text.enclosed [text.new_line text.new_line])
-                                    (format text.new_line))
-                                
-                                #.None
-                                ""))))
-         (text.interposed text.new_line)
-         ..block))
-
-  (def: .public snippet
-    {#.doc "A snippet of code."}
-    (-> Text (Markdown Span))
-    (|>> (text.enclosed ["`` " " ``"]) :abstraction))
-
-  (def: .public generic_code
-    {#.doc "A (generic) block of code."}
-    (-> Text (Markdown Block))
-    (let [open (format "```" text.new_line)
-          close (format text.new_line "```")]
-      (|>> (text.enclosed [open close]) ..block)))
-
-  (def: .public (code language block)
-    {#.doc "A block of code of a specific language."}
-    (-> Text Text (Markdown Block))
-    (let [open (format "```" language text.new_line)
-          close (format text.new_line "```")]
-      (|> block
-          (text.enclosed [open close])
-          ..block)))
-
-  (def: .public (image description url)
-    (-> Text URL (Markdown Span))
-    (:abstraction (format "![" (..safe description) "](" url ")")))
-
-  (def: .public horizontal_rule
-    (Markdown Block)
-    (..block "___"))
-
-  (def: .public (link description url)
-    (-> (Markdown Span) URL (Markdown Span))
-    (:abstraction (format "[" (:representation description) "](" url ")")))
-
-  (type: .public Email
-    Text)
-
-  (template [ ]
-    [(def: .public 
-       (->  (Markdown Span))
-       (|>> (text.enclosed ["<" ">"]) :abstraction))]
-
-    [url URL]
-    [email Email]
-    )
-
-  (template [  ]
-    [(def: .public ( pre post)
-       (-> (Markdown ) (Markdown ) (Markdown ))
-       (:abstraction (format (:representation pre)  (:representation post))))]
-
-    [and Span " "]
-    [then Block ""]
-    )
-
-  (def: .public markdown
-    (All (_ a) (-> (Markdown a) Text))
-    (|>> :representation))
+  [(def: .public empty
+     Markdown
+     (:abstraction ""))
+
+   (def: .public text
+     (-> Text (Markdown Span))
+     (|>> ..safe :abstraction))
+
+   (def: blank_line
+     (format text.new_line text.new_line))
+
+   (template [ ]
+     [(def: .public ( content)
+        (-> Text (Markdown Block))
+        (:abstraction (format  " " (..safe content) ..blank_line)))]
+
+     [heading/1 "#"]
+     [heading/2 "##"]
+     [heading/3 "###"]
+     [heading/4 "####"]
+     [heading/5 "#####"]
+     [heading/6 "######"]
+     )
+
+   (def: (block content)
+     (-> Text (Markdown Block))
+     (:abstraction (format content ..blank_line)))
+
+   (def: .public paragraph
+     (-> (Markdown Span) (Markdown Block))
+     (|>> :representation ..block))
+
+   (def: .public break
+     (Markdown Span)
+     (:abstraction (format "  " text.new_line)))
+
+   (template [ ]
+     [(def: .public 
+        (-> (Markdown Span) (Markdown Span))
+        (|>> :representation
+             (text.enclosed [ ])
+             :abstraction))]
+
+     [bold "**"]
+     [italic "_"]
+     )
+
+   (def: (prefix with)
+     (-> Text (-> Text Text))
+     (|>> (text.all_split_by text.new_line)
+          (list\each (function (_ line)
+                       (if (text.empty? line)
+                         line
+                         (format with line))))
+          (text.interposed text.new_line)))
+
+   (def: indent
+     (-> Text Text)
+     (..prefix text.tab))
+
+   (def: .public quote
+     (-> (Markdown Block) (Markdown Block))
+     (|>> :representation
+          (..prefix "> ")
+          :abstraction))
+
+   (def: .public numbered_list
+     (-> (List [(Markdown Span) (Maybe (Markdown Block))])
+         (Markdown Block))
+     (|>> list.enumeration
+          (list\each (function (_ [idx [summary detail]])
+                       (format "1. " (:representation summary)
+                               (case detail
+                                 (#.Some detail)
+                                 (|> detail
+                                     :representation
+                                     ..indent
+                                     (text.enclosed [text.new_line text.new_line])
+                                     (format text.new_line))
+                                 
+                                 #.None
+                                 ""))))
+          (text.interposed text.new_line)
+          ..block))
+
+   (def: .public bullet_list
+     (-> (List [(Markdown Span) (Maybe (Markdown Block))])
+         (Markdown Block))
+     (|>> (list\each (function (_ [summary detail])
+                       (format "* " (:representation summary)
+                               (case detail
+                                 (#.Some detail)
+                                 (|> detail
+                                     :representation
+                                     ..indent
+                                     (text.enclosed [text.new_line text.new_line])
+                                     (format text.new_line))
+                                 
+                                 #.None
+                                 ""))))
+          (text.interposed text.new_line)
+          ..block))
+
+   (def: .public snippet
+     {#.doc "A snippet of code."}
+     (-> Text (Markdown Span))
+     (|>> (text.enclosed ["`` " " ``"]) :abstraction))
+
+   (def: .public generic_code
+     {#.doc "A (generic) block of code."}
+     (-> Text (Markdown Block))
+     (let [open (format "```" text.new_line)
+           close (format text.new_line "```")]
+       (|>> (text.enclosed [open close]) ..block)))
+
+   (def: .public (code language block)
+     {#.doc "A block of code of a specific language."}
+     (-> Text Text (Markdown Block))
+     (let [open (format "```" language text.new_line)
+           close (format text.new_line "```")]
+       (|> block
+           (text.enclosed [open close])
+           ..block)))
+
+   (def: .public (image description url)
+     (-> Text URL (Markdown Span))
+     (:abstraction (format "![" (..safe description) "](" url ")")))
+
+   (def: .public horizontal_rule
+     (Markdown Block)
+     (..block "___"))
+
+   (def: .public (link description url)
+     (-> (Markdown Span) URL (Markdown Span))
+     (:abstraction (format "[" (:representation description) "](" url ")")))
+
+   (type: .public Email
+     Text)
+
+   (template [ ]
+     [(def: .public 
+        (->  (Markdown Span))
+        (|>> (text.enclosed ["<" ">"]) :abstraction))]
+
+     [url URL]
+     [email Email]
+     )
+
+   (template [  ]
+     [(def: .public ( pre post)
+        (-> (Markdown ) (Markdown ) (Markdown ))
+        (:abstraction (format (:representation pre)  (:representation post))))]
+
+     [and Span " "]
+     [then Block ""]
+     )
+
+   (def: .public markdown
+     (All (_ a) (-> (Markdown a) Text))
+     (|>> :representation))]
   )
diff --git a/stdlib/source/library/lux/data/format/tar.lux b/stdlib/source/library/lux/data/format/tar.lux
index bb8228146..7a5d8106b 100644
--- a/stdlib/source/library/lux/data/format/tar.lux
+++ b/stdlib/source/library/lux/data/format/tar.lux
@@ -71,35 +71,33 @@
       ["Maximum" (%.nat (-- ))]))
 
    (abstract: .public 
-     {}
-     
      Nat
 
-     (def: .public ( value)
-       (-> Nat (Try ))
-       (if (n.<  value)
-         (#try.Success (:abstraction value))
-         (exception.except  [value])))
-
-     (def: .public 
-       (->  Nat)
-       (|>> :representation))
-
-     (def: 
-       (Writer )
-       (let [suffix 
-             padded_size (n.+ (text.size suffix) )]
-         (|>> :representation
-              (\ n.octal encoded)
-              (..octal_padding )
-              (text.suffix suffix)
-              (\ utf8.codec encoded)
-              (format.segment padded_size))))
-
-     (def: 
-       (-> Nat )
-       (|>> (n.% )
-            :abstraction))
+     [(def: .public ( value)
+        (-> Nat (Try ))
+        (if (n.<  value)
+          (#try.Success (:abstraction value))
+          (exception.except  [value])))
+
+      (def: .public 
+        (->  Nat)
+        (|>> :representation))
+
+      (def: 
+        (Writer )
+        (let [suffix 
+              padded_size (n.+ (text.size suffix) )]
+          (|>> :representation
+               (\ n.octal encoded)
+               (..octal_padding )
+               (text.suffix suffix)
+               (\ utf8.codec encoded)
+               (format.segment padded_size))))
+
+      (def: 
+        (-> Nat )
+        (|>> (n.% )
+             :abstraction))]
      )]
 
   [not_a_small_number small_limit ..small_size
@@ -156,59 +154,57 @@
        (..big value)))))
 
 (abstract: Checksum
-  {}
-  
   Text
 
-  (def: from_checksum
-    (-> Checksum Text)
-    (|>> :representation))
-
-  (def: dummy_checksum
-    Checksum
-    (:abstraction "        "))
-
-  (def: checksum_suffix
-    (format ..blank ..null))
-
-  (def: checksum
-    (-> Binary Nat)
-    (binary.aggregate n.+ 0))
-
-  (def: checksum_checksum
-    (|> ..dummy_checksum
-        :representation
-        (\ utf8.codec encoded)
-        ..checksum))
-
-  (def: checksum_code
-    (-> Binary Checksum)
-    (|>> ..checksum
-         ..as_small
-         ..from_small
-         (\ n.octal encoded)
-         (..octal_padding ..small_size)
-         (text.suffix ..checksum_suffix)
-         :abstraction))
-
-  (def: checksum_writer
-    (Writer Checksum)
-    (let [padded_size (n.+ (text.size ..checksum_suffix)
-                           ..small_size)]
-      (|>> :representation
-           (\ utf8.codec encoded)
-           (format.segment padded_size))))
-
-  (def: checksum_parser
-    (Parser [Nat Checksum])
-    (do <>.monad
-      [ascii (.segment ..small_size)
-       digits (<>.lifted (\ utf8.codec decoded ascii))
-       _ ..small_suffix
-       value (<>.lifted
-              (\ n.octal decoded digits))]
-      (in [value
-           (:abstraction (format digits ..checksum_suffix))])))
+  [(def: from_checksum
+     (-> Checksum Text)
+     (|>> :representation))
+
+   (def: dummy_checksum
+     Checksum
+     (:abstraction "        "))
+
+   (def: checksum_suffix
+     (format ..blank ..null))
+
+   (def: checksum
+     (-> Binary Nat)
+     (binary.aggregate n.+ 0))
+
+   (def: checksum_checksum
+     (|> ..dummy_checksum
+         :representation
+         (\ utf8.codec encoded)
+         ..checksum))
+
+   (def: checksum_code
+     (-> Binary Checksum)
+     (|>> ..checksum
+          ..as_small
+          ..from_small
+          (\ n.octal encoded)
+          (..octal_padding ..small_size)
+          (text.suffix ..checksum_suffix)
+          :abstraction))
+
+   (def: checksum_writer
+     (Writer Checksum)
+     (let [padded_size (n.+ (text.size ..checksum_suffix)
+                            ..small_size)]
+       (|>> :representation
+            (\ utf8.codec encoded)
+            (format.segment padded_size))))
+
+   (def: checksum_parser
+     (Parser [Nat Checksum])
+     (do <>.monad
+       [ascii (.segment ..small_size)
+        digits (<>.lifted (\ utf8.codec decoded ascii))
+        _ ..small_suffix
+        value (<>.lifted
+               (\ n.octal decoded digits))]
+       (in [value
+            (:abstraction (format digits ..checksum_suffix))])))]
   )
 
 (def: last_ascii
@@ -248,57 +244,55 @@
 
 (template [        ]
   [(abstract: .public 
-     {}
-     
      
 
-     (exception: .public ( {value Text})
-       (exception.report
-        ["Value" (%.text value)]
-        ["Size" (%.nat (text.size value))]
-        ["Maximum" (%.nat )]))
-
-     (def: .public ( value)
-       (->  (Try ))
-       (if (..ascii? value)
-         (if (|> value
-                 (\ utf8.codec encoded)
-                 binary.size
-                 (n.> ))
-           (exception.except  [value])
-           (#try.Success (:abstraction value)))
-         (exception.except ..not_ascii [value])))
-
-     (def: .public 
-       (->  )
-       (|>> :representation))
-
-     (def: 
-       (Writer )
-       (let [suffix ..null
-             padded_size (n.+ (text.size suffix) )]
-         (|>> :representation
-              (text.suffix suffix)
-              (\ utf8.codec encoded)
-              (format.segment padded_size))))
-
-     (def: 
-       (Parser )
-       (do <>.monad
-         [string (.segment )
-          end .bits/8
-          .let [expected (`` (char (~~ (static ..null))))]
-          _ (<>.assertion (exception.error ..wrong_character [expected end])
-                          (n.= expected end))]
-         (<>.lifted
-          (do [! try.monad]
-            [ascii (..un_padded string)
-             text (\ utf8.codec decoded ascii)]
-            ( text)))))
-
-     (def: .public 
-       
-       (try.trusted ( "")))
+     [(exception: .public ( {value Text})
+        (exception.report
+         ["Value" (%.text value)]
+         ["Size" (%.nat (text.size value))]
+         ["Maximum" (%.nat )]))
+
+      (def: .public ( value)
+        (->  (Try ))
+        (if (..ascii? value)
+          (if (|> value
+                  (\ utf8.codec encoded)
+                  binary.size
+                  (n.> ))
+            (exception.except  [value])
+            (#try.Success (:abstraction value)))
+          (exception.except ..not_ascii [value])))
+
+      (def: .public 
+        (->  )
+        (|>> :representation))
+
+      (def: 
+        (Writer )
+        (let [suffix ..null
+              padded_size (n.+ (text.size suffix) )]
+          (|>> :representation
+               (text.suffix suffix)
+               (\ utf8.codec encoded)
+               (format.segment padded_size))))
+
+      (def: 
+        (Parser )
+        (do <>.monad
+          [string (.segment )
+           end .bits/8
+           .let [expected (`` (char (~~ (static ..null))))]
+           _ (<>.assertion (exception.error ..wrong_character [expected end])
+                           (n.= expected end))]
+          (<>.lifted
+           (do [! try.monad]
+             [ascii (..un_padded string)
+              text (\ utf8.codec decoded ascii)]
+             ( text)))))
+
+      (def: .public 
+        
+        (try.trusted ( "")))]
      )]
 
   [Name Text      ..name_size name_is_too_long name from_name name_writer name_parser anonymous]
@@ -308,35 +302,33 @@
 (def: magic_size Size 7)
 
 (abstract: Magic
-  {}
-  
   Text
 
-  (def: ustar (:abstraction "ustar  "))
-
-  (def: from_magic
-    (-> Magic Text)
-    (|>> :representation))
-
-  (def: magic_writer
-    (Writer Magic)
-    (let [padded_size (n.+ (text.size ..null)
-                           ..magic_size)]
-      (|>> :representation
-           (\ utf8.codec encoded)
-           (format.segment padded_size))))
-
-  (def: magic_parser
-    (Parser Magic)
-    (do <>.monad
-      [string (.segment ..magic_size)
-       end .bits/8
-       .let [expected (`` (char (~~ (static ..null))))]
-       _ (<>.assertion (exception.error ..wrong_character [expected end])
-                       (n.= expected end))]
-      (<>.lifted
-       (\ try.monad each (|>> :abstraction)
-          (\ utf8.codec decoded string)))))
+  [(def: ustar (:abstraction "ustar  "))
+
+   (def: from_magic
+     (-> Magic Text)
+     (|>> :representation))
+
+   (def: magic_writer
+     (Writer Magic)
+     (let [padded_size (n.+ (text.size ..null)
+                            ..magic_size)]
+       (|>> :representation
+            (\ utf8.codec encoded)
+            (format.segment padded_size))))
+
+   (def: magic_parser
+     (Parser Magic)
+     (do <>.monad
+       [string (.segment ..magic_size)
+        end .bits/8
+        .let [expected (`` (char (~~ (static ..null))))]
+        _ (<>.assertion (exception.error ..wrong_character [expected end])
+                        (n.= expected end))]
+       (<>.lifted
+        (\ try.monad each (|>> :abstraction)
+           (\ utf8.codec decoded string)))))]
   )
 
 (def: block_size Size 512)
@@ -396,137 +388,133 @@
       (..small_number ..device_size)))
 
 (abstract: Link_Flag
-  {}
-  
   Char
 
-  (def: link_flag
-    (-> Link_Flag Char)
-    (|>> :representation))
-
-  (def: link_flag_writer
-    (Writer Link_Flag)
-    (|>> :representation
-         format.bits/8))
-
-  (with_expansions [ (as_is [0 old_normal]
-                                     [(char "0") normal]
-                                     [(char "1") link]
-                                     [(char "2") symbolic_link]
-                                     [(char "3") character]
-                                     [(char "4") block]
-                                     [(char "5") directory]
-                                     [(char "6") fifo]
-                                     [(char "7") contiguous])]
-    (template [ ]
-      [(def: 
-         Link_Flag
-         (:abstraction ))]
-
-      
-      )
-
-    (exception: .public (invalid_link_flag {value Nat})
-      (exception.report
-       ["Value" (%.nat value)]))
-
-    (def: link_flag_parser
-      (Parser Link_Flag)
-      (do <>.monad
-        [linkflag .bits/8]
-        (case (.nat linkflag)
-          (^template [ ]
-            [(^ )
-             (in )])
-          ()
-
-          _
-          (<>.lifted
-           (exception.except ..invalid_link_flag [(.nat linkflag)]))))))
+  [(def: link_flag
+     (-> Link_Flag Char)
+     (|>> :representation))
+
+   (def: link_flag_writer
+     (Writer Link_Flag)
+     (|>> :representation
+          format.bits/8))
+
+   (with_expansions [ (as_is [0 old_normal]
+                                      [(char "0") normal]
+                                      [(char "1") link]
+                                      [(char "2") symbolic_link]
+                                      [(char "3") character]
+                                      [(char "4") block]
+                                      [(char "5") directory]
+                                      [(char "6") fifo]
+                                      [(char "7") contiguous])]
+     (template [ ]
+       [(def: 
+          Link_Flag
+          (:abstraction ))]
+
+       
+       )
+
+     (exception: .public (invalid_link_flag {value Nat})
+       (exception.report
+        ["Value" (%.nat value)]))
+
+     (def: link_flag_parser
+       (Parser Link_Flag)
+       (do <>.monad
+         [linkflag .bits/8]
+         (case (.nat linkflag)
+           (^template [ ]
+             [(^ )
+              (in )])
+           ()
+
+           _
+           (<>.lifted
+            (exception.except ..invalid_link_flag [(.nat linkflag)]))))))]
   )
 
 (abstract: .public Mode
-  {}
-  
   Nat
 
-  (def: .public mode
-    (-> Mode Nat)
-    (|>> :representation))
-
-  (def: .public (and left right)
-    (-> Mode Mode Mode)
-    (:abstraction
-     (i64.or (:representation left)
-             (:representation right))))
-
-  (def: mode_writer
-    (Writer Mode)
-    (|>> :representation
-         ..small
-         try.trusted
-         ..small_writer))
-
-  (exception: .public (invalid_mode {value Nat})
-    (exception.report
-     ["Value" (%.nat value)]))
-
-  (with_expansions [ (as_is ["0000" none]
-                                     
-                                     ["0001" execute_by_other]
-                                     ["0002" write_by_other]
-                                     ["0004" read_by_other]
-
-                                     ["0010" execute_by_group]
-                                     ["0020" write_by_group]
-                                     ["0040" read_by_group]
-
-                                     ["0100" execute_by_owner]
-                                     ["0200" write_by_owner]
-                                     ["0400" read_by_owner]
-
-                                     ["1000" save_text]
-                                     ["2000" set_group_id_on_execution]
-                                     ["4000" set_user_id_on_execution])]
-    (template [ ]
-      [(def: .public 
-         Mode
-         (:abstraction (number.oct )))]
-
-      
-      )
-
-    (def: maximum_mode
-      Mode
-      ($_ and
-          ..none
-          
-          ..execute_by_other
-          ..write_by_other
-          ..read_by_other
-
-          ..execute_by_group
-          ..write_by_group
-          ..read_by_group
-
-          ..execute_by_owner
-          ..write_by_owner
-          ..read_by_owner
-
-          ..save_text
-          ..set_group_id_on_execution
-          ..set_user_id_on_execution
-          ))
-
-    (def: mode_parser
-      (Parser Mode)
-      (do [! <>.monad]
-        [value (\ ! each ..from_small ..small_parser)]
-        (if (n.> (:representation ..maximum_mode)
-                 value)
-          (<>.lifted
-           (exception.except ..invalid_mode [value]))
-          (in (:abstraction value))))))
+  [(def: .public mode
+     (-> Mode Nat)
+     (|>> :representation))
+
+   (def: .public (and left right)
+     (-> Mode Mode Mode)
+     (:abstraction
+      (i64.or (:representation left)
+              (:representation right))))
+
+   (def: mode_writer
+     (Writer Mode)
+     (|>> :representation
+          ..small
+          try.trusted
+          ..small_writer))
+
+   (exception: .public (invalid_mode {value Nat})
+     (exception.report
+      ["Value" (%.nat value)]))
+
+   (with_expansions [ (as_is ["0000" none]
+                                      
+                                      ["0001" execute_by_other]
+                                      ["0002" write_by_other]
+                                      ["0004" read_by_other]
+
+                                      ["0010" execute_by_group]
+                                      ["0020" write_by_group]
+                                      ["0040" read_by_group]
+
+                                      ["0100" execute_by_owner]
+                                      ["0200" write_by_owner]
+                                      ["0400" read_by_owner]
+
+                                      ["1000" save_text]
+                                      ["2000" set_group_id_on_execution]
+                                      ["4000" set_user_id_on_execution])]
+     (template [ ]
+       [(def: .public 
+          Mode
+          (:abstraction (number.oct )))]
+
+       
+       )
+
+     (def: maximum_mode
+       Mode
+       ($_ and
+           ..none
+           
+           ..execute_by_other
+           ..write_by_other
+           ..read_by_other
+
+           ..execute_by_group
+           ..write_by_group
+           ..read_by_group
+
+           ..execute_by_owner
+           ..write_by_owner
+           ..read_by_owner
+
+           ..save_text
+           ..set_group_id_on_execution
+           ..set_user_id_on_execution
+           ))
+
+     (def: mode_parser
+       (Parser Mode)
+       (do [! <>.monad]
+         [value (\ ! each ..from_small ..small_parser)]
+         (if (n.> (:representation ..maximum_mode)
+                  value)
+           (<>.lifted
+            (exception.except ..invalid_mode [value]))
+           (in (:abstraction value))))))]
   )
 
 (def: maximum_content_size
@@ -536,23 +524,21 @@
       (list\mix n.* 1)))
 
 (abstract: .public Content
-  {}
-  
   [Big Binary]
 
-  (def: .public (content content)
-    (-> Binary (Try Content))
-    (do try.monad
-      [size (..big (binary.size content))]
-      (in (:abstraction [size content]))))
+  [(def: .public (content content)
+     (-> Binary (Try Content))
+     (do try.monad
+       [size (..big (binary.size content))]
+       (in (:abstraction [size content]))))
 
-  (def: from_content
-    (-> Content [Big Binary])
-    (|>> :representation))
+   (def: from_content
+     (-> Content [Big Binary])
+     (|>> :representation))
 
-  (def: .public data
-    (-> Content Binary)
-    (|>> :representation product.right))
+   (def: .public data
+     (-> Content Binary)
+     (|>> :representation product.right))]
   )
 
 (type: .public ID
diff --git a/stdlib/source/library/lux/data/text/buffer.lux b/stdlib/source/library/lux/data/text/buffer.lux
index 828a4772e..af3341930 100644
--- a/stdlib/source/library/lux/data/text/buffer.lux
+++ b/stdlib/source/library/lux/data/text/buffer.lux
@@ -48,8 +48,6 @@
            (as_is))))
 
 (`` (abstract: .public Buffer
-      {}
-
       (for {@.old [Nat (-> java/lang/StringBuilder java/lang/StringBuilder)]
             @.jvm [Nat (-> java/lang/StringBuilder java/lang/StringBuilder)]
             @.js [Nat (-> (JS_Array Text) (JS_Array Text))]
@@ -57,79 +55,79 @@
            ... default
            (Row Text))
 
-      (def: .public empty
-        Buffer
-        (:abstraction (with_expansions [ [0 function.identity]]
-                        (for {@.old 
-                              @.jvm 
-                              @.js [0 function.identity]
-                              @.lua [0 function.identity]}
-                             ... default
-                             row.empty))))
+      [(def: .public empty
+         Buffer
+         (:abstraction (with_expansions [ [0 function.identity]]
+                         (for {@.old 
+                               @.jvm 
+                               @.js [0 function.identity]
+                               @.lua [0 function.identity]}
+                              ... default
+                              row.empty))))
 
-      (def: .public (then chunk buffer)
-        (-> Text Buffer Buffer)
-        (with_expansions [ (let [[capacity transform] (:representation buffer)
-                                      then! (: (-> Text java/lang/StringBuilder java/lang/StringBuilder)
-                                               (function (_ chunk builder)
-                                                 (exec
-                                                   (java/lang/Appendable::append (:as java/lang/CharSequence chunk)
-                                                                                 builder)
-                                                   builder)))]
-                                  (:abstraction [(n.+ (//.size chunk) capacity)
-                                                 (|>> transform (then! chunk))]))]
-          (for {@.old 
-                @.jvm 
-                @.js (let [[capacity transform] (:representation buffer)
-                           then! (: (-> (JS_Array Text) (JS_Array Text))
-                                    (function (_ array)
-                                      (exec
-                                        (JS_Array::push [chunk] array)
-                                        array)))]
-                       (:abstraction [(n.+ (//.size chunk) capacity)
-                                      (|>> transform then!)]))
-                @.lua (let [[capacity transform] (:representation buffer)
-                            then! (: (-> (array.Array Text) (array.Array Text))
+       (def: .public (then chunk buffer)
+         (-> Text Buffer Buffer)
+         (with_expansions [ (let [[capacity transform] (:representation buffer)
+                                       then! (: (-> Text java/lang/StringBuilder java/lang/StringBuilder)
+                                                (function (_ chunk builder)
+                                                  (exec
+                                                    (java/lang/Appendable::append (:as java/lang/CharSequence chunk)
+                                                                                  builder)
+                                                    builder)))]
+                                   (:abstraction [(n.+ (//.size chunk) capacity)
+                                                  (|>> transform (then! chunk))]))]
+           (for {@.old 
+                 @.jvm 
+                 @.js (let [[capacity transform] (:representation buffer)
+                            then! (: (-> (JS_Array Text) (JS_Array Text))
                                      (function (_ array)
                                        (exec
-                                         (table/insert [array chunk])
+                                         (JS_Array::push [chunk] array)
                                          array)))]
                         (:abstraction [(n.+ (//.size chunk) capacity)
-                                       (|>> transform then!)]))}
-               ... default
-               (|> buffer :representation (row.suffix chunk) :abstraction))))
+                                       (|>> transform then!)]))
+                 @.lua (let [[capacity transform] (:representation buffer)
+                             then! (: (-> (array.Array Text) (array.Array Text))
+                                      (function (_ array)
+                                        (exec
+                                          (table/insert [array chunk])
+                                          array)))]
+                         (:abstraction [(n.+ (//.size chunk) capacity)
+                                        (|>> transform then!)]))}
+                ... default
+                (|> buffer :representation (row.suffix chunk) :abstraction))))
 
-      (def: .public size
-        (-> Buffer Nat)
-        (with_expansions [ (|>> :representation product.left)]
-          (for {@.old 
-                @.jvm 
-                @.js 
-                @.lua }
-               ... default
-               (|>> :representation
-                    (row\mix (function (_ chunk total)
-                               (n.+ (//.size chunk) total))
-                             0)))))
+       (def: .public size
+         (-> Buffer Nat)
+         (with_expansions [ (|>> :representation product.left)]
+           (for {@.old 
+                 @.jvm 
+                 @.js 
+                 @.lua }
+                ... default
+                (|>> :representation
+                     (row\mix (function (_ chunk total)
+                                (n.+ (//.size chunk) total))
+                              0)))))
 
-      (def: .public (text buffer)
-        (-> Buffer Text)
-        (with_expansions [ (let [[capacity transform] (:representation buffer)]
-                                  (|> (java/lang/StringBuilder::new (.int capacity))
-                                      transform
-                                      java/lang/StringBuilder::toString))]
-          (for {@.old 
-                @.jvm 
-                @.js (let [[capacity transform] (:representation buffer)]
-                       (|> (array.empty 0)
-                           (:as (JS_Array Text))
-                           transform
-                           (JS_Array::join [""])))
-                @.lua (let [[capacity transform] (:representation buffer)]
-                        (table/concat [(transform (array.empty 0)) ""]))}
-               ... default
-               (row\mix (function (_ chunk total)
-                          (format total chunk))
-                        ""
-                        (:representation buffer)))))
+       (def: .public (text buffer)
+         (-> Buffer Text)
+         (with_expansions [ (let [[capacity transform] (:representation buffer)]
+                                   (|> (java/lang/StringBuilder::new (.int capacity))
+                                       transform
+                                       java/lang/StringBuilder::toString))]
+           (for {@.old 
+                 @.jvm 
+                 @.js (let [[capacity transform] (:representation buffer)]
+                        (|> (array.empty 0)
+                            (:as (JS_Array Text))
+                            transform
+                            (JS_Array::join [""])))
+                 @.lua (let [[capacity transform] (:representation buffer)]
+                         (table/concat [(transform (array.empty 0)) ""]))}
+                ... default
+                (row\mix (function (_ chunk total)
+                           (format total chunk))
+                         ""
+                         (:representation buffer)))))]
       ))
diff --git a/stdlib/source/library/lux/data/text/encoding.lux b/stdlib/source/library/lux/data/text/encoding.lux
index 952c285f0..3b6dff526 100644
--- a/stdlib/source/library/lux/data/text/encoding.lux
+++ b/stdlib/source/library/lux/data/text/encoding.lux
@@ -8,161 +8,159 @@
 
 ... https://en.wikipedia.org/wiki/Character_encoding#Common_character_encodings
 (abstract: .public Encoding
-  {}
-  
   Text
 
-  (template [ ]
-    [(`` (def: .public 
-           Encoding
-           (:abstraction )))]
+  [(template [ ]
+     [(`` (def: .public 
+            Encoding
+            (:abstraction )))]
 
-    [ascii "ASCII"]
+     [ascii "ASCII"]
 
-    [ibm_037 "IBM037"]
-    [ibm_273 "IBM273"]
-    [ibm_277 "IBM277"]
-    [ibm_278 "IBM278"]
-    [ibm_280 "IBM280"]
-    [ibm_284 "IBM284"]
-    [ibm_285 "IBM285"]
-    [ibm_290 "IBM290"]
-    [ibm_297 "IBM297"]
-    [ibm_300 "IBM300"]
-    [ibm_420 "IBM420"]
-    [ibm_424 "IBM424"]
-    [ibm_437 "IBM437"]
-    [ibm_500 "IBM500"]
-    [ibm_737 "IBM737"]
-    [ibm_775 "IBM775"]
-    [ibm_833 "IBM833"]
-    [ibm_834 "IBM834"]
-    [ibm_838 "IBM-Thai"]
-    [ibm_850 "IBM850"]
-    [ibm_852 "IBM852"]
-    [ibm_855 "IBM855"]
-    [ibm_856 "IBM856"]
-    [ibm_857 "IBM857"]
-    [ibm_858 "IBM00858"]
-    [ibm_860 "IBM860"]
-    [ibm_861 "IBM861"]
-    [ibm_862 "IBM862"]
-    [ibm_863 "IBM863"]
-    [ibm_864 "IBM864"]
-    [ibm_865 "IBM865"]
-    [ibm_866 "IBM866"]
-    [ibm_868 "IBM868"]
-    [ibm_869 "IBM869"]
-    [ibm_870 "IBM870"]
-    [ibm_871 "IBM871"]
-    [ibm_874 "IBM874"]
-    [ibm_875 "IBM875"]
-    [ibm_918 "IBM918"]
-    [ibm_921 "IBM921"]
-    [ibm_922 "IBM922"]
-    [ibm_930 "IBM930"]
-    [ibm_933 "IBM933"]
-    [ibm_935 "IBM935"]
-    [ibm_937 "IBM937"]
-    [ibm_939 "IBM939"]
-    [ibm_942 "IBM942"]
-    [ibm_942c "IBM942C"]
-    [ibm_943 "IBM943"]
-    [ibm_943c "IBM943C"]
-    [ibm_948 "IBM948"]
-    [ibm_949 "IBM949"]
-    [ibm_949c "IBM949C"]
-    [ibm_950 "IBM950"]
-    [ibm_964 "IBM964"]
-    [ibm_970 "IBM970"]
-    [ibm_1006 "IBM1006"]
-    [ibm_1025 "IBM1025"]
-    [ibm_1026 "IBM1026"]
-    [ibm_1046 "IBM1046"]
-    [ibm_1047 "IBM1047"]
-    [ibm_1097 "IBM1097"]
-    [ibm_1098 "IBM1098"]
-    [ibm_1112 "IBM1112"]
-    [ibm_1122 "IBM1122"]
-    [ibm_1123 "IBM1123"]
-    [ibm_1124 "IBM1124"]
-    [ibm_1140 "IBM01140"]
-    [ibm_1141 "IBM01141"]
-    [ibm_1142 "IBM01142"]
-    [ibm_1143 "IBM01143"]
-    [ibm_1144 "IBM01144"]
-    [ibm_1145 "IBM01145"]
-    [ibm_1146 "IBM01146"]
-    [ibm_1147 "IBM01147"]
-    [ibm_1148 "IBM01148"]
-    [ibm_1149 "IBM01149"]
-    [ibm_1166 "IBM1166"]
-    [ibm_1364 "IBM1364"]
-    [ibm_1381 "IBM1381"]
-    [ibm_1383 "IBM1383"]
-    [ibm_33722 "IBM33722"]
-    
-    [iso_2022_cn "ISO-2022-CN"]
-    [iso2022_cn_cns "ISO2022-CN-CNS"]
-    [iso2022_cn_gb "ISO2022-CN-GB"]
-    [iso_2022_jp "ISO-2022-JP"]
-    [iso_2022_jp_2 "ISO-2022-JP-2"]
-    [iso_2022_kr "ISO-2022-KR"]
-    [iso_8859_1 "ISO-8859-1"]
-    [iso_8859_2 "ISO-8859-2"]
-    [iso_8859_3 "ISO-8859-3"]
-    [iso_8859_4 "ISO-8859-4"]
-    [iso_8859_5 "ISO-8859-5"]
-    [iso_8859_6 "ISO-8859-6"]
-    [iso_8859_7 "ISO-8859-7"]
-    [iso_8859_8 "ISO-8859-8"]
-    [iso_8859_9 "ISO-8859-9"]
-    [iso_8859_11 "iso-8859-11"]
-    [iso_8859_13 "ISO-8859-13"]
-    [iso_8859_15 "ISO-8859-15"]
+     [ibm_037 "IBM037"]
+     [ibm_273 "IBM273"]
+     [ibm_277 "IBM277"]
+     [ibm_278 "IBM278"]
+     [ibm_280 "IBM280"]
+     [ibm_284 "IBM284"]
+     [ibm_285 "IBM285"]
+     [ibm_290 "IBM290"]
+     [ibm_297 "IBM297"]
+     [ibm_300 "IBM300"]
+     [ibm_420 "IBM420"]
+     [ibm_424 "IBM424"]
+     [ibm_437 "IBM437"]
+     [ibm_500 "IBM500"]
+     [ibm_737 "IBM737"]
+     [ibm_775 "IBM775"]
+     [ibm_833 "IBM833"]
+     [ibm_834 "IBM834"]
+     [ibm_838 "IBM-Thai"]
+     [ibm_850 "IBM850"]
+     [ibm_852 "IBM852"]
+     [ibm_855 "IBM855"]
+     [ibm_856 "IBM856"]
+     [ibm_857 "IBM857"]
+     [ibm_858 "IBM00858"]
+     [ibm_860 "IBM860"]
+     [ibm_861 "IBM861"]
+     [ibm_862 "IBM862"]
+     [ibm_863 "IBM863"]
+     [ibm_864 "IBM864"]
+     [ibm_865 "IBM865"]
+     [ibm_866 "IBM866"]
+     [ibm_868 "IBM868"]
+     [ibm_869 "IBM869"]
+     [ibm_870 "IBM870"]
+     [ibm_871 "IBM871"]
+     [ibm_874 "IBM874"]
+     [ibm_875 "IBM875"]
+     [ibm_918 "IBM918"]
+     [ibm_921 "IBM921"]
+     [ibm_922 "IBM922"]
+     [ibm_930 "IBM930"]
+     [ibm_933 "IBM933"]
+     [ibm_935 "IBM935"]
+     [ibm_937 "IBM937"]
+     [ibm_939 "IBM939"]
+     [ibm_942 "IBM942"]
+     [ibm_942c "IBM942C"]
+     [ibm_943 "IBM943"]
+     [ibm_943c "IBM943C"]
+     [ibm_948 "IBM948"]
+     [ibm_949 "IBM949"]
+     [ibm_949c "IBM949C"]
+     [ibm_950 "IBM950"]
+     [ibm_964 "IBM964"]
+     [ibm_970 "IBM970"]
+     [ibm_1006 "IBM1006"]
+     [ibm_1025 "IBM1025"]
+     [ibm_1026 "IBM1026"]
+     [ibm_1046 "IBM1046"]
+     [ibm_1047 "IBM1047"]
+     [ibm_1097 "IBM1097"]
+     [ibm_1098 "IBM1098"]
+     [ibm_1112 "IBM1112"]
+     [ibm_1122 "IBM1122"]
+     [ibm_1123 "IBM1123"]
+     [ibm_1124 "IBM1124"]
+     [ibm_1140 "IBM01140"]
+     [ibm_1141 "IBM01141"]
+     [ibm_1142 "IBM01142"]
+     [ibm_1143 "IBM01143"]
+     [ibm_1144 "IBM01144"]
+     [ibm_1145 "IBM01145"]
+     [ibm_1146 "IBM01146"]
+     [ibm_1147 "IBM01147"]
+     [ibm_1148 "IBM01148"]
+     [ibm_1149 "IBM01149"]
+     [ibm_1166 "IBM1166"]
+     [ibm_1364 "IBM1364"]
+     [ibm_1381 "IBM1381"]
+     [ibm_1383 "IBM1383"]
+     [ibm_33722 "IBM33722"]
+     
+     [iso_2022_cn "ISO-2022-CN"]
+     [iso2022_cn_cns "ISO2022-CN-CNS"]
+     [iso2022_cn_gb "ISO2022-CN-GB"]
+     [iso_2022_jp "ISO-2022-JP"]
+     [iso_2022_jp_2 "ISO-2022-JP-2"]
+     [iso_2022_kr "ISO-2022-KR"]
+     [iso_8859_1 "ISO-8859-1"]
+     [iso_8859_2 "ISO-8859-2"]
+     [iso_8859_3 "ISO-8859-3"]
+     [iso_8859_4 "ISO-8859-4"]
+     [iso_8859_5 "ISO-8859-5"]
+     [iso_8859_6 "ISO-8859-6"]
+     [iso_8859_7 "ISO-8859-7"]
+     [iso_8859_8 "ISO-8859-8"]
+     [iso_8859_9 "ISO-8859-9"]
+     [iso_8859_11 "iso-8859-11"]
+     [iso_8859_13 "ISO-8859-13"]
+     [iso_8859_15 "ISO-8859-15"]
 
-    [mac_arabic "MacArabic"]
-    [mac_central_europe "MacCentralEurope"]
-    [mac_croatian "MacCroatian"]
-    [mac_cyrillic "MacCyrillic"]
-    [mac_dingbat "MacDingbat"]
-    [mac_greek "MacGreek"]
-    [mac_hebrew "MacHebrew"]
-    [mac_iceland "MacIceland"]
-    [mac_roman "MacRoman"]
-    [mac_romania "MacRomania"]
-    [mac_symbol "MacSymbol"]
-    [mac_thai "MacThai"]
-    [mac_turkish "MacTurkish"]
-    [mac_ukraine "MacUkraine"]
-    
-    [utf_8 "UTF-8"]
-    [utf_16 "UTF-16"]
-    [utf_32 "UTF-32"]
+     [mac_arabic "MacArabic"]
+     [mac_central_europe "MacCentralEurope"]
+     [mac_croatian "MacCroatian"]
+     [mac_cyrillic "MacCyrillic"]
+     [mac_dingbat "MacDingbat"]
+     [mac_greek "MacGreek"]
+     [mac_hebrew "MacHebrew"]
+     [mac_iceland "MacIceland"]
+     [mac_roman "MacRoman"]
+     [mac_romania "MacRomania"]
+     [mac_symbol "MacSymbol"]
+     [mac_thai "MacThai"]
+     [mac_turkish "MacTurkish"]
+     [mac_ukraine "MacUkraine"]
+     
+     [utf_8 "UTF-8"]
+     [utf_16 "UTF-16"]
+     [utf_32 "UTF-32"]
 
-    [windows_31j "windows-31j"]
-    [windows_874 "windows-874"]
-    [windows_949 "windows-949"]
-    [windows_950 "windows-950"]
-    [windows_1250 "windows-1250"]
-    [windows_1252 "windows-1252"]
-    [windows_1251 "windows-1251"]
-    [windows_1253 "windows-1253"]
-    [windows_1254 "windows-1254"]
-    [windows_1255 "windows-1255"]
-    [windows_1256 "windows-1256"]
-    [windows_1257 "windows-1257"]
-    [windows_1258 "windows-1258"]
-    [windows_iso2022jp "windows-iso2022jp"]
-    [windows_50220 "windows-50220"]
-    [windows_50221 "windows-50221"]
-    
-    [cesu_8 "CESU-8"]
-    [koi8_r "KOI8-R"]
-    [koi8_u "KOI8-U"]
-    )
+     [windows_31j "windows-31j"]
+     [windows_874 "windows-874"]
+     [windows_949 "windows-949"]
+     [windows_950 "windows-950"]
+     [windows_1250 "windows-1250"]
+     [windows_1252 "windows-1252"]
+     [windows_1251 "windows-1251"]
+     [windows_1253 "windows-1253"]
+     [windows_1254 "windows-1254"]
+     [windows_1255 "windows-1255"]
+     [windows_1256 "windows-1256"]
+     [windows_1257 "windows-1257"]
+     [windows_1258 "windows-1258"]
+     [windows_iso2022jp "windows-iso2022jp"]
+     [windows_50220 "windows-50220"]
+     [windows_50221 "windows-50221"]
+     
+     [cesu_8 "CESU-8"]
+     [koi8_r "KOI8-R"]
+     [koi8_u "KOI8-U"]
+     )
 
-  (def: .public name
-    (-> Encoding Text)
-    (|>> :representation))
+   (def: .public name
+     (-> Encoding Text)
+     (|>> :representation))]
   )
diff --git a/stdlib/source/library/lux/data/text/unicode/block.lux b/stdlib/source/library/lux/data/text/unicode/block.lux
index 7d0bfca33..bca01c5ee 100644
--- a/stdlib/source/library/lux/data/text/unicode/block.lux
+++ b/stdlib/source/library/lux/data/text/unicode/block.lux
@@ -15,49 +15,47 @@
   [/// {"+" [Char]}])
 
 (abstract: .public Block
-  {}
-
   (Interval Char)
   
-  (implementation: .public monoid
-    (Monoid Block)
-    
-    (def: identity
-      (:abstraction
-       (interval.between n.enum n\top n\bottom)))
-    
-    (def: (composite left right)
-      (let [left (:representation left)
-            right (:representation right)]
-        (:abstraction
-         (interval.between n.enum
-                           (n.min (\ left bottom)
-                                  (\ right bottom))
-                           (n.max (\ left top)
-                                  (\ right top)))))))
+  [(implementation: .public monoid
+     (Monoid Block)
+     
+     (def: identity
+       (:abstraction
+        (interval.between n.enum n\top n\bottom)))
+     
+     (def: (composite left right)
+       (let [left (:representation left)
+             right (:representation right)]
+         (:abstraction
+          (interval.between n.enum
+                            (n.min (\ left bottom)
+                                   (\ right bottom))
+                            (n.max (\ left top)
+                                   (\ right top)))))))
 
-  (def: .public (block start additional)
-    (-> Char Nat Block)
-    (:abstraction (interval.between n.enum start (n.+ additional start))))
+   (def: .public (block start additional)
+     (-> Char Nat Block)
+     (:abstraction (interval.between n.enum start (n.+ additional start))))
 
-  (template [ ]
-    [(def: .public 
-       (-> Block Char)
-       (|>> :representation (value@ )))]
+   (template [ ]
+     [(def: .public 
+        (-> Block Char)
+        (|>> :representation (value@ )))]
 
-    [start #interval.bottom]
-    [end   #interval.top]
-    )
+     [start #interval.bottom]
+     [end   #interval.top]
+     )
 
-  (def: .public (size block)
-    (-> Block Nat)
-    (let [start (value@ #interval.bottom (:representation block))
-          end (value@ #interval.top (:representation block))]
-      (|> end (n.- start) ++)))
+   (def: .public (size block)
+     (-> Block Nat)
+     (let [start (value@ #interval.bottom (:representation block))
+           end (value@ #interval.top (:representation block))]
+       (|> end (n.- start) ++)))
 
-  (def: .public (within? block char)
-    (All (_ a) (-> Block Char Bit))
-    (interval.within? (:representation block) char))
+   (def: .public (within? block char)
+     (All (_ a) (-> Block Char Bit))
+     (interval.within? (:representation block) char))]
   )
 
 (implementation: .public equivalence
diff --git a/stdlib/source/library/lux/data/text/unicode/set.lux b/stdlib/source/library/lux/data/text/unicode/set.lux
index bab5bf9ae..b47505a09 100644
--- a/stdlib/source/library/lux/data/text/unicode/set.lux
+++ b/stdlib/source/library/lux/data/text/unicode/set.lux
@@ -27,212 +27,210 @@
                @))
 
 (abstract: .public Set
-  {}
-  
   (Tree :@: Block [])
 
-  (def: .public (composite left right)
-    (-> Set Set Set)
-    (:abstraction
-     (\ builder branch
-        (:representation left)
-        (:representation right))))
-
-  (def: (singleton block)
-    (-> Block Set)
-    (:abstraction
-     (\ builder leaf block [])))
-
-  (def: .public (set [head tail])
-    (-> [Block (List Block)] Set)
-    (list\mix (: (-> Block Set Set)
-                 (function (_ block set)
-                   (..composite (..singleton block) set)))
-              (..singleton head)
-              tail))
-
-  (def: character/0
-    Set
-    (..set [//block.basic_latin
-            (list //block.latin_1_supplement
-                  //block.latin_extended_a
-                  //block.latin_extended_b
-                  //block.ipa_extensions
-                  //block.spacing_modifier_letters
-                  //block.combining_diacritical_marks
-                  //block.greek_and_coptic
-                  //block.cyrillic
-                  //block.cyrillic_supplementary
-                  //block.armenian
-                  //block.hebrew
-                  //block.arabic
-                  //block.syriac
-                  //block.thaana
-                  //block.devanagari
-                  //block.bengali
-                  //block.gurmukhi
-                  //block.gujarati
-                  //block.oriya
-                  //block.tamil
-                  //block.telugu
-                  //block.kannada
-                  //block.malayalam
-                  //block.sinhala
-                  //block.thai
-                  //block.lao
-                  //block.tibetan
-                  //block.myanmar
-                  //block.georgian)]))
-
-  (def: character/1
-    Set
-    (..set [//block.hangul_jamo
-            (list //block.ethiopic
-                  //block.cherokee
-                  //block.unified_canadian_aboriginal_syllabics
-                  //block.ogham
-                  //block.runic
-                  //block.tagalog
-                  //block.hanunoo
-                  //block.buhid
-                  //block.tagbanwa
-                  //block.khmer
-                  //block.mongolian
-                  //block.limbu
-                  //block.tai_le
-                  //block.khmer_symbols
-                  //block.phonetic_extensions
-                  //block.latin_extended_additional
-                  //block.greek_extended
-                  //block.general_punctuation
-                  //block.superscripts_and_subscripts
-                  //block.currency_symbols
-                  //block.combining_diacritical_marks_for_symbols
-                  //block.letterlike_symbols
-                  //block.number_forms
-                  //block.arrows
-                  //block.mathematical_operators
-                  //block.miscellaneous_technical
-                  //block.control_pictures
-                  //block.optical_character_recognition
-                  //block.enclosed_alphanumerics
-                  //block.box_drawing)]))
-
-  (def: character/2
-    Set
-    (..set [//block.block_elements
-            (list //block.geometric_shapes
-                  //block.miscellaneous_symbols
-                  //block.dingbats
-                  //block.miscellaneous_mathematical_symbols_a
-                  //block.supplemental_arrows_a
-                  //block.braille_patterns
-                  //block.supplemental_arrows_b
-                  //block.miscellaneous_mathematical_symbols_b
-                  //block.supplemental_mathematical_operators
-                  //block.miscellaneous_symbols_and_arrows
-                  //block.cjk_radicals_supplement
-                  //block.kangxi_radicals
-                  //block.ideographic_description_characters
-                  //block.cjk_symbols_and_punctuation
-                  //block.hiragana
-                  //block.katakana
-                  //block.bopomofo
-                  //block.hangul_compatibility_jamo
-                  //block.kanbun
-                  //block.bopomofo_extended
-                  //block.katakana_phonetic_extensions
-                  //block.enclosed_cjk_letters_and_months
-                  //block.cjk_compatibility
-                  //block.cjk_unified_ideographs_extension_a
-                  //block.yijing_hexagram_symbols
-                  //block.cjk_unified_ideographs
-                  //block.yi_syllables
-                  //block.yi_radicals
-                  //block.hangul_syllables
-                  )]))
-
-  (def: .public character
-    Set
-    ($_ ..composite
-        ..character/0
-        ..character/1
-        ..character/2
-        ))
-
-  (def: .public non_character
-    Set
-    (..set [//block.high_surrogates
-            (list  //block.high_private_use_surrogates
-                   //block.low_surrogates
-                   //block.private_use_area
-                   //block.cjk_compatibility_ideographs
-                   //block.alphabetic_presentation_forms
-                   //block.arabic_presentation_forms_a
-                   //block.variation_selectors
-                   //block.combining_half_marks
-                   //block.cjk_compatibility_forms
-                   //block.small_form_variants
-                   //block.arabic_presentation_forms_b
-                   //block.halfwidth_and_fullwidth_forms
-                   //block.specials
-                   ... //block.linear_b_syllabary
-                   ... //block.linear_b_ideograms
-                   ... //block.aegean_numbers
-                   ... //block.old_italic
-                   ... //block.gothic
-                   ... //block.ugaritic
-                   ... //block.deseret
-                   ... //block.shavian
-                   ... //block.osmanya
-                   ... //block.cypriot_syllabary
-                   ... //block.byzantine_musical_symbols
-                   ... //block.musical_symbols
-                   ... //block.tai_xuan_jing_symbols
-                   ... //block.mathematical_alphanumeric_symbols
-                   ... //block.cjk_unified_ideographs_extension_b
-                   ... //block.cjk_compatibility_ideographs_supplement
-                   ... //block.tags
+  [(def: .public (composite left right)
+     (-> Set Set Set)
+     (:abstraction
+      (\ builder branch
+         (:representation left)
+         (:representation right))))
+
+   (def: (singleton block)
+     (-> Block Set)
+     (:abstraction
+      (\ builder leaf block [])))
+
+   (def: .public (set [head tail])
+     (-> [Block (List Block)] Set)
+     (list\mix (: (-> Block Set Set)
+                  (function (_ block set)
+                    (..composite (..singleton block) set)))
+               (..singleton head)
+               tail))
+
+   (def: character/0
+     Set
+     (..set [//block.basic_latin
+             (list //block.latin_1_supplement
+                   //block.latin_extended_a
+                   //block.latin_extended_b
+                   //block.ipa_extensions
+                   //block.spacing_modifier_letters
+                   //block.combining_diacritical_marks
+                   //block.greek_and_coptic
+                   //block.cyrillic
+                   //block.cyrillic_supplementary
+                   //block.armenian
+                   //block.hebrew
+                   //block.arabic
+                   //block.syriac
+                   //block.thaana
+                   //block.devanagari
+                   //block.bengali
+                   //block.gurmukhi
+                   //block.gujarati
+                   //block.oriya
+                   //block.tamil
+                   //block.telugu
+                   //block.kannada
+                   //block.malayalam
+                   //block.sinhala
+                   //block.thai
+                   //block.lao
+                   //block.tibetan
+                   //block.myanmar
+                   //block.georgian)]))
+
+   (def: character/1
+     Set
+     (..set [//block.hangul_jamo
+             (list //block.ethiopic
+                   //block.cherokee
+                   //block.unified_canadian_aboriginal_syllabics
+                   //block.ogham
+                   //block.runic
+                   //block.tagalog
+                   //block.hanunoo
+                   //block.buhid
+                   //block.tagbanwa
+                   //block.khmer
+                   //block.mongolian
+                   //block.limbu
+                   //block.tai_le
+                   //block.khmer_symbols
+                   //block.phonetic_extensions
+                   //block.latin_extended_additional
+                   //block.greek_extended
+                   //block.general_punctuation
+                   //block.superscripts_and_subscripts
+                   //block.currency_symbols
+                   //block.combining_diacritical_marks_for_symbols
+                   //block.letterlike_symbols
+                   //block.number_forms
+                   //block.arrows
+                   //block.mathematical_operators
+                   //block.miscellaneous_technical
+                   //block.control_pictures
+                   //block.optical_character_recognition
+                   //block.enclosed_alphanumerics
+                   //block.box_drawing)]))
+
+   (def: character/2
+     Set
+     (..set [//block.block_elements
+             (list //block.geometric_shapes
+                   //block.miscellaneous_symbols
+                   //block.dingbats
+                   //block.miscellaneous_mathematical_symbols_a
+                   //block.supplemental_arrows_a
+                   //block.braille_patterns
+                   //block.supplemental_arrows_b
+                   //block.miscellaneous_mathematical_symbols_b
+                   //block.supplemental_mathematical_operators
+                   //block.miscellaneous_symbols_and_arrows
+                   //block.cjk_radicals_supplement
+                   //block.kangxi_radicals
+                   //block.ideographic_description_characters
+                   //block.cjk_symbols_and_punctuation
+                   //block.hiragana
+                   //block.katakana
+                   //block.bopomofo
+                   //block.hangul_compatibility_jamo
+                   //block.kanbun
+                   //block.bopomofo_extended
+                   //block.katakana_phonetic_extensions
+                   //block.enclosed_cjk_letters_and_months
+                   //block.cjk_compatibility
+                   //block.cjk_unified_ideographs_extension_a
+                   //block.yijing_hexagram_symbols
+                   //block.cjk_unified_ideographs
+                   //block.yi_syllables
+                   //block.yi_radicals
+                   //block.hangul_syllables
                    )]))
 
-  (def: .public full
-    Set
-    ($_ ..composite
-        ..character
-        ..non_character
-        ))
-
-  (def: .public start
-    (-> Set Char)
-    (|>> :representation
-         tree.tag
-         //block.start))
-
-  (def: .public end
-    (-> Set Char)
-    (|>> :representation
-         tree.tag
-         //block.end))
-
-  (def: .public (member? set character)
-    (-> Set Char Bit)
-    (loop [tree (:representation set)]
-      (if (//block.within? (tree.tag tree) character)
-        (case (tree.root tree)
-          (0 #0 _)
-          true
-          
-          (0 #1 left right)
-          (or (recur left)
-              (recur right)))
-        false)))
-
-  (implementation: .public equivalence
-    (Equivalence Set)
-
-    (def: (= reference subject)
-      (set\= (set.of_list //block.hash (tree.tags (:representation reference)))
-             (set.of_list //block.hash (tree.tags (:representation subject))))))
+   (def: .public character
+     Set
+     ($_ ..composite
+         ..character/0
+         ..character/1
+         ..character/2
+         ))
+
+   (def: .public non_character
+     Set
+     (..set [//block.high_surrogates
+             (list  //block.high_private_use_surrogates
+                    //block.low_surrogates
+                    //block.private_use_area
+                    //block.cjk_compatibility_ideographs
+                    //block.alphabetic_presentation_forms
+                    //block.arabic_presentation_forms_a
+                    //block.variation_selectors
+                    //block.combining_half_marks
+                    //block.cjk_compatibility_forms
+                    //block.small_form_variants
+                    //block.arabic_presentation_forms_b
+                    //block.halfwidth_and_fullwidth_forms
+                    //block.specials
+                    ... //block.linear_b_syllabary
+                    ... //block.linear_b_ideograms
+                    ... //block.aegean_numbers
+                    ... //block.old_italic
+                    ... //block.gothic
+                    ... //block.ugaritic
+                    ... //block.deseret
+                    ... //block.shavian
+                    ... //block.osmanya
+                    ... //block.cypriot_syllabary
+                    ... //block.byzantine_musical_symbols
+                    ... //block.musical_symbols
+                    ... //block.tai_xuan_jing_symbols
+                    ... //block.mathematical_alphanumeric_symbols
+                    ... //block.cjk_unified_ideographs_extension_b
+                    ... //block.cjk_compatibility_ideographs_supplement
+                    ... //block.tags
+                    )]))
+
+   (def: .public full
+     Set
+     ($_ ..composite
+         ..character
+         ..non_character
+         ))
+
+   (def: .public start
+     (-> Set Char)
+     (|>> :representation
+          tree.tag
+          //block.start))
+
+   (def: .public end
+     (-> Set Char)
+     (|>> :representation
+          tree.tag
+          //block.end))
+
+   (def: .public (member? set character)
+     (-> Set Char Bit)
+     (loop [tree (:representation set)]
+       (if (//block.within? (tree.tag tree) character)
+         (case (tree.root tree)
+           (0 #0 _)
+           true
+           
+           (0 #1 left right)
+           (or (recur left)
+               (recur right)))
+         false)))
+
+   (implementation: .public equivalence
+     (Equivalence Set)
+
+     (def: (= reference subject)
+       (set\= (set.of_list //block.hash (tree.tags (:representation reference)))
+              (set.of_list //block.hash (tree.tags (:representation subject))))))]
   )
 
 (template [ ]
diff --git a/stdlib/source/library/lux/ffi.js.lux b/stdlib/source/library/lux/ffi.js.lux
index 49cd0067a..b8a1dbf58 100644
--- a/stdlib/source/library/lux/ffi.js.lux
+++ b/stdlib/source/library/lux/ffi.js.lux
@@ -22,20 +22,15 @@
      ["[0]" code]
      ["[0]" template]]]])
 
-(abstract: .public (Object brand)
-  {}
-  
-  Any)
+(abstract: .public (Object brand) Any [])
 
 (template []
   [(with_expansions [ (template.identifier [ "'"])]
      (abstract: 
-       {}
-       
        Any
        
-       (type: .public 
-         (Object ))))]
+       [(type: .public 
+          (Object ))]))]
 
   [Function]
   [Symbol]
diff --git a/stdlib/source/library/lux/ffi.lua.lux b/stdlib/source/library/lux/ffi.lua.lux
index 4144c573f..b4dac8f03 100644
--- a/stdlib/source/library/lux/ffi.lua.lux
+++ b/stdlib/source/library/lux/ffi.lua.lux
@@ -23,13 +23,11 @@
      ["[0]" code]
      ["[0]" template]]]])
 
-(abstract: .public (Object brand)
-  {}
-  Any)
+(abstract: .public (Object brand) Any [])
 
 (template []
   [(with_expansions [ (template.identifier [ "'"])]
-     (abstract:  {} Any)
+     (abstract:  Any [])
      (type: .public 
        (..Object )))]
 
diff --git a/stdlib/source/library/lux/ffi.php.lux b/stdlib/source/library/lux/ffi.php.lux
index 245c56391..095b1b754 100644
--- a/stdlib/source/library/lux/ffi.php.lux
+++ b/stdlib/source/library/lux/ffi.php.lux
@@ -23,11 +23,11 @@
      ["[0]" code]
      ["[0]" template]]]])
 
-(abstract: .public (Object brand) {} Any)
+(abstract: .public (Object brand) Any [])
 
 (template []
   [(with_expansions [ (template.identifier [ "'"])]
-     (abstract: .public  {} Any)
+     (abstract: .public  Any [])
      (type: .public 
        (..Object )))]
 
diff --git a/stdlib/source/library/lux/ffi.py.lux b/stdlib/source/library/lux/ffi.py.lux
index b6f7eced4..d0ac65ba0 100644
--- a/stdlib/source/library/lux/ffi.py.lux
+++ b/stdlib/source/library/lux/ffi.py.lux
@@ -23,13 +23,11 @@
      ["[0]" code]
      ["[0]" template]]]])
 
-(abstract: .public (Object brand)
-  {}
-  Any)
+(abstract: .public (Object brand) Any [])
 
 (template []
   [(with_expansions [ (template.identifier [ "'"])]
-     (abstract:  {} Any)
+     (abstract:  Any [])
      (type: .public 
        (..Object )))]
 
diff --git a/stdlib/source/library/lux/ffi.rb.lux b/stdlib/source/library/lux/ffi.rb.lux
index 54900494b..62620c6af 100644
--- a/stdlib/source/library/lux/ffi.rb.lux
+++ b/stdlib/source/library/lux/ffi.rb.lux
@@ -23,13 +23,11 @@
      ["[0]" code]
      ["[0]" template]]]])
 
-(abstract: .public (Object brand)
-  {}
-  Any)
+(abstract: .public (Object brand) Any [])
 
 (template []
   [(with_expansions [ (template.identifier [ "'"])]
-     (abstract:  {} Any)
+     (abstract:  Any [])
      (type: .public 
        (..Object )))]
 
diff --git a/stdlib/source/library/lux/ffi.scm.lux b/stdlib/source/library/lux/ffi.scm.lux
index f4f0a0cda..0a3efb41a 100644
--- a/stdlib/source/library/lux/ffi.scm.lux
+++ b/stdlib/source/library/lux/ffi.scm.lux
@@ -23,11 +23,11 @@
      ["[0]" code]
      ["[0]" template]]]])
 
-(abstract: .public (Object brand) {} Any)
+(abstract: .public (Object brand) Any [])
 
 (template []
   [(with_expansions [ (template.identifier [ "'"])]
-     (abstract: .public  {} Any)
+     (abstract: .public  Any [])
      (type: .public 
        (..Object )))]
 
diff --git a/stdlib/source/library/lux/locale.lux b/stdlib/source/library/lux/locale.lux
index 5b855793b..e0ac8bce0 100644
--- a/stdlib/source/library/lux/locale.lux
+++ b/stdlib/source/library/lux/locale.lux
@@ -17,32 +17,30 @@
    ["[0]" territory {"+" [Territory]}]])
 
 (abstract: .public Locale
-  {}
-  
   Text
 
-  (def: territory_separator "_")
-  (def: encoding_separator ".")
+  [(def: territory_separator "_")
+   (def: encoding_separator ".")
 
-  (def: .public (locale language territory encoding)
-    (-> Language (Maybe Territory) (Maybe Encoding) Locale)
-    (:abstraction (format (language.code language)
-                          (|> territory
-                              (maybe\each (|>> territory.long_code (format ..territory_separator)))
-                              (maybe.else ""))
-                          (|> encoding
-                              (maybe\each (|>> encoding.name (format ..encoding_separator)))
-                              (maybe.else "")))))
+   (def: .public (locale language territory encoding)
+     (-> Language (Maybe Territory) (Maybe Encoding) Locale)
+     (:abstraction (format (language.code language)
+                           (|> territory
+                               (maybe\each (|>> territory.long_code (format ..territory_separator)))
+                               (maybe.else ""))
+                           (|> encoding
+                               (maybe\each (|>> encoding.name (format ..encoding_separator)))
+                               (maybe.else "")))))
 
-  (def: .public code
-    (-> Locale Text)
-    (|>> :representation))
+   (def: .public code
+     (-> Locale Text)
+     (|>> :representation))
 
-  (def: .public hash
-    (Hash Locale)
-    (\ hash.functor each ..code text.hash))
+   (def: .public hash
+     (Hash Locale)
+     (\ hash.functor each ..code text.hash))
 
-  (def: .public equivalence
-    (Equivalence Locale)
-    (\ ..hash &equivalence))
+   (def: .public equivalence
+     (Equivalence Locale)
+     (\ ..hash &equivalence))]
   )
diff --git a/stdlib/source/library/lux/locale/language.lux b/stdlib/source/library/lux/locale/language.lux
index e3a48b904..f8314c376 100644
--- a/stdlib/source/library/lux/locale/language.lux
+++ b/stdlib/source/library/lux/locale/language.lux
@@ -13,564 +13,562 @@
 
 ... https://en.wikipedia.org/wiki/List_of_ISO_639-2_codes
 (abstract: .public Language
-  {}
-
   (Record
    [#name Text
     #code Text])
 
-  (template [ ]
-    [(def: .public 
-       (-> Language Text)
-       (|>> :representation (value@ )))]
-
-    [name #name]
-    [code #code]
-    )
-
-  (template []
-    [(with_expansions [' (template.spliced )]
-       (template [   +]
-         [(def: .public 
-            Language
-            (:abstraction [#name 
-                           #code ]))
-          (`` (template []
-                [(def: .public 
-                   Language
-                   )]
-
-                (~~ (template.spliced +))))]
-
-         '
-         ))]
-
-    [[["mis" "uncoded languages" uncoded []]
-      ["mul" "multiple languages" multiple []]
-      ["und" "undetermined" undetermined []]
-      ["zxx" "no linguistic content; not applicable" not_applicable []]]]
-
-    [[["aar" "Afar" afar []]
-      ["abk" "Abkhazian" abkhazian []]
-      ["ace" "Achinese" achinese []]
-      ["ach" "Acoli" acoli []]
-      ["ada" "Adangme" adangme []]
-      ["ady" "Adyghe; Adygei" adyghe []]
-      ["afa" "Afro-Asiatic languages" afro_asiatic []]
-      ["afh" "Afrihili" afrihili []]
-      ["afr" "Afrikaans" afrikaans []]
-      ["ain" "Ainu" ainu []]
-      ["aka" "Akan" akan []]
-      ["akk" "Akkadian" akkadian []]
-      ["ale" "Aleut" aleut []]
-      ["alg" "Algonquian languages" algonquian []]
-      ["alt" "Southern Altai" southern_altai []]
-      ["amh" "Amharic" amharic []]
-      ["ang" "Old English (ca.450–1100)" old_english []]
-      ["anp" "Angika" angika []]
-      ["apa" "Apache languages" apache []]
-      ["ara" "Arabic" arabic []]
-      ["arc" "Official Aramaic (700–300 BCE); Imperial Aramaic (700–300 BCE)" official_aramaic [[imperial_aramaic]]]
-      ["arg" "Aragonese" aragonese []]
-      ["arn" "Mapudungun; Mapuche" mapudungun []]
-      ["arp" "Arapaho" arapaho []]
-      ["art" "Artificial languages" artificial []]
-      ["arw" "Arawak" arawak []]
-      ["asm" "Assamese" assamese []]
-      ["ast" "Asturian; Bable; Leonese; Asturleonese" asturian [[bable] [leonese] [asturleonese]]]
-      ["ath" "Athapascan languages" athapascan []]
-      ["aus" "Australian languages" australian []]
-      ["ava" "Avaric" avaric []]
-      ["ave" "Avestan" avestan []]
-      ["awa" "Awadhi" awadhi []]
-      ["aym" "Aymara" aymara []]
-      ["aze" "Azerbaijani" azerbaijani []]]]
-    
-    [[["bad" "Banda languages" banda []]
-      ["bai" "Bamileke languages" bamileke []]
-      ["bak" "Bashkir" bashkir []]
-      ["bal" "Baluchi" baluchi []]
-      ["bam" "Bambara" bambara []]
-      ["ban" "Balinese" balinese []]
-      ["bas" "Basa" basa []]
-      ["bat" "Baltic languages" baltic []]
-      ["bej" "Beja; Bedawiyet" beja []]
-      ["bel" "Belarusian" belarusian []]
-      ["bem" "Bemba" bemba []]
-      ["ben" "Bengali" bengali []]
-      ["ber" "Berber languages" berber []]
-      ["bho" "Bhojpuri" bhojpuri []]
-      ["bih" "Bihari languages" bihari []]
-      ["bik" "Bikol" bikol []]
-      ["bin" "Bini; Edo" bini [[edo]]]
-      ["bis" "Bislama" bislama []]
-      ["bla" "Siksika" siksika []]
-      ["bnt" "Bantu languages" bantu []]
-      ["bod" "Tibetan" tibetan []]
-      ["bos" "Bosnian" bosnian []]
-      ["bra" "Braj" braj []]
-      ["bre" "Breton" breton []]
-      ["btk" "Batak languages" batak []]
-      ["bua" "Buriat" buriat []]
-      ["bug" "Buginese" buginese []]
-      ["bul" "Bulgarian" bulgarian []]
-      ["byn" "Blin; Bilin" blin [[bilin]]]]]
-
-    [[["cad" "Caddo" caddo []]
-      ["cai" "Central American Indian languages" central_american_indian []]
-      ["car" "Galibi Carib" galibi_carib []]
-      ["cat" "Catalan; Valencian" catalan [[valencian]]]
-      ["cau" "Caucasian languages" caucasian []]
-      ["ceb" "Cebuano" cebuano []]
-      ["cel" "Celtic languages" celtic []]
-      ["ces" "Czech" czech []]
-      ["cha" "Chamorro" chamorro []]
-      ["chb" "Chibcha" chibcha []]
-      ["che" "Chechen" chechen []]
-      ["chg" "Chagatai" chagatai []]
-      ["chk" "Chuukese" chuukese []]
-      ["chm" "Mari" mari []]
-      ["chn" "Chinook jargon" chinook []]
-      ["cho" "Choctaw" choctaw []]
-      ["chp" "Chipewyan; Dene Suline" chipewyan []]
-      ["chr" "Cherokee" cherokee []]
-      ["chu" "Church Slavic; Old Slavonic; Church Slavonic; Old Bulgarian; Old Church Slavonic" church_slavic [[old_slavonic] [church_slavonic] [old_bulgarian] [old_church_slavonic]]]
-      ["chv" "Chuvash" chuvash []]
-      ["chy" "Cheyenne" cheyenne []]
-      ["cmc" "Chamic languages" chamic []]
-      ["cnr" "Montenegrin" montenegrin []]
-      ["cop" "Coptic" coptic []]
-      ["cor" "Cornish" cornish []]
-      ["cos" "Corsican" corsican []]
-      ["cpe" "Creoles and pidgins, English based" creoles_and_pidgins/english []]
-      ["cpf" "Creoles and pidgins, French-based" creoles_and_pidgins/french []]
-      ["cpp" "Creoles and pidgins, Portuguese-based" creoles_and_pidgins/portuguese []]
-      ["cre" "Cree" cree []]
-      ["crh" "Crimean Tatar; Crimean Turkish" crimean []]
-      ["crp" "Creoles and pidgins" creoles_and_pidgins []]
-      ["csb" "Kashubian" kashubian []]
-      ["cus" "Cushitic languages" cushitic []]
-      ["cym" "Welsh" welsh []]]]
-    
-    [[["dak" "Dakota" dakota []]
-      ["dan" "Danish" danish []]
-      ["dar" "Dargwa" dargwa []]
-      ["day" "Land Dayak languages" land_dayak []]
-      ["del" "Delaware" delaware []]
-      ["den" "Slave (Athapascan)" slavey []]
-      ["deu" "German" german []]
-      ["dgr" "Dogrib" dogrib []]
-      ["din" "Dinka" dinka []]
-      ["div" "Divehi; Dhivehi; Maldivian" dhivehi [[maldivian]]]
-      ["doi" "Dogri" dogri []]
-      ["dra" "Dravidian languages" dravidian []]
-      ["dsb" "Lower Sorbian" lower_sorbian []]
-      ["dua" "Duala" duala []]
-      ["dum" "Middle Dutch (ca. 1050–1350)" middle_dutch []]
-      ["dyu" "Dyula" dyula []]
-      ["dzo" "Dzongkha" dzongkha []]]]
-
-    [[["efi" "Efik" efik []]
-      ["egy" "Ancient Egyptian" egyptian []]
-      ["eka" "Ekajuk" ekajuk []]
-      ["ell" "Modern Greek (1453–)" greek []]
-      ["elx" "Elamite" elamite []]
-      ["eng" "English" english []]
-      ["enm" "Middle English (1100–1500)" middle_english []]
-      ["epo" "Esperanto" esperanto []]
-      ["est" "Estonian" estonian []]
-      ["eus" "Basque" basque []]
-      ["ewe" "Ewe" ewe []]
-      ["ewo" "Ewondo" ewondo []]]]
-
-    [[["fan" "Fang" fang []]
-      ["fao" "Faroese" faroese []]
-      ["fas" "Persian" persian []]
-      ["fat" "Fanti" fanti []]
-      ["fij" "Fijian" fijian []]
-      ["fil" "Filipino; Pilipino" filipino []]
-      ["fin" "Finnish" finnish []]
-      ["fiu" "Finno-Ugrian languages" finno_ugrian []]
-      ["fon" "Fon" fon []]
-      ["fra" "French" french []]
-      ["frm" "Middle French (ca. 1400–1600)" middle_french []]
-      ["fro" "Old French (ca. 842–1400)" old_french []]
-      ["frr" "Northern Frisian" northern_frisian []]
-      ["frs" "Eastern Frisian" eastern_frisian []]
-      ["fry" "Western Frisian" western_frisian []]
-      ["ful" "Fulah" fulah []]
-      ["fur" "Friulian" friulian []]]]
-
-    [[["gaa" "Ga" ga []]
-      ["gay" "Gayo" gayo []]
-      ["gba" "Gbaya" gbaya []]
-      ["gem" "Germanic languages" germanic []]
-      ["gez" "Geez" geez []]
-      ["gil" "Gilbertese" gilbertese []]
-      ["gla" "Gaelic; Scottish Gaelic" gaelic []]
-      ["gle" "Irish" irish []]
-      ["glg" "Galician" galician []]
-      ["glv" "Manx" manx []]
-      ["gmh" "Middle High German (ca. 1050–1500)" middle_high_german []]
-      ["goh" "Old High German (ca. 750–1050)" old_high_german []]
-      ["gon" "Gondi" gondi []]
-      ["gor" "Gorontalo" gorontalo []]
-      ["got" "Gothic" gothic []]
-      ["grb" "Grebo" grebo []]
-      ["grc" "Ancient Greek (to 1453)" ancient_greek []]
-      ["grn" "Guarani" guarani []]
-      ["gsw" "Swiss German; Alemannic; Alsatian" swiss_german [[alemannic] [alsatian]]]
-      ["guj" "Gujarati" gujarati []]
-      ["gwi" "Gwich'in" gwich'in []]]]
-
-    [[["hai" "Haida" haida []]
-      ["hat" "Haitian; Haitian Creole" haitian []]
-      ["hau" "Hausa" hausa []]
-      ["haw" "Hawaiian" hawaiian []]
-      ["heb" "Hebrew" hebrew []]
-      ["her" "Herero" herero []]
-      ["hil" "Hiligaynon" hiligaynon []]
-      ["him" "Himachali languages; Pahari languages" himachali []]
-      ["hin" "Hindi" hindi []]
-      ["hit" "Hittite" hittite []]
-      ["hmn" "Hmong; Mong" hmong []]
-      ["hmo" "Hiri Motu" hiri_motu []]
-      ["hrv" "Croatian" croatian []]
-      ["hsb" "Upper Sorbian" upper_sorbian []]
-      ["hun" "Hungarian" hungarian []]
-      ["hup" "Hupa" hupa []]
-      ["hye" "Armenian" armenian []]]]
-
-    [[["iba" "Iban" iban []]
-      ["ibo" "Igbo" igbo []]
-      ["ido" "Ido" ido []]
-      ["iii" "Sichuan Yi; Nuosu" sichuan_yi [[nuosu]]]
-      ["ijo" "Ijo languages" ijo []]
-      ["iku" "Inuktitut" inuktitut []]
-      ["ile" "Interlingue; Occidental" interlingue []]
-      ["ilo" "Iloko" iloko []]
-      ["ina" "Interlingua (International Auxiliary Language Association)" interlingua []]
-      ["inc" "Indic languages" indic []]
-      ["ind" "Indonesian" indonesian []]
-      ["ine" "Indo-European languages" indo_european []]
-      ["inh" "Ingush" ingush []]
-      ["ipk" "Inupiaq" inupiaq []]
-      ["ira" "Iranian languages" iranian []]
-      ["iro" "Iroquoian languages" iroquoian []]
-      ["isl" "Icelandic" icelandic []]
-      ["ita" "Italian" italian []]]]
-
-    [[["jav" "Javanese" javanese []]
-      ["jbo" "Lojban" lojban []]
-      ["jpn" "Japanese" japanese []]
-      ["jpr" "Judeo-Persian" judeo_persian []]
-      ["jrb" "Judeo-Arabic" judeo_arabic []]]]
-
-    [[["kaa" "Kara-Kalpak" kara_kalpak []]
-      ["kab" "Kabyle" kabyle []]
-      ["kac" "Kachin; Jingpho" kachin [[jingpho]]]
-      ["kal" "Kalaallisut; Greenlandic" kalaallisut [[greenlandic]]]
-      ["kam" "Kamba" kamba []]
-      ["kan" "Kannada" kannada []]
-      ["kar" "Karen languages" karen []]
-      ["kas" "Kashmiri" kashmiri []]
-      ["kat" "Georgian" georgian []]
-      ["kau" "Kanuri" kanuri []]
-      ["kaw" "Kawi" kawi []]
-      ["kaz" "Kazakh" kazakh []]
-      ["kbd" "Kabardian" kabardian []]
-      ["kha" "Khasi" khasi []]
-      ["khi" "Khoisan languages" khoisan []]
-      ["khm" "Central Khmer" central_khmer []]
-      ["kho" "Khotanese; Sakan" khotanese [[sakan]]]
-      ["kik" "Kikuyu; Gikuyu" gikuyu []]
-      ["kin" "Kinyarwanda" kinyarwanda []]
-      ["kir" "Kirghiz; Kyrgyz" kyrgyz []]
-      ["kmb" "Kimbundu" kimbundu []]
-      ["kok" "Konkani" konkani []]
-      ["kom" "Komi" komi []]
-      ["kon" "Kongo" kongo []]
-      ["kor" "Korean" korean []]
-      ["kos" "Kosraean" kosraean []]
-      ["kpe" "Kpelle" kpelle []]
-      ["krc" "Karachay-Balkar" karachay_balkar []]
-      ["krl" "Karelian" karelian []]
-      ["kro" "Kru languages" kru []]
-      ["kru" "Kurukh" kurukh []]
-      ["kua" "Kuanyama; Kwanyama" kwanyama []]
-      ["kum" "Kumyk" kumyk []]
-      ["kur" "Kurdish" kurdish []]
-      ["kut" "Kutenai" kutenai []]]]
-
-    [[["lad" "Ladino" ladino []]
-      ["lah" "Lahnda" lahnda []]
-      ["lam" "Lamba" lamba []]
-      ["lao" "Lao" lao []]
-      ["lat" "Latin" latin []]
-      ["lav" "Latvian" latvian []]
-      ["lez" "Lezghian" lezghian []]
-      ["lim" "Limburgan; Limburger; Limburgish" limburgan []]
-      ["lin" "Lingala" lingala []]
-      ["lit" "Lithuanian" lithuanian []]
-      ["lol" "Mongo" mongo []]
-      ["loz" "Lozi" lozi []]
-      ["ltz" "Luxembourgish; Letzeburgesch" luxembourgish []]
-      ["lua" "Luba-Lulua" luba_lulua []]
-      ["lub" "Luba-Katanga" luba_katanga []]
-      ["lug" "Ganda" ganda []]
-      ["lui" "Luiseno" luiseno []]
-      ["lun" "Lunda" lunda []]
-      ["luo" "Luo (Kenya and Tanzania)" luo []]
-      ["lus" "Lushai" lushai []]]]
-
-    [[["mad" "Madurese" madurese []]
-      ["mag" "Magahi" magahi []]
-      ["mah" "Marshallese" marshallese []]
-      ["mai" "Maithili" maithili []]
-      ["mak" "Makasar" makasar []]
-      ["mal" "Malayalam" malayalam []]
-      ["man" "Mandingo" mandingo []]
-      ["map" "Austronesian languages" austronesian []]
-      ["mar" "Marathi" marathi []]
-      ["mas" "Masai" masai []]
-      ["mdf" "Moksha" moksha []]
-      ["mdr" "Mandar" mandar []]
-      ["men" "Mende" mende []]
-      ["mga" "Middle Irish (900–1200)" middle_irish []]
-      ["mic" "Mi'kmaq; Micmac" mi'kmaq [[micmac]]]
-      ["min" "Minangkabau" minangkabau []]
-      ["mkd" "Macedonian" macedonian []]
-      ["mkh" "Mon-Khmer languages" mon_khmer []]
-      ["mlg" "Malagasy" malagasy []]
-      ["mlt" "Maltese" maltese []]
-      ["mnc" "Manchu" manchu []]
-      ["mni" "Manipuri" manipuri []]
-      ["mno" "Manobo languages" manobo []]
-      ["moh" "Mohawk" mohawk []]
-      ["mon" "Mongolian" mongolian []]
-      ["mos" "Mossi" mossi []]
-      ["mri" "Maori" maori []]
-      ["msa" "Malay" malay []]
-      ["mun" "Munda languages" munda []]
-      ["mus" "Creek" creek []]
-      ["mwl" "Mirandese" mirandese []]
-      ["mwr" "Marwari" marwari []]
-      ["mya" "Burmese" burmese []]
-      ["myn" "Mayan languages" mayan []]
-      ["myv" "Erzya" erzya []]]]
-
-    [[["nah" "Nahuatl languages" nahuatl []]
-      ["nai" "North American Indian languages" north_american_indian []]
-      ["nap" "Neapolitan" neapolitan []]
-      ["nau" "Nauru" nauru []]
-      ["nav" "Navajo; Navaho" navajo []]
-      ["nbl" "South Ndebele" south_ndebele []]
-      ["nde" "North Ndebele" north_ndebele []]
-      ["ndo" "Ndonga" ndonga []]
-      ["nds" "Low German; Low Saxon" low_german []]
-      ["nep" "Nepali" nepali []]
-      ["new" "Nepal Bhasa; Newari" newari [[nepal_bhasa]]]
-      ["nia" "Nias" nias []]
-      ["nic" "Niger-Kordofanian languages" niger_kordofanian []]
-      ["niu" "Niuean" niuean []]
-      ["nld" "Dutch; Flemish" dutch [[flemish]]]
-      ["nno" "Norwegian Nynorsk" nynorsk []]
-      ["nob" "Norwegian Bokmål" bokmal []]
-      ["nog" "Nogai" nogai []]
-      ["non" "Old Norse" old_norse []]
-      ["nor" "Norwegian" norwegian []]
-      ["nqo" "N'Ko" n'ko []]
-      ["nso" "Pedi; Sepedi; Northern Sotho" northern_sotho [[pedi] [sepedi]]]
-      ["nub" "Nubian languages" nubian []]
-      ["nwc" "Classical Newari; Old Newari; Classical Nepal Bhasa" old_newari [[classical_newari] [classical_nepal_bhasa]]]
-      ["nya" "Chichewa; Chewa; Nyanja" nyanja [[chichewa] [chewa]]]
-      ["nym" "Nyamwezi" nyamwezi []]
-      ["nyn" "Nyankole" nyankole []]
-      ["nyo" "Nyoro" nyoro []]
-      ["nzi" "Nzima" nzima []]]]
-
-    [[["oci" "Occitan (post 1500); Provençal" occitan [[provencal]]]
-      ["oji" "Ojibwa" ojibwa []]
-      ["ori" "Oriya" oriya []]
-      ["orm" "Oromo" oromo []]
-      ["osa" "Osage" osage []]
-      ["oss" "Ossetian; Ossetic" ossetic []]
-      ["ota" "Ottoman Turkish (1500–1928)" ottoman_turkish []]
-      ["oto" "Otomian languages" otomian []]]]
-
-    [[["paa" "Papuan languages" papuan []]
-      ["pag" "Pangasinan" pangasinan []]
-      ["pal" "Pahlavi" pahlavi []]
-      ["pam" "Pampanga; Kapampangan" pampanga [[kapampangan]]]
-      ["pan" "Panjabi; Punjabi" punjabi []]
-      ["pap" "Papiamento" papiamento []]
-      ["pau" "Palauan" palauan []]
-      ["peo" "Old Persian (ca. 600–400 B.C.)" old_persian []]
-      ["phi" "Philippine languages" philippine []]
-      ["phn" "Phoenician" phoenician []]
-      ["pli" "Pali" pali []]
-      ["pol" "Polish" polish []]
-      ["pon" "Pohnpeian" pohnpeian []]
-      ["por" "Portuguese" portuguese []]
-      ["pra" "Prakrit languages" prakrit []]
-      ["pro" "Old Provençal (to 1500); Old Occitan (to 1500)" old_provencal []]
-      ["pus" "Pushto; Pashto" pashto []]]]
-
-    [[["que" "Quechua" quechua []]]]
-
-    [[["raj" "Rajasthani" rajasthani []]
-      ["rap" "Rapanui" rapanui []]
-      ["rar" "Rarotongan; Cook Islands Maori" rarotongan [[cook_islands_maori]]]
-      ["roa" "Romance languages" romance []]
-      ["roh" "Romansh" romansh []]
-      ["rom" "Romany" romany []]
-      ["ron" "Romanian; Moldavian; Moldovan" romanian [[moldavian] [moldovan]]]
-      ["run" "Rundi" rundi []]
-      ["rup" "Aromanian; Arumanian; Macedo-Romanian" aromanian [[arumanian] [macedo_romanian]]]
-      ["rus" "Russian" russian []]]]
-
-    [[["sad" "Sandawe" sandawe []]
-      ["sag" "Sango" sango []]
-      ["sah" "Yakut" yakut []]
-      ["sai" "South American Indian (Other)" south_american_indian []]
-      ["sal" "Salishan languages" salishan []]
-      ["sam" "Samaritan Aramaic" samaritan_aramaic []]
-      ["san" "Sanskrit" sanskrit []]
-      ["sas" "Sasak" sasak []]
-      ["sat" "Santali" santali []]
-      ["scn" "Sicilian" sicilian []]
-      ["sco" "Scots" scots []]
-      ["sel" "Selkup" selkup []]
-      ["sem" "Semitic languages" semitic []]
-      ["sga" "Old Irish (to 900)" old_irish []]
-      ["sgn" "Sign Languages" sign []]
-      ["shn" "Shan" shan []]
-      ["sid" "Sidamo" sidamo []]
-      ["sin" "Sinhala; Sinhalese" sinhalese []]
-      ["sio" "Siouan languages" siouan []]
-      ["sit" "Sino-Tibetan languages" sino_tibetan []]
-      ["sla" "Slavic languages" slavic []]
-      ["slk" "Slovak" slovak []]
-      ["slv" "Slovenian" slovenian []]
-      ["sma" "Southern Sami" southern_sami []]
-      ["sme" "Northern Sami" northern_sami []]
-      ["smi" "Sami languages" sami []]
-      ["smj" "Lule Sami" lule []]
-      ["smn" "Inari Sami" inari []]
-      ["smo" "Samoan" samoan []]
-      ["sms" "Skolt Sami" skolt_sami []]
-      ["sna" "Shona" shona []]
-      ["snd" "Sindhi" sindhi []]
-      ["snk" "Soninke" soninke []]
-      ["sog" "Sogdian" sogdian []]
-      ["som" "Somali" somali []]
-      ["son" "Songhai languages" songhai []]
-      ["sot" "Southern Sotho" southern_sotho []]
-      ["spa" "Spanish; Castilian" spanish [[castilian]]]
-      ["sqi" "Albanian" albanian []]
-      ["srd" "Sardinian" sardinian []]
-      ["srn" "Sranan Tongo" sranan_tongo []]
-      ["srp" "Serbian" serbian []]
-      ["srr" "Serer" serer []]
-      ["ssa" "Nilo-Saharan languages" nilo_saharan []]
-      ["ssw" "Swati" swati []]
-      ["suk" "Sukuma" sukuma []]
-      ["sun" "Sundanese" sundanese []]
-      ["sus" "Susu" susu []]
-      ["sux" "Sumerian" sumerian []]
-      ["swa" "Swahili" swahili []]
-      ["swe" "Swedish" swedish []]
-      ["syc" "Classical Syriac" classical_syriac []]
-      ["syr" "Syriac" syriac []]]]
-
-    [[["tah" "Tahitian" tahitian []]
-      ["tai" "Tai languages" tai []]
-      ["tam" "Tamil" tamil []]
-      ["tat" "Tatar" tatar []]
-      ["tel" "Telugu" telugu []]
-      ["tem" "Timne" timne []]
-      ["ter" "Tereno" tereno []]
-      ["tet" "Tetum" tetum []]
-      ["tgk" "Tajik" tajik []]
-      ["tgl" "Tagalog" tagalog []]
-      ["tha" "Thai" thai []]
-      ["tig" "Tigre" tigre []]
-      ["tir" "Tigrinya" tigrinya []]
-      ["tiv" "Tiv" tiv []]
-      ["tkl" "Tokelau" tokelau []]
-      ["tlh" "Klingon; tlhIngan-Hol" klingon []]
-      ["tli" "Tlingit" tlingit []]
-      ["tmh" "Tamashek" tamashek []]
-      ["tog" "Tonga (Nyasa)" tonga []]
-      ["ton" "Tonga (Tonga Islands)" tongan []]
-      ["tpi" "Tok Pisin" tok_pisin []]
-      ["tsi" "Tsimshian" tsimshian []]
-      ["tsn" "Tswana" tswana []]
-      ["tso" "Tsonga" tsonga []]
-      ["tuk" "Turkmen" turkmen []]
-      ["tum" "Tumbuka" tumbuka []]
-      ["tup" "Tupi languages" tupi []]
-      ["tur" "Turkish" turkish []]
-      ["tut" "Altaic languages" altaic []]
-      ["tvl" "Tuvalu" tuvalu []]
-      ["twi" "Twi" twi []]
-      ["tyv" "Tuvinian" tuvinian []]]]
-
-    [[["udm" "Udmurt" udmurt []]
-      ["uga" "Ugaritic" ugaritic []]
-      ["uig" "Uighur; Uyghur" uyghur []]
-      ["ukr" "Ukrainian" ukrainian []]
-      ["umb" "Umbundu" umbundu []]
-      ["urd" "Urdu" urdu []]
-      ["uzb" "Uzbek" uzbek []]]]
-
-    [[["vai" "Vai" vai []]
-      ["ven" "Venda" venda []]
-      ["vie" "Vietnamese" vietnamese []]
-      ["vol" "Volapük" volapük []]
-      ["vot" "Votic" votic []]]]
-
-    [[["wak" "Wakashan languages" wakashan []]
-      ["wal" "Wolaitta; Wolaytta" walamo []]
-      ["war" "Waray" waray []]
-      ["was" "Washo" washo []]
-      ["wen" "Sorbian languages" sorbian []]
-      ["wln" "Walloon" walloon []]
-      ["wol" "Wolof" wolof []]]]
-
-    [[["xal" "Kalmyk; Oirat" kalmyk [[oirat]]]
-      ["xho" "Xhosa" xhosa []]]]
-
-    [[["yao" "Yao" yao []]
-      ["yap" "Yapese" yapese []]
-      ["yid" "Yiddish" yiddish []]
-      ["yor" "Yoruba" yoruba []]
-      ["ypk" "Yupik languages" yupik []]]]
-
-    [[["zap" "Zapotec" zapotec []]
-      ["zbl" "Blissymbols; Blissymbolics; Bliss" blissymbols []]
-      ["zen" "Zenaga" zenaga []]
-      ["zgh" "Standard Moroccan Tamazight" standard_moroccan_tamazight []]
-      ["zha" "Zhuang; Chuang" zhuang []]
-      ["zho" "Chinese" chinese []]
-      ["znd" "Zande languages" zande []]
-      ["zul" "Zulu" zulu []]
-      ["zun" "Zuni" zuni []]
-      ["zza" "Zaza; Dimili; Dimli; Kirdki; Kirmanjki; Zazaki" zaza [[dimili] [dimli] [kirdki] [kirmanjki] [zazaki]]]]])
-
-  (implementation: .public equivalence
-    (Equivalence Language)
-    
-    (def: (= reference sample)
-      (same? reference sample)))
-
-  (implementation: .public hash
-    (Hash Language)
-    
-    (def: &equivalence
-      ..equivalence)
-    
-    (def: hash
-      (|>> ..code
-           (\ text.hash hash))))
+  [(template [ ]
+     [(def: .public 
+        (-> Language Text)
+        (|>> :representation (value@ )))]
+
+     [name #name]
+     [code #code]
+     )
+
+   (template []
+     [(with_expansions [' (template.spliced )]
+        (template [   +]
+          [(def: .public 
+             Language
+             (:abstraction [#name 
+                            #code ]))
+           (`` (template []
+                 [(def: .public 
+                    Language
+                    )]
+
+                 (~~ (template.spliced +))))]
+
+          '
+          ))]
+
+     [[["mis" "uncoded languages" uncoded []]
+       ["mul" "multiple languages" multiple []]
+       ["und" "undetermined" undetermined []]
+       ["zxx" "no linguistic content; not applicable" not_applicable []]]]
+
+     [[["aar" "Afar" afar []]
+       ["abk" "Abkhazian" abkhazian []]
+       ["ace" "Achinese" achinese []]
+       ["ach" "Acoli" acoli []]
+       ["ada" "Adangme" adangme []]
+       ["ady" "Adyghe; Adygei" adyghe []]
+       ["afa" "Afro-Asiatic languages" afro_asiatic []]
+       ["afh" "Afrihili" afrihili []]
+       ["afr" "Afrikaans" afrikaans []]
+       ["ain" "Ainu" ainu []]
+       ["aka" "Akan" akan []]
+       ["akk" "Akkadian" akkadian []]
+       ["ale" "Aleut" aleut []]
+       ["alg" "Algonquian languages" algonquian []]
+       ["alt" "Southern Altai" southern_altai []]
+       ["amh" "Amharic" amharic []]
+       ["ang" "Old English (ca.450–1100)" old_english []]
+       ["anp" "Angika" angika []]
+       ["apa" "Apache languages" apache []]
+       ["ara" "Arabic" arabic []]
+       ["arc" "Official Aramaic (700–300 BCE); Imperial Aramaic (700–300 BCE)" official_aramaic [[imperial_aramaic]]]
+       ["arg" "Aragonese" aragonese []]
+       ["arn" "Mapudungun; Mapuche" mapudungun []]
+       ["arp" "Arapaho" arapaho []]
+       ["art" "Artificial languages" artificial []]
+       ["arw" "Arawak" arawak []]
+       ["asm" "Assamese" assamese []]
+       ["ast" "Asturian; Bable; Leonese; Asturleonese" asturian [[bable] [leonese] [asturleonese]]]
+       ["ath" "Athapascan languages" athapascan []]
+       ["aus" "Australian languages" australian []]
+       ["ava" "Avaric" avaric []]
+       ["ave" "Avestan" avestan []]
+       ["awa" "Awadhi" awadhi []]
+       ["aym" "Aymara" aymara []]
+       ["aze" "Azerbaijani" azerbaijani []]]]
+     
+     [[["bad" "Banda languages" banda []]
+       ["bai" "Bamileke languages" bamileke []]
+       ["bak" "Bashkir" bashkir []]
+       ["bal" "Baluchi" baluchi []]
+       ["bam" "Bambara" bambara []]
+       ["ban" "Balinese" balinese []]
+       ["bas" "Basa" basa []]
+       ["bat" "Baltic languages" baltic []]
+       ["bej" "Beja; Bedawiyet" beja []]
+       ["bel" "Belarusian" belarusian []]
+       ["bem" "Bemba" bemba []]
+       ["ben" "Bengali" bengali []]
+       ["ber" "Berber languages" berber []]
+       ["bho" "Bhojpuri" bhojpuri []]
+       ["bih" "Bihari languages" bihari []]
+       ["bik" "Bikol" bikol []]
+       ["bin" "Bini; Edo" bini [[edo]]]
+       ["bis" "Bislama" bislama []]
+       ["bla" "Siksika" siksika []]
+       ["bnt" "Bantu languages" bantu []]
+       ["bod" "Tibetan" tibetan []]
+       ["bos" "Bosnian" bosnian []]
+       ["bra" "Braj" braj []]
+       ["bre" "Breton" breton []]
+       ["btk" "Batak languages" batak []]
+       ["bua" "Buriat" buriat []]
+       ["bug" "Buginese" buginese []]
+       ["bul" "Bulgarian" bulgarian []]
+       ["byn" "Blin; Bilin" blin [[bilin]]]]]
+
+     [[["cad" "Caddo" caddo []]
+       ["cai" "Central American Indian languages" central_american_indian []]
+       ["car" "Galibi Carib" galibi_carib []]
+       ["cat" "Catalan; Valencian" catalan [[valencian]]]
+       ["cau" "Caucasian languages" caucasian []]
+       ["ceb" "Cebuano" cebuano []]
+       ["cel" "Celtic languages" celtic []]
+       ["ces" "Czech" czech []]
+       ["cha" "Chamorro" chamorro []]
+       ["chb" "Chibcha" chibcha []]
+       ["che" "Chechen" chechen []]
+       ["chg" "Chagatai" chagatai []]
+       ["chk" "Chuukese" chuukese []]
+       ["chm" "Mari" mari []]
+       ["chn" "Chinook jargon" chinook []]
+       ["cho" "Choctaw" choctaw []]
+       ["chp" "Chipewyan; Dene Suline" chipewyan []]
+       ["chr" "Cherokee" cherokee []]
+       ["chu" "Church Slavic; Old Slavonic; Church Slavonic; Old Bulgarian; Old Church Slavonic" church_slavic [[old_slavonic] [church_slavonic] [old_bulgarian] [old_church_slavonic]]]
+       ["chv" "Chuvash" chuvash []]
+       ["chy" "Cheyenne" cheyenne []]
+       ["cmc" "Chamic languages" chamic []]
+       ["cnr" "Montenegrin" montenegrin []]
+       ["cop" "Coptic" coptic []]
+       ["cor" "Cornish" cornish []]
+       ["cos" "Corsican" corsican []]
+       ["cpe" "Creoles and pidgins, English based" creoles_and_pidgins/english []]
+       ["cpf" "Creoles and pidgins, French-based" creoles_and_pidgins/french []]
+       ["cpp" "Creoles and pidgins, Portuguese-based" creoles_and_pidgins/portuguese []]
+       ["cre" "Cree" cree []]
+       ["crh" "Crimean Tatar; Crimean Turkish" crimean []]
+       ["crp" "Creoles and pidgins" creoles_and_pidgins []]
+       ["csb" "Kashubian" kashubian []]
+       ["cus" "Cushitic languages" cushitic []]
+       ["cym" "Welsh" welsh []]]]
+     
+     [[["dak" "Dakota" dakota []]
+       ["dan" "Danish" danish []]
+       ["dar" "Dargwa" dargwa []]
+       ["day" "Land Dayak languages" land_dayak []]
+       ["del" "Delaware" delaware []]
+       ["den" "Slave (Athapascan)" slavey []]
+       ["deu" "German" german []]
+       ["dgr" "Dogrib" dogrib []]
+       ["din" "Dinka" dinka []]
+       ["div" "Divehi; Dhivehi; Maldivian" dhivehi [[maldivian]]]
+       ["doi" "Dogri" dogri []]
+       ["dra" "Dravidian languages" dravidian []]
+       ["dsb" "Lower Sorbian" lower_sorbian []]
+       ["dua" "Duala" duala []]
+       ["dum" "Middle Dutch (ca. 1050–1350)" middle_dutch []]
+       ["dyu" "Dyula" dyula []]
+       ["dzo" "Dzongkha" dzongkha []]]]
+
+     [[["efi" "Efik" efik []]
+       ["egy" "Ancient Egyptian" egyptian []]
+       ["eka" "Ekajuk" ekajuk []]
+       ["ell" "Modern Greek (1453–)" greek []]
+       ["elx" "Elamite" elamite []]
+       ["eng" "English" english []]
+       ["enm" "Middle English (1100–1500)" middle_english []]
+       ["epo" "Esperanto" esperanto []]
+       ["est" "Estonian" estonian []]
+       ["eus" "Basque" basque []]
+       ["ewe" "Ewe" ewe []]
+       ["ewo" "Ewondo" ewondo []]]]
+
+     [[["fan" "Fang" fang []]
+       ["fao" "Faroese" faroese []]
+       ["fas" "Persian" persian []]
+       ["fat" "Fanti" fanti []]
+       ["fij" "Fijian" fijian []]
+       ["fil" "Filipino; Pilipino" filipino []]
+       ["fin" "Finnish" finnish []]
+       ["fiu" "Finno-Ugrian languages" finno_ugrian []]
+       ["fon" "Fon" fon []]
+       ["fra" "French" french []]
+       ["frm" "Middle French (ca. 1400–1600)" middle_french []]
+       ["fro" "Old French (ca. 842–1400)" old_french []]
+       ["frr" "Northern Frisian" northern_frisian []]
+       ["frs" "Eastern Frisian" eastern_frisian []]
+       ["fry" "Western Frisian" western_frisian []]
+       ["ful" "Fulah" fulah []]
+       ["fur" "Friulian" friulian []]]]
+
+     [[["gaa" "Ga" ga []]
+       ["gay" "Gayo" gayo []]
+       ["gba" "Gbaya" gbaya []]
+       ["gem" "Germanic languages" germanic []]
+       ["gez" "Geez" geez []]
+       ["gil" "Gilbertese" gilbertese []]
+       ["gla" "Gaelic; Scottish Gaelic" gaelic []]
+       ["gle" "Irish" irish []]
+       ["glg" "Galician" galician []]
+       ["glv" "Manx" manx []]
+       ["gmh" "Middle High German (ca. 1050–1500)" middle_high_german []]
+       ["goh" "Old High German (ca. 750–1050)" old_high_german []]
+       ["gon" "Gondi" gondi []]
+       ["gor" "Gorontalo" gorontalo []]
+       ["got" "Gothic" gothic []]
+       ["grb" "Grebo" grebo []]
+       ["grc" "Ancient Greek (to 1453)" ancient_greek []]
+       ["grn" "Guarani" guarani []]
+       ["gsw" "Swiss German; Alemannic; Alsatian" swiss_german [[alemannic] [alsatian]]]
+       ["guj" "Gujarati" gujarati []]
+       ["gwi" "Gwich'in" gwich'in []]]]
+
+     [[["hai" "Haida" haida []]
+       ["hat" "Haitian; Haitian Creole" haitian []]
+       ["hau" "Hausa" hausa []]
+       ["haw" "Hawaiian" hawaiian []]
+       ["heb" "Hebrew" hebrew []]
+       ["her" "Herero" herero []]
+       ["hil" "Hiligaynon" hiligaynon []]
+       ["him" "Himachali languages; Pahari languages" himachali []]
+       ["hin" "Hindi" hindi []]
+       ["hit" "Hittite" hittite []]
+       ["hmn" "Hmong; Mong" hmong []]
+       ["hmo" "Hiri Motu" hiri_motu []]
+       ["hrv" "Croatian" croatian []]
+       ["hsb" "Upper Sorbian" upper_sorbian []]
+       ["hun" "Hungarian" hungarian []]
+       ["hup" "Hupa" hupa []]
+       ["hye" "Armenian" armenian []]]]
+
+     [[["iba" "Iban" iban []]
+       ["ibo" "Igbo" igbo []]
+       ["ido" "Ido" ido []]
+       ["iii" "Sichuan Yi; Nuosu" sichuan_yi [[nuosu]]]
+       ["ijo" "Ijo languages" ijo []]
+       ["iku" "Inuktitut" inuktitut []]
+       ["ile" "Interlingue; Occidental" interlingue []]
+       ["ilo" "Iloko" iloko []]
+       ["ina" "Interlingua (International Auxiliary Language Association)" interlingua []]
+       ["inc" "Indic languages" indic []]
+       ["ind" "Indonesian" indonesian []]
+       ["ine" "Indo-European languages" indo_european []]
+       ["inh" "Ingush" ingush []]
+       ["ipk" "Inupiaq" inupiaq []]
+       ["ira" "Iranian languages" iranian []]
+       ["iro" "Iroquoian languages" iroquoian []]
+       ["isl" "Icelandic" icelandic []]
+       ["ita" "Italian" italian []]]]
+
+     [[["jav" "Javanese" javanese []]
+       ["jbo" "Lojban" lojban []]
+       ["jpn" "Japanese" japanese []]
+       ["jpr" "Judeo-Persian" judeo_persian []]
+       ["jrb" "Judeo-Arabic" judeo_arabic []]]]
+
+     [[["kaa" "Kara-Kalpak" kara_kalpak []]
+       ["kab" "Kabyle" kabyle []]
+       ["kac" "Kachin; Jingpho" kachin [[jingpho]]]
+       ["kal" "Kalaallisut; Greenlandic" kalaallisut [[greenlandic]]]
+       ["kam" "Kamba" kamba []]
+       ["kan" "Kannada" kannada []]
+       ["kar" "Karen languages" karen []]
+       ["kas" "Kashmiri" kashmiri []]
+       ["kat" "Georgian" georgian []]
+       ["kau" "Kanuri" kanuri []]
+       ["kaw" "Kawi" kawi []]
+       ["kaz" "Kazakh" kazakh []]
+       ["kbd" "Kabardian" kabardian []]
+       ["kha" "Khasi" khasi []]
+       ["khi" "Khoisan languages" khoisan []]
+       ["khm" "Central Khmer" central_khmer []]
+       ["kho" "Khotanese; Sakan" khotanese [[sakan]]]
+       ["kik" "Kikuyu; Gikuyu" gikuyu []]
+       ["kin" "Kinyarwanda" kinyarwanda []]
+       ["kir" "Kirghiz; Kyrgyz" kyrgyz []]
+       ["kmb" "Kimbundu" kimbundu []]
+       ["kok" "Konkani" konkani []]
+       ["kom" "Komi" komi []]
+       ["kon" "Kongo" kongo []]
+       ["kor" "Korean" korean []]
+       ["kos" "Kosraean" kosraean []]
+       ["kpe" "Kpelle" kpelle []]
+       ["krc" "Karachay-Balkar" karachay_balkar []]
+       ["krl" "Karelian" karelian []]
+       ["kro" "Kru languages" kru []]
+       ["kru" "Kurukh" kurukh []]
+       ["kua" "Kuanyama; Kwanyama" kwanyama []]
+       ["kum" "Kumyk" kumyk []]
+       ["kur" "Kurdish" kurdish []]
+       ["kut" "Kutenai" kutenai []]]]
+
+     [[["lad" "Ladino" ladino []]
+       ["lah" "Lahnda" lahnda []]
+       ["lam" "Lamba" lamba []]
+       ["lao" "Lao" lao []]
+       ["lat" "Latin" latin []]
+       ["lav" "Latvian" latvian []]
+       ["lez" "Lezghian" lezghian []]
+       ["lim" "Limburgan; Limburger; Limburgish" limburgan []]
+       ["lin" "Lingala" lingala []]
+       ["lit" "Lithuanian" lithuanian []]
+       ["lol" "Mongo" mongo []]
+       ["loz" "Lozi" lozi []]
+       ["ltz" "Luxembourgish; Letzeburgesch" luxembourgish []]
+       ["lua" "Luba-Lulua" luba_lulua []]
+       ["lub" "Luba-Katanga" luba_katanga []]
+       ["lug" "Ganda" ganda []]
+       ["lui" "Luiseno" luiseno []]
+       ["lun" "Lunda" lunda []]
+       ["luo" "Luo (Kenya and Tanzania)" luo []]
+       ["lus" "Lushai" lushai []]]]
+
+     [[["mad" "Madurese" madurese []]
+       ["mag" "Magahi" magahi []]
+       ["mah" "Marshallese" marshallese []]
+       ["mai" "Maithili" maithili []]
+       ["mak" "Makasar" makasar []]
+       ["mal" "Malayalam" malayalam []]
+       ["man" "Mandingo" mandingo []]
+       ["map" "Austronesian languages" austronesian []]
+       ["mar" "Marathi" marathi []]
+       ["mas" "Masai" masai []]
+       ["mdf" "Moksha" moksha []]
+       ["mdr" "Mandar" mandar []]
+       ["men" "Mende" mende []]
+       ["mga" "Middle Irish (900–1200)" middle_irish []]
+       ["mic" "Mi'kmaq; Micmac" mi'kmaq [[micmac]]]
+       ["min" "Minangkabau" minangkabau []]
+       ["mkd" "Macedonian" macedonian []]
+       ["mkh" "Mon-Khmer languages" mon_khmer []]
+       ["mlg" "Malagasy" malagasy []]
+       ["mlt" "Maltese" maltese []]
+       ["mnc" "Manchu" manchu []]
+       ["mni" "Manipuri" manipuri []]
+       ["mno" "Manobo languages" manobo []]
+       ["moh" "Mohawk" mohawk []]
+       ["mon" "Mongolian" mongolian []]
+       ["mos" "Mossi" mossi []]
+       ["mri" "Maori" maori []]
+       ["msa" "Malay" malay []]
+       ["mun" "Munda languages" munda []]
+       ["mus" "Creek" creek []]
+       ["mwl" "Mirandese" mirandese []]
+       ["mwr" "Marwari" marwari []]
+       ["mya" "Burmese" burmese []]
+       ["myn" "Mayan languages" mayan []]
+       ["myv" "Erzya" erzya []]]]
+
+     [[["nah" "Nahuatl languages" nahuatl []]
+       ["nai" "North American Indian languages" north_american_indian []]
+       ["nap" "Neapolitan" neapolitan []]
+       ["nau" "Nauru" nauru []]
+       ["nav" "Navajo; Navaho" navajo []]
+       ["nbl" "South Ndebele" south_ndebele []]
+       ["nde" "North Ndebele" north_ndebele []]
+       ["ndo" "Ndonga" ndonga []]
+       ["nds" "Low German; Low Saxon" low_german []]
+       ["nep" "Nepali" nepali []]
+       ["new" "Nepal Bhasa; Newari" newari [[nepal_bhasa]]]
+       ["nia" "Nias" nias []]
+       ["nic" "Niger-Kordofanian languages" niger_kordofanian []]
+       ["niu" "Niuean" niuean []]
+       ["nld" "Dutch; Flemish" dutch [[flemish]]]
+       ["nno" "Norwegian Nynorsk" nynorsk []]
+       ["nob" "Norwegian Bokmål" bokmal []]
+       ["nog" "Nogai" nogai []]
+       ["non" "Old Norse" old_norse []]
+       ["nor" "Norwegian" norwegian []]
+       ["nqo" "N'Ko" n'ko []]
+       ["nso" "Pedi; Sepedi; Northern Sotho" northern_sotho [[pedi] [sepedi]]]
+       ["nub" "Nubian languages" nubian []]
+       ["nwc" "Classical Newari; Old Newari; Classical Nepal Bhasa" old_newari [[classical_newari] [classical_nepal_bhasa]]]
+       ["nya" "Chichewa; Chewa; Nyanja" nyanja [[chichewa] [chewa]]]
+       ["nym" "Nyamwezi" nyamwezi []]
+       ["nyn" "Nyankole" nyankole []]
+       ["nyo" "Nyoro" nyoro []]
+       ["nzi" "Nzima" nzima []]]]
+
+     [[["oci" "Occitan (post 1500); Provençal" occitan [[provencal]]]
+       ["oji" "Ojibwa" ojibwa []]
+       ["ori" "Oriya" oriya []]
+       ["orm" "Oromo" oromo []]
+       ["osa" "Osage" osage []]
+       ["oss" "Ossetian; Ossetic" ossetic []]
+       ["ota" "Ottoman Turkish (1500–1928)" ottoman_turkish []]
+       ["oto" "Otomian languages" otomian []]]]
+
+     [[["paa" "Papuan languages" papuan []]
+       ["pag" "Pangasinan" pangasinan []]
+       ["pal" "Pahlavi" pahlavi []]
+       ["pam" "Pampanga; Kapampangan" pampanga [[kapampangan]]]
+       ["pan" "Panjabi; Punjabi" punjabi []]
+       ["pap" "Papiamento" papiamento []]
+       ["pau" "Palauan" palauan []]
+       ["peo" "Old Persian (ca. 600–400 B.C.)" old_persian []]
+       ["phi" "Philippine languages" philippine []]
+       ["phn" "Phoenician" phoenician []]
+       ["pli" "Pali" pali []]
+       ["pol" "Polish" polish []]
+       ["pon" "Pohnpeian" pohnpeian []]
+       ["por" "Portuguese" portuguese []]
+       ["pra" "Prakrit languages" prakrit []]
+       ["pro" "Old Provençal (to 1500); Old Occitan (to 1500)" old_provencal []]
+       ["pus" "Pushto; Pashto" pashto []]]]
+
+     [[["que" "Quechua" quechua []]]]
+
+     [[["raj" "Rajasthani" rajasthani []]
+       ["rap" "Rapanui" rapanui []]
+       ["rar" "Rarotongan; Cook Islands Maori" rarotongan [[cook_islands_maori]]]
+       ["roa" "Romance languages" romance []]
+       ["roh" "Romansh" romansh []]
+       ["rom" "Romany" romany []]
+       ["ron" "Romanian; Moldavian; Moldovan" romanian [[moldavian] [moldovan]]]
+       ["run" "Rundi" rundi []]
+       ["rup" "Aromanian; Arumanian; Macedo-Romanian" aromanian [[arumanian] [macedo_romanian]]]
+       ["rus" "Russian" russian []]]]
+
+     [[["sad" "Sandawe" sandawe []]
+       ["sag" "Sango" sango []]
+       ["sah" "Yakut" yakut []]
+       ["sai" "South American Indian (Other)" south_american_indian []]
+       ["sal" "Salishan languages" salishan []]
+       ["sam" "Samaritan Aramaic" samaritan_aramaic []]
+       ["san" "Sanskrit" sanskrit []]
+       ["sas" "Sasak" sasak []]
+       ["sat" "Santali" santali []]
+       ["scn" "Sicilian" sicilian []]
+       ["sco" "Scots" scots []]
+       ["sel" "Selkup" selkup []]
+       ["sem" "Semitic languages" semitic []]
+       ["sga" "Old Irish (to 900)" old_irish []]
+       ["sgn" "Sign Languages" sign []]
+       ["shn" "Shan" shan []]
+       ["sid" "Sidamo" sidamo []]
+       ["sin" "Sinhala; Sinhalese" sinhalese []]
+       ["sio" "Siouan languages" siouan []]
+       ["sit" "Sino-Tibetan languages" sino_tibetan []]
+       ["sla" "Slavic languages" slavic []]
+       ["slk" "Slovak" slovak []]
+       ["slv" "Slovenian" slovenian []]
+       ["sma" "Southern Sami" southern_sami []]
+       ["sme" "Northern Sami" northern_sami []]
+       ["smi" "Sami languages" sami []]
+       ["smj" "Lule Sami" lule []]
+       ["smn" "Inari Sami" inari []]
+       ["smo" "Samoan" samoan []]
+       ["sms" "Skolt Sami" skolt_sami []]
+       ["sna" "Shona" shona []]
+       ["snd" "Sindhi" sindhi []]
+       ["snk" "Soninke" soninke []]
+       ["sog" "Sogdian" sogdian []]
+       ["som" "Somali" somali []]
+       ["son" "Songhai languages" songhai []]
+       ["sot" "Southern Sotho" southern_sotho []]
+       ["spa" "Spanish; Castilian" spanish [[castilian]]]
+       ["sqi" "Albanian" albanian []]
+       ["srd" "Sardinian" sardinian []]
+       ["srn" "Sranan Tongo" sranan_tongo []]
+       ["srp" "Serbian" serbian []]
+       ["srr" "Serer" serer []]
+       ["ssa" "Nilo-Saharan languages" nilo_saharan []]
+       ["ssw" "Swati" swati []]
+       ["suk" "Sukuma" sukuma []]
+       ["sun" "Sundanese" sundanese []]
+       ["sus" "Susu" susu []]
+       ["sux" "Sumerian" sumerian []]
+       ["swa" "Swahili" swahili []]
+       ["swe" "Swedish" swedish []]
+       ["syc" "Classical Syriac" classical_syriac []]
+       ["syr" "Syriac" syriac []]]]
+
+     [[["tah" "Tahitian" tahitian []]
+       ["tai" "Tai languages" tai []]
+       ["tam" "Tamil" tamil []]
+       ["tat" "Tatar" tatar []]
+       ["tel" "Telugu" telugu []]
+       ["tem" "Timne" timne []]
+       ["ter" "Tereno" tereno []]
+       ["tet" "Tetum" tetum []]
+       ["tgk" "Tajik" tajik []]
+       ["tgl" "Tagalog" tagalog []]
+       ["tha" "Thai" thai []]
+       ["tig" "Tigre" tigre []]
+       ["tir" "Tigrinya" tigrinya []]
+       ["tiv" "Tiv" tiv []]
+       ["tkl" "Tokelau" tokelau []]
+       ["tlh" "Klingon; tlhIngan-Hol" klingon []]
+       ["tli" "Tlingit" tlingit []]
+       ["tmh" "Tamashek" tamashek []]
+       ["tog" "Tonga (Nyasa)" tonga []]
+       ["ton" "Tonga (Tonga Islands)" tongan []]
+       ["tpi" "Tok Pisin" tok_pisin []]
+       ["tsi" "Tsimshian" tsimshian []]
+       ["tsn" "Tswana" tswana []]
+       ["tso" "Tsonga" tsonga []]
+       ["tuk" "Turkmen" turkmen []]
+       ["tum" "Tumbuka" tumbuka []]
+       ["tup" "Tupi languages" tupi []]
+       ["tur" "Turkish" turkish []]
+       ["tut" "Altaic languages" altaic []]
+       ["tvl" "Tuvalu" tuvalu []]
+       ["twi" "Twi" twi []]
+       ["tyv" "Tuvinian" tuvinian []]]]
+
+     [[["udm" "Udmurt" udmurt []]
+       ["uga" "Ugaritic" ugaritic []]
+       ["uig" "Uighur; Uyghur" uyghur []]
+       ["ukr" "Ukrainian" ukrainian []]
+       ["umb" "Umbundu" umbundu []]
+       ["urd" "Urdu" urdu []]
+       ["uzb" "Uzbek" uzbek []]]]
+
+     [[["vai" "Vai" vai []]
+       ["ven" "Venda" venda []]
+       ["vie" "Vietnamese" vietnamese []]
+       ["vol" "Volapük" volapük []]
+       ["vot" "Votic" votic []]]]
+
+     [[["wak" "Wakashan languages" wakashan []]
+       ["wal" "Wolaitta; Wolaytta" walamo []]
+       ["war" "Waray" waray []]
+       ["was" "Washo" washo []]
+       ["wen" "Sorbian languages" sorbian []]
+       ["wln" "Walloon" walloon []]
+       ["wol" "Wolof" wolof []]]]
+
+     [[["xal" "Kalmyk; Oirat" kalmyk [[oirat]]]
+       ["xho" "Xhosa" xhosa []]]]
+
+     [[["yao" "Yao" yao []]
+       ["yap" "Yapese" yapese []]
+       ["yid" "Yiddish" yiddish []]
+       ["yor" "Yoruba" yoruba []]
+       ["ypk" "Yupik languages" yupik []]]]
+
+     [[["zap" "Zapotec" zapotec []]
+       ["zbl" "Blissymbols; Blissymbolics; Bliss" blissymbols []]
+       ["zen" "Zenaga" zenaga []]
+       ["zgh" "Standard Moroccan Tamazight" standard_moroccan_tamazight []]
+       ["zha" "Zhuang; Chuang" zhuang []]
+       ["zho" "Chinese" chinese []]
+       ["znd" "Zande languages" zande []]
+       ["zul" "Zulu" zulu []]
+       ["zun" "Zuni" zuni []]
+       ["zza" "Zaza; Dimili; Dimli; Kirdki; Kirmanjki; Zazaki" zaza [[dimili] [dimli] [kirdki] [kirmanjki] [zazaki]]]]])
+
+   (implementation: .public equivalence
+     (Equivalence Language)
+     
+     (def: (= reference sample)
+       (same? reference sample)))
+
+   (implementation: .public hash
+     (Hash Language)
+     
+     (def: &equivalence
+       ..equivalence)
+     
+     (def: hash
+       (|>> ..code
+            (\ text.hash hash))))]
   )
diff --git a/stdlib/source/library/lux/locale/territory.lux b/stdlib/source/library/lux/locale/territory.lux
index 834828075..ded9f2110 100644
--- a/stdlib/source/library/lux/locale/territory.lux
+++ b/stdlib/source/library/lux/locale/territory.lux
@@ -13,303 +13,301 @@
 
 ... https://en.wikipedia.org/wiki/ISO_3166-1
 (abstract: .public Territory
-  {}
-
   (Record
    [#name Text
     #short Text
     #long Text
     #code Nat])
 
-  (template [  ]
-    [(def: .public 
-       (-> Territory )
-       (|>> :representation
-            (value@ )))]
+  [(template [  ]
+     [(def: .public 
+        (-> Territory )
+        (|>> :representation
+             (value@ )))]
 
-    [name         #name  Text]
-    [short_code   #short Text]
-    [long_code    #long  Text]
-    [numeric_code #code  Nat]
-    )
+     [name         #name  Text]
+     [short_code   #short Text]
+     [long_code    #long  Text]
+     [numeric_code #code  Nat]
+     )
 
-  (template [    
+] - [(def: .public
- Territory - (:abstraction [#name - #short - #long - #code ])) + (template [
+] + [(def: .public
+ Territory + (:abstraction [#name + #short + #long + #code ])) - (`` (template [] - [(def: .public Territory
)] + (`` (template [] + [(def: .public Territory
)] - (~~ (template.spliced +))))] + (~~ (template.spliced +))))] - ["AF" "AFG" 004 "Afghanistan" afghanistan []] - ["AX" "ALA" 248 "Åland Islands" aland_islands []] - ["AL" "ALB" 008 "Albania" albania []] - ["DZ" "DZA" 012 "Algeria" algeria []] - ["AS" "ASM" 016 "American Samoa" american_samoa []] - ["AD" "AND" 020 "Andorra" andorra []] - ["AO" "AGO" 024 "Angola" angola []] - ["AI" "AIA" 660 "Anguilla" anguilla []] - ["AQ" "ATA" 010 "Antarctica" antarctica []] - ["AG" "ATG" 028 "Antigua and Barbuda" antigua [[barbuda]]] - ["AR" "ARG" 032 "Argentina" argentina []] - ["AM" "ARM" 051 "Armenia" armenia []] - ["AW" "ABW" 533 "Aruba" aruba []] - ["AU" "AUS" 036 "Australia" australia []] - ["AT" "AUT" 040 "Austria" austria []] - ["AZ" "AZE" 031 "Azerbaijan" azerbaijan []] - ["BS" "BHS" 044 "The Bahamas" the_bahamas []] - ["BH" "BHR" 048 "Bahrain" bahrain []] - ["BD" "BGD" 050 "Bangladesh" bangladesh []] - ["BB" "BRB" 052 "Barbados" barbados []] - ["BY" "BLR" 112 "Belarus" belarus []] - ["BE" "BEL" 056 "Belgium" belgium []] - ["BZ" "BLZ" 084 "Belize" belize []] - ["BJ" "BEN" 204 "Benin" benin []] - ["BM" "BMU" 060 "Bermuda" bermuda []] - ["BT" "BTN" 064 "Bhutan" bhutan []] - ["BO" "BOL" 068 "Bolivia" bolivia []] - ["BQ" "BES" 535 "Bonaire, Sint Eustatius and Saba" bonaire [[sint_eustatius] [saba]]] - ["BA" "BIH" 070 "Bosnia and Herzegovina" bosnia [[herzegovina]]] - ["BW" "BWA" 072 "Botswana" botswana []] - ["BV" "BVT" 074 "Bouvet Island" bouvet_island []] - ["BR" "BRA" 076 "Brazil" brazil []] - ["IO" "IOT" 086 "British Indian Ocean Territory" british_indian_ocean_territory []] - ["BN" "BRN" 096 "Brunei Darussalam" brunei_darussalam []] - ["BG" "BGR" 100 "Bulgaria" bulgaria []] - ["BF" "BFA" 854 "Burkina Faso" burkina_faso []] - ["BI" "BDI" 108 "Burundi" burundi []] - ["CV" "CPV" 132 "Cape Verde" cape_verde []] - ["KH" "KHM" 116 "Cambodia" cambodia []] - ["CM" "CMR" 120 "Cameroon" cameroon []] - ["CA" "CAN" 124 "Canada" canada []] - ["KY" "CYM" 136 "Cayman Islands" cayman_islands []] - ["CF" "CAF" 140 "Central African Republic" central_african_republic []] - ["TD" "TCD" 148 "Chad" chad []] - ["CL" "CHL" 152 "Chile" chile []] - ["CN" "CHN" 156 "China" china []] - ["CX" "CXR" 162 "Christmas Island" christmas_island []] - ["CC" "CCK" 166 "Cocos (Keeling) Islands" cocos_islands []] - ["CO" "COL" 170 "Colombia" colombia []] - ["KM" "COM" 174 "Comoros" comoros []] - ["CG" "COG" 178 "Congo" congo []] - ["CD" "COD" 180 "Democratic Republic of the Congo" democratic_republic_of_the_congo []] - ["CK" "COK" 184 "Cook Islands" cook_islands []] - ["CR" "CRI" 188 "Costa Rica" costa_rica []] - ["CI" "CIV" 384 "Ivory Coast" ivory_coast []] - ["HR" "HRV" 191 "Croatia" croatia []] - ["CU" "CUB" 192 "Cuba" cuba []] - ["CW" "CUW" 531 "Curacao" curacao []] - ["CY" "CYP" 196 "Cyprus" cyprus []] - ["CZ" "CZE" 203 "Czech Republic" czech_republic []] - ["DK" "DNK" 208 "Denmark" denmark []] - ["DJ" "DJI" 262 "Djibouti" djibouti []] - ["DM" "DMA" 212 "Dominica" dominica []] - ["DO" "DOM" 214 "Dominican Republic" dominican_republic []] - ["EC" "ECU" 218 "Ecuador" ecuador []] - ["EG" "EGY" 818 "Egypt" egypt []] - ["SV" "SLV" 222 "El Salvador" el_salvador []] - ["GQ" "GNQ" 226 "Equatorial Guinea" equatorial_guinea []] - ["ER" "ERI" 232 "Eritrea" eritrea []] - ["EE" "EST" 233 "Estonia" estonia []] - ["SZ" "SWZ" 748 "Eswatini" eswatini []] - ["ET" "ETH" 231 "Ethiopia" ethiopia []] - ["FK" "FLK" 238 "Falkland Islands" falkland_islands []] - ["FO" "FRO" 234 "Faroe Islands" faroe_islands []] - ["FJ" "FJI" 242 "Fiji" fiji []] - ["FI" "FIN" 246 "Finland" finland []] - ["FR" "FRA" 250 "France" france []] - ["GF" "GUF" 254 "French Guiana" french_guiana []] - ["PF" "PYF" 258 "French Polynesia" french_polynesia []] - ["TF" "ATF" 260 "French Southern Territories" french_southern_territories []] - ["GA" "GAB" 266 "Gabon" gabon []] - ["GM" "GMB" 270 "The Gambia" the_gambia []] - ["GE" "GEO" 268 "Georgia" georgia []] - ["DE" "DEU" 276 "Germany" germany []] - ["GH" "GHA" 288 "Ghana" ghana []] - ["GI" "GIB" 292 "Gibraltar" gibraltar []] - ["GR" "GRC" 300 "Greece" greece []] - ["GL" "GRL" 304 "Greenland" greenland []] - ["GD" "GRD" 308 "Grenada" grenada []] - ["GP" "GLP" 312 "Guadeloupe" guadeloupe []] - ["GU" "GUM" 316 "Guam" guam []] - ["GT" "GTM" 320 "Guatemala" guatemala []] - ["GG" "GGY" 831 "Guernsey" guernsey []] - ["GN" "GIN" 324 "Guinea" guinea []] - ["GW" "GNB" 624 "Guinea-Bissau" guinea_bissau []] - ["GY" "GUY" 328 "Guyana" guyana []] - ["HT" "HTI" 332 "Haiti" haiti []] - ["HM" "HMD" 334 "Heard Island and McDonald Islands" heard_island [[mcdonald_islands]]] - ["VA" "VAT" 336 "Vatican City" vatican_city []] - ["HN" "HND" 340 "Honduras" honduras []] - ["HK" "HKG" 344 "Hong Kong" hong_kong []] - ["HU" "HUN" 348 "Hungary" hungary []] - ["IS" "ISL" 352 "Iceland" iceland []] - ["IN" "IND" 356 "India" india []] - ["ID" "IDN" 360 "Indonesia" indonesia []] - ["IR" "IRN" 364 "Iran" iran []] - ["IQ" "IRQ" 368 "Iraq" iraq []] - ["IE" "IRL" 372 "Ireland" ireland []] - ["IM" "IMN" 833 "Isle of Man" isle_of_man []] - ["IL" "ISR" 376 "Israel" israel []] - ["IT" "ITA" 380 "Italy" italy []] - ["JM" "JAM" 388 "Jamaica" jamaica []] - ["JP" "JPN" 392 "Japan" japan []] - ["JE" "JEY" 832 "Jersey" jersey []] - ["JO" "JOR" 400 "Jordan" jordan []] - ["KZ" "KAZ" 398 "Kazakhstan" kazakhstan []] - ["KE" "KEN" 404 "Kenya" kenya []] - ["KI" "KIR" 296 "Kiribati" kiribati []] - ["KP" "PRK" 408 "North Korea" north_korea []] - ["KR" "KOR" 410 "South Korea" south_korea []] - ["KW" "KWT" 414 "Kuwait" kuwait []] - ["KG" "KGZ" 417 "Kyrgyzstan" kyrgyzstan []] - ["LA" "LAO" 418 "Laos" laos []] - ["LV" "LVA" 428 "Latvia" latvia []] - ["LB" "LBN" 422 "Lebanon" lebanon []] - ["LS" "LSO" 426 "Lesotho" lesotho []] - ["LR" "LBR" 430 "Liberia" liberia []] - ["LY" "LBY" 434 "Libya" libya []] - ["LI" "LIE" 438 "Liechtenstein" liechtenstein []] - ["LT" "LTU" 440 "Lithuania" lithuania []] - ["LU" "LUX" 442 "Luxembourg" luxembourg []] - ["MO" "MAC" 446 "Macau" macau []] - ["MK" "MKD" 807 "Macedonia" macedonia []] - ["MG" "MDG" 450 "Madagascar" madagascar []] - ["MW" "MWI" 454 "Malawi" malawi []] - ["MY" "MYS" 458 "Malaysia" malaysia []] - ["MV" "MDV" 462 "Maldives" maldives []] - ["ML" "MLI" 466 "Mali" mali []] - ["MT" "MLT" 470 "Malta" malta []] - ["MH" "MHL" 584 "Marshall Islands" marshall_islands []] - ["MQ" "MTQ" 474 "Martinique" martinique []] - ["MR" "MRT" 478 "Mauritania" mauritania []] - ["MU" "MUS" 480 "Mauritius" mauritius []] - ["YT" "MYT" 175 "Mayotte" mayotte []] - ["MX" "MEX" 484 "Mexico" mexico []] - ["FM" "FSM" 583 "Micronesia" micronesia []] - ["MD" "MDA" 498 "Moldova" moldova []] - ["MC" "MCO" 492 "Monaco" monaco []] - ["MN" "MNG" 496 "Mongolia" mongolia []] - ["ME" "MNE" 499 "Montenegro" montenegro []] - ["MS" "MSR" 500 "Montserrat" montserrat []] - ["MA" "MAR" 504 "Morocco" morocco []] - ["MZ" "MOZ" 508 "Mozambique" mozambique []] - ["MM" "MMR" 104 "Myanmar" myanmar []] - ["NA" "NAM" 516 "Namibia" namibia []] - ["NR" "NRU" 520 "Nauru" nauru []] - ["NP" "NPL" 524 "Nepal" nepal []] - ["NL" "NLD" 528 "Netherlands" netherlands []] - ["NC" "NCL" 540 "New Caledonia" new_caledonia []] - ["NZ" "NZL" 554 "New Zealand" new_zealand []] - ["NI" "NIC" 558 "Nicaragua" nicaragua []] - ["NE" "NER" 562 "Niger" niger []] - ["NG" "NGA" 566 "Nigeria" nigeria []] - ["NU" "NIU" 570 "Niue" niue []] - ["NF" "NFK" 574 "Norfolk Island" norfolk_island []] - ["MP" "MNP" 580 "Northern Mariana Islands" northern_mariana_islands []] - ["NO" "NOR" 578 "Norway" norway []] - ["OM" "OMN" 512 "Oman" oman []] - ["PK" "PAK" 586 "Pakistan" pakistan []] - ["PW" "PLW" 585 "Palau" palau []] - ["PS" "PSE" 275 "Palestine" palestine []] - ["PA" "PAN" 591 "Panama" panama []] - ["PG" "PNG" 598 "Papua New Guinea" papua_new_guinea []] - ["PY" "PRY" 600 "Paraguay" paraguay []] - ["PE" "PER" 604 "Peru" peru []] - ["PH" "PHL" 608 "Philippines" philippines []] - ["PN" "PCN" 612 "Pitcairn Islands" pitcairn_islands []] - ["PL" "POL" 616 "Poland" poland []] - ["PT" "PRT" 620 "Portugal" portugal []] - ["PR" "PRI" 630 "Puerto Rico" puerto_rico []] - ["QA" "QAT" 634 "Qatar" qatar []] - ["RE" "REU" 638 "Reunion" reunion []] - ["RO" "ROU" 642 "Romania" romania []] - ["RU" "RUS" 643 "Russia" russia []] - ["RW" "RWA" 646 "Rwanda" rwanda []] - ["BL" "BLM" 652 "Saint Barthélemy" saint_barthelemy []] - ["SH" "SHN" 654 "Saint Helena, Ascension and Tristan da Cunha" saint_helena [[ascension] [tristan_da_cunha]]] - ["KN" "KNA" 659 "Saint Kitts and Nevis" saint_kitts [[nevis]]] - ["LC" "LCA" 662 "Saint Lucia" saint_lucia []] - ["MF" "MAF" 663 "Saint Martin" saint_martin []] - ["PM" "SPM" 666 "Saint Pierre and Miquelon" saint_pierre [[miquelon]]] - ["VC" "VCT" 670 "Saint Vincent and the Grenadines" saint_vincent [[the_grenadines]]] - ["WS" "WSM" 882 "Samoa" samoa []] - ["SM" "SMR" 674 "San Marino" san_marino []] - ["ST" "STP" 678 "Sao Tome and Principe" sao_tome [[principe]]] - ["SA" "SAU" 682 "Saudi Arabia" saudi_arabia []] - ["SN" "SEN" 686 "Senegal" senegal []] - ["RS" "SRB" 688 "Serbia" serbia []] - ["SC" "SYC" 690 "Seychelles" seychelles []] - ["SL" "SLE" 694 "Sierra Leone" sierra_leone []] - ["SG" "SGP" 702 "Singapore" singapore []] - ["SX" "SXM" 534 "Sint Maarten" sint_maarten []] - ["SK" "SVK" 703 "Slovakia" slovakia []] - ["SI" "SVN" 705 "Slovenia" slovenia []] - ["SB" "SLB" 090 "Solomon Islands" solomon_islands []] - ["SO" "SOM" 706 "Somalia" somalia []] - ["ZA" "ZAF" 710 "South Africa" south_africa []] - ["GS" "SGS" 239 "South Georgia and the South Sandwich Islands" south_georgia [[south_sandwich_islands]]] - ["SS" "SSD" 728 "South Sudan" south_sudan []] - ["ES" "ESP" 724 "Spain" spain []] - ["LK" "LKA" 144 "Sri Lanka" sri_lanka []] - ["SD" "SDN" 729 "Sudan" sudan []] - ["SR" "SUR" 740 "Suriname" suriname []] - ["SJ" "SJM" 744 "Svalbard and Jan Mayen" svalbard [[jan_mayen]]] - ["SE" "SWE" 752 "Sweden" sweden []] - ["CH" "CHE" 756 "Switzerland" switzerland []] - ["SY" "SYR" 760 "Syria" syria []] - ["TW" "TWN" 158 "Taiwan" taiwan []] - ["TJ" "TJK" 762 "Tajikistan" tajikistan []] - ["TZ" "TZA" 834 "Tanzania" tanzania []] - ["TH" "THA" 764 "Thailand" thailand []] - ["TL" "TLS" 626 "East Timor" east_timor []] - ["TG" "TGO" 768 "Togo" togo []] - ["TK" "TKL" 772 "Tokelau" tokelau []] - ["TO" "TON" 776 "Tonga" tonga []] - ["TT" "TTO" 780 "Trinidad and Tobago" trinidad [[tobago]]] - ["TN" "TUN" 788 "Tunisia" tunisia []] - ["TR" "TUR" 792 "Turkey" turkey []] - ["TM" "TKM" 795 "Turkmenistan" turkmenistan []] - ["TC" "TCA" 796 "Turks and Caicos Islands" turks [[caicos_islands]]] - ["TV" "TUV" 798 "Tuvalu" tuvalu []] - ["UG" "UGA" 800 "Uganda" uganda []] - ["UA" "UKR" 804 "Ukraine" ukraine []] - ["AE" "ARE" 784 "United Arab Emirates" united_arab_emirates []] - ["GB" "GBR" 826 "United Kingdom of Great Britain and Northern Ireland" united_kingdom [[northern_ireland]]] - ["US" "USA" 840 "United States of America" united_states_of_america []] - ["UM" "UMI" 581 "United States Minor Outlying Islands" united_states_minor_outlying_islands []] - ["UY" "URY" 858 "Uruguay" uruguay []] - ["UZ" "UZB" 860 "Uzbekistan" uzbekistan []] - ["VU" "VUT" 548 "Vanuatu" vanuatu []] - ["VE" "VEN" 862 "Venezuela" venezuela []] - ["VN" "VNM" 704 "Vietnam" vietnam []] - ["VG" "VGB" 092 "British Virgin Islands" british_virgin_islands []] - ["VI" "VIR" 850 "United States Virgin Islands" united_states_virgin_islands []] - ["WF" "WLF" 876 "Wallis and Futuna" wallis [[futuna]]] - ["EH" "ESH" 732 "Western Sahara" western_sahara []] - ["YE" "YEM" 887 "Yemen" yemen []] - ["ZM" "ZMB" 894 "Zambia" zambia []] - ["ZW" "ZWE" 716 "Zimbabwe" zimbabwe []] - ) + ["AF" "AFG" 004 "Afghanistan" afghanistan []] + ["AX" "ALA" 248 "Åland Islands" aland_islands []] + ["AL" "ALB" 008 "Albania" albania []] + ["DZ" "DZA" 012 "Algeria" algeria []] + ["AS" "ASM" 016 "American Samoa" american_samoa []] + ["AD" "AND" 020 "Andorra" andorra []] + ["AO" "AGO" 024 "Angola" angola []] + ["AI" "AIA" 660 "Anguilla" anguilla []] + ["AQ" "ATA" 010 "Antarctica" antarctica []] + ["AG" "ATG" 028 "Antigua and Barbuda" antigua [[barbuda]]] + ["AR" "ARG" 032 "Argentina" argentina []] + ["AM" "ARM" 051 "Armenia" armenia []] + ["AW" "ABW" 533 "Aruba" aruba []] + ["AU" "AUS" 036 "Australia" australia []] + ["AT" "AUT" 040 "Austria" austria []] + ["AZ" "AZE" 031 "Azerbaijan" azerbaijan []] + ["BS" "BHS" 044 "The Bahamas" the_bahamas []] + ["BH" "BHR" 048 "Bahrain" bahrain []] + ["BD" "BGD" 050 "Bangladesh" bangladesh []] + ["BB" "BRB" 052 "Barbados" barbados []] + ["BY" "BLR" 112 "Belarus" belarus []] + ["BE" "BEL" 056 "Belgium" belgium []] + ["BZ" "BLZ" 084 "Belize" belize []] + ["BJ" "BEN" 204 "Benin" benin []] + ["BM" "BMU" 060 "Bermuda" bermuda []] + ["BT" "BTN" 064 "Bhutan" bhutan []] + ["BO" "BOL" 068 "Bolivia" bolivia []] + ["BQ" "BES" 535 "Bonaire, Sint Eustatius and Saba" bonaire [[sint_eustatius] [saba]]] + ["BA" "BIH" 070 "Bosnia and Herzegovina" bosnia [[herzegovina]]] + ["BW" "BWA" 072 "Botswana" botswana []] + ["BV" "BVT" 074 "Bouvet Island" bouvet_island []] + ["BR" "BRA" 076 "Brazil" brazil []] + ["IO" "IOT" 086 "British Indian Ocean Territory" british_indian_ocean_territory []] + ["BN" "BRN" 096 "Brunei Darussalam" brunei_darussalam []] + ["BG" "BGR" 100 "Bulgaria" bulgaria []] + ["BF" "BFA" 854 "Burkina Faso" burkina_faso []] + ["BI" "BDI" 108 "Burundi" burundi []] + ["CV" "CPV" 132 "Cape Verde" cape_verde []] + ["KH" "KHM" 116 "Cambodia" cambodia []] + ["CM" "CMR" 120 "Cameroon" cameroon []] + ["CA" "CAN" 124 "Canada" canada []] + ["KY" "CYM" 136 "Cayman Islands" cayman_islands []] + ["CF" "CAF" 140 "Central African Republic" central_african_republic []] + ["TD" "TCD" 148 "Chad" chad []] + ["CL" "CHL" 152 "Chile" chile []] + ["CN" "CHN" 156 "China" china []] + ["CX" "CXR" 162 "Christmas Island" christmas_island []] + ["CC" "CCK" 166 "Cocos (Keeling) Islands" cocos_islands []] + ["CO" "COL" 170 "Colombia" colombia []] + ["KM" "COM" 174 "Comoros" comoros []] + ["CG" "COG" 178 "Congo" congo []] + ["CD" "COD" 180 "Democratic Republic of the Congo" democratic_republic_of_the_congo []] + ["CK" "COK" 184 "Cook Islands" cook_islands []] + ["CR" "CRI" 188 "Costa Rica" costa_rica []] + ["CI" "CIV" 384 "Ivory Coast" ivory_coast []] + ["HR" "HRV" 191 "Croatia" croatia []] + ["CU" "CUB" 192 "Cuba" cuba []] + ["CW" "CUW" 531 "Curacao" curacao []] + ["CY" "CYP" 196 "Cyprus" cyprus []] + ["CZ" "CZE" 203 "Czech Republic" czech_republic []] + ["DK" "DNK" 208 "Denmark" denmark []] + ["DJ" "DJI" 262 "Djibouti" djibouti []] + ["DM" "DMA" 212 "Dominica" dominica []] + ["DO" "DOM" 214 "Dominican Republic" dominican_republic []] + ["EC" "ECU" 218 "Ecuador" ecuador []] + ["EG" "EGY" 818 "Egypt" egypt []] + ["SV" "SLV" 222 "El Salvador" el_salvador []] + ["GQ" "GNQ" 226 "Equatorial Guinea" equatorial_guinea []] + ["ER" "ERI" 232 "Eritrea" eritrea []] + ["EE" "EST" 233 "Estonia" estonia []] + ["SZ" "SWZ" 748 "Eswatini" eswatini []] + ["ET" "ETH" 231 "Ethiopia" ethiopia []] + ["FK" "FLK" 238 "Falkland Islands" falkland_islands []] + ["FO" "FRO" 234 "Faroe Islands" faroe_islands []] + ["FJ" "FJI" 242 "Fiji" fiji []] + ["FI" "FIN" 246 "Finland" finland []] + ["FR" "FRA" 250 "France" france []] + ["GF" "GUF" 254 "French Guiana" french_guiana []] + ["PF" "PYF" 258 "French Polynesia" french_polynesia []] + ["TF" "ATF" 260 "French Southern Territories" french_southern_territories []] + ["GA" "GAB" 266 "Gabon" gabon []] + ["GM" "GMB" 270 "The Gambia" the_gambia []] + ["GE" "GEO" 268 "Georgia" georgia []] + ["DE" "DEU" 276 "Germany" germany []] + ["GH" "GHA" 288 "Ghana" ghana []] + ["GI" "GIB" 292 "Gibraltar" gibraltar []] + ["GR" "GRC" 300 "Greece" greece []] + ["GL" "GRL" 304 "Greenland" greenland []] + ["GD" "GRD" 308 "Grenada" grenada []] + ["GP" "GLP" 312 "Guadeloupe" guadeloupe []] + ["GU" "GUM" 316 "Guam" guam []] + ["GT" "GTM" 320 "Guatemala" guatemala []] + ["GG" "GGY" 831 "Guernsey" guernsey []] + ["GN" "GIN" 324 "Guinea" guinea []] + ["GW" "GNB" 624 "Guinea-Bissau" guinea_bissau []] + ["GY" "GUY" 328 "Guyana" guyana []] + ["HT" "HTI" 332 "Haiti" haiti []] + ["HM" "HMD" 334 "Heard Island and McDonald Islands" heard_island [[mcdonald_islands]]] + ["VA" "VAT" 336 "Vatican City" vatican_city []] + ["HN" "HND" 340 "Honduras" honduras []] + ["HK" "HKG" 344 "Hong Kong" hong_kong []] + ["HU" "HUN" 348 "Hungary" hungary []] + ["IS" "ISL" 352 "Iceland" iceland []] + ["IN" "IND" 356 "India" india []] + ["ID" "IDN" 360 "Indonesia" indonesia []] + ["IR" "IRN" 364 "Iran" iran []] + ["IQ" "IRQ" 368 "Iraq" iraq []] + ["IE" "IRL" 372 "Ireland" ireland []] + ["IM" "IMN" 833 "Isle of Man" isle_of_man []] + ["IL" "ISR" 376 "Israel" israel []] + ["IT" "ITA" 380 "Italy" italy []] + ["JM" "JAM" 388 "Jamaica" jamaica []] + ["JP" "JPN" 392 "Japan" japan []] + ["JE" "JEY" 832 "Jersey" jersey []] + ["JO" "JOR" 400 "Jordan" jordan []] + ["KZ" "KAZ" 398 "Kazakhstan" kazakhstan []] + ["KE" "KEN" 404 "Kenya" kenya []] + ["KI" "KIR" 296 "Kiribati" kiribati []] + ["KP" "PRK" 408 "North Korea" north_korea []] + ["KR" "KOR" 410 "South Korea" south_korea []] + ["KW" "KWT" 414 "Kuwait" kuwait []] + ["KG" "KGZ" 417 "Kyrgyzstan" kyrgyzstan []] + ["LA" "LAO" 418 "Laos" laos []] + ["LV" "LVA" 428 "Latvia" latvia []] + ["LB" "LBN" 422 "Lebanon" lebanon []] + ["LS" "LSO" 426 "Lesotho" lesotho []] + ["LR" "LBR" 430 "Liberia" liberia []] + ["LY" "LBY" 434 "Libya" libya []] + ["LI" "LIE" 438 "Liechtenstein" liechtenstein []] + ["LT" "LTU" 440 "Lithuania" lithuania []] + ["LU" "LUX" 442 "Luxembourg" luxembourg []] + ["MO" "MAC" 446 "Macau" macau []] + ["MK" "MKD" 807 "Macedonia" macedonia []] + ["MG" "MDG" 450 "Madagascar" madagascar []] + ["MW" "MWI" 454 "Malawi" malawi []] + ["MY" "MYS" 458 "Malaysia" malaysia []] + ["MV" "MDV" 462 "Maldives" maldives []] + ["ML" "MLI" 466 "Mali" mali []] + ["MT" "MLT" 470 "Malta" malta []] + ["MH" "MHL" 584 "Marshall Islands" marshall_islands []] + ["MQ" "MTQ" 474 "Martinique" martinique []] + ["MR" "MRT" 478 "Mauritania" mauritania []] + ["MU" "MUS" 480 "Mauritius" mauritius []] + ["YT" "MYT" 175 "Mayotte" mayotte []] + ["MX" "MEX" 484 "Mexico" mexico []] + ["FM" "FSM" 583 "Micronesia" micronesia []] + ["MD" "MDA" 498 "Moldova" moldova []] + ["MC" "MCO" 492 "Monaco" monaco []] + ["MN" "MNG" 496 "Mongolia" mongolia []] + ["ME" "MNE" 499 "Montenegro" montenegro []] + ["MS" "MSR" 500 "Montserrat" montserrat []] + ["MA" "MAR" 504 "Morocco" morocco []] + ["MZ" "MOZ" 508 "Mozambique" mozambique []] + ["MM" "MMR" 104 "Myanmar" myanmar []] + ["NA" "NAM" 516 "Namibia" namibia []] + ["NR" "NRU" 520 "Nauru" nauru []] + ["NP" "NPL" 524 "Nepal" nepal []] + ["NL" "NLD" 528 "Netherlands" netherlands []] + ["NC" "NCL" 540 "New Caledonia" new_caledonia []] + ["NZ" "NZL" 554 "New Zealand" new_zealand []] + ["NI" "NIC" 558 "Nicaragua" nicaragua []] + ["NE" "NER" 562 "Niger" niger []] + ["NG" "NGA" 566 "Nigeria" nigeria []] + ["NU" "NIU" 570 "Niue" niue []] + ["NF" "NFK" 574 "Norfolk Island" norfolk_island []] + ["MP" "MNP" 580 "Northern Mariana Islands" northern_mariana_islands []] + ["NO" "NOR" 578 "Norway" norway []] + ["OM" "OMN" 512 "Oman" oman []] + ["PK" "PAK" 586 "Pakistan" pakistan []] + ["PW" "PLW" 585 "Palau" palau []] + ["PS" "PSE" 275 "Palestine" palestine []] + ["PA" "PAN" 591 "Panama" panama []] + ["PG" "PNG" 598 "Papua New Guinea" papua_new_guinea []] + ["PY" "PRY" 600 "Paraguay" paraguay []] + ["PE" "PER" 604 "Peru" peru []] + ["PH" "PHL" 608 "Philippines" philippines []] + ["PN" "PCN" 612 "Pitcairn Islands" pitcairn_islands []] + ["PL" "POL" 616 "Poland" poland []] + ["PT" "PRT" 620 "Portugal" portugal []] + ["PR" "PRI" 630 "Puerto Rico" puerto_rico []] + ["QA" "QAT" 634 "Qatar" qatar []] + ["RE" "REU" 638 "Reunion" reunion []] + ["RO" "ROU" 642 "Romania" romania []] + ["RU" "RUS" 643 "Russia" russia []] + ["RW" "RWA" 646 "Rwanda" rwanda []] + ["BL" "BLM" 652 "Saint Barthélemy" saint_barthelemy []] + ["SH" "SHN" 654 "Saint Helena, Ascension and Tristan da Cunha" saint_helena [[ascension] [tristan_da_cunha]]] + ["KN" "KNA" 659 "Saint Kitts and Nevis" saint_kitts [[nevis]]] + ["LC" "LCA" 662 "Saint Lucia" saint_lucia []] + ["MF" "MAF" 663 "Saint Martin" saint_martin []] + ["PM" "SPM" 666 "Saint Pierre and Miquelon" saint_pierre [[miquelon]]] + ["VC" "VCT" 670 "Saint Vincent and the Grenadines" saint_vincent [[the_grenadines]]] + ["WS" "WSM" 882 "Samoa" samoa []] + ["SM" "SMR" 674 "San Marino" san_marino []] + ["ST" "STP" 678 "Sao Tome and Principe" sao_tome [[principe]]] + ["SA" "SAU" 682 "Saudi Arabia" saudi_arabia []] + ["SN" "SEN" 686 "Senegal" senegal []] + ["RS" "SRB" 688 "Serbia" serbia []] + ["SC" "SYC" 690 "Seychelles" seychelles []] + ["SL" "SLE" 694 "Sierra Leone" sierra_leone []] + ["SG" "SGP" 702 "Singapore" singapore []] + ["SX" "SXM" 534 "Sint Maarten" sint_maarten []] + ["SK" "SVK" 703 "Slovakia" slovakia []] + ["SI" "SVN" 705 "Slovenia" slovenia []] + ["SB" "SLB" 090 "Solomon Islands" solomon_islands []] + ["SO" "SOM" 706 "Somalia" somalia []] + ["ZA" "ZAF" 710 "South Africa" south_africa []] + ["GS" "SGS" 239 "South Georgia and the South Sandwich Islands" south_georgia [[south_sandwich_islands]]] + ["SS" "SSD" 728 "South Sudan" south_sudan []] + ["ES" "ESP" 724 "Spain" spain []] + ["LK" "LKA" 144 "Sri Lanka" sri_lanka []] + ["SD" "SDN" 729 "Sudan" sudan []] + ["SR" "SUR" 740 "Suriname" suriname []] + ["SJ" "SJM" 744 "Svalbard and Jan Mayen" svalbard [[jan_mayen]]] + ["SE" "SWE" 752 "Sweden" sweden []] + ["CH" "CHE" 756 "Switzerland" switzerland []] + ["SY" "SYR" 760 "Syria" syria []] + ["TW" "TWN" 158 "Taiwan" taiwan []] + ["TJ" "TJK" 762 "Tajikistan" tajikistan []] + ["TZ" "TZA" 834 "Tanzania" tanzania []] + ["TH" "THA" 764 "Thailand" thailand []] + ["TL" "TLS" 626 "East Timor" east_timor []] + ["TG" "TGO" 768 "Togo" togo []] + ["TK" "TKL" 772 "Tokelau" tokelau []] + ["TO" "TON" 776 "Tonga" tonga []] + ["TT" "TTO" 780 "Trinidad and Tobago" trinidad [[tobago]]] + ["TN" "TUN" 788 "Tunisia" tunisia []] + ["TR" "TUR" 792 "Turkey" turkey []] + ["TM" "TKM" 795 "Turkmenistan" turkmenistan []] + ["TC" "TCA" 796 "Turks and Caicos Islands" turks [[caicos_islands]]] + ["TV" "TUV" 798 "Tuvalu" tuvalu []] + ["UG" "UGA" 800 "Uganda" uganda []] + ["UA" "UKR" 804 "Ukraine" ukraine []] + ["AE" "ARE" 784 "United Arab Emirates" united_arab_emirates []] + ["GB" "GBR" 826 "United Kingdom of Great Britain and Northern Ireland" united_kingdom [[northern_ireland]]] + ["US" "USA" 840 "United States of America" united_states_of_america []] + ["UM" "UMI" 581 "United States Minor Outlying Islands" united_states_minor_outlying_islands []] + ["UY" "URY" 858 "Uruguay" uruguay []] + ["UZ" "UZB" 860 "Uzbekistan" uzbekistan []] + ["VU" "VUT" 548 "Vanuatu" vanuatu []] + ["VE" "VEN" 862 "Venezuela" venezuela []] + ["VN" "VNM" 704 "Vietnam" vietnam []] + ["VG" "VGB" 092 "British Virgin Islands" british_virgin_islands []] + ["VI" "VIR" 850 "United States Virgin Islands" united_states_virgin_islands []] + ["WF" "WLF" 876 "Wallis and Futuna" wallis [[futuna]]] + ["EH" "ESH" 732 "Western Sahara" western_sahara []] + ["YE" "YEM" 887 "Yemen" yemen []] + ["ZM" "ZMB" 894 "Zambia" zambia []] + ["ZW" "ZWE" 716 "Zimbabwe" zimbabwe []] + ) - (implementation: .public equivalence - (Equivalence Territory) - - (def: (= reference sample) - (same? reference sample))) + (implementation: .public equivalence + (Equivalence Territory) + + (def: (= reference sample) + (same? reference sample))) - (implementation: .public hash - (Hash Territory) - - (def: &equivalence ..equivalence) - - (def: hash - (|>> :representation - (value@ #long) - (\ text.hash hash)))) + (implementation: .public hash + (Hash Territory) + + (def: &equivalence ..equivalence) + + (def: hash + (|>> :representation + (value@ #long) + (\ text.hash hash))))] ) diff --git a/stdlib/source/library/lux/math/modular.lux b/stdlib/source/library/lux/math/modular.lux index bc496557f..a1f8b8bd3 100644 --- a/stdlib/source/library/lux/math/modular.lux +++ b/stdlib/source/library/lux/math/modular.lux @@ -28,118 +28,116 @@ ["[1]" modulus {"+" [Modulus]}]]) (abstract: .public (Mod m) - {} - (Record [#modulus (Modulus m) #value Int]) - (def: .public (modular modulus value) - (All (_ %) (-> (Modulus %) Int (Mod %))) - (:abstraction [#modulus modulus - #value (i.mod (//.divisor modulus) value)])) - - (template [ ] - [(def: .public - (All (_ %) (-> (Mod %) )) - (|>> :representation ))] - - [modulus (Modulus %) product.left] - [value Int product.right] - ) - - (exception: .public [%] (incorrect_modulus {modulus (Modulus %)} - {parsed Int}) - (exception.report - ["Expected" (i\encoded (//.divisor modulus))] - ["Actual" (i\encoded parsed)])) - - (def: separator - " mod ") - - (def: intL - (Parser Int) - (<>.codec i.decimal - (.and (.one_of "-+") (.many .decimal)))) - - (implementation: .public (codec expected) - (All (_ %) (-> (Modulus %) (Codec Text (Mod %)))) - - (def: (encoded modular) - (let [[_ value] (:representation modular)] - ($_ text\composite - (i\encoded value) - ..separator - (i\encoded (//.divisor expected))))) - - (def: decoded - (.result - (do <>.monad - [[value _ actual] ($_ <>.and intL (.this ..separator) intL) - _ (<>.assertion (exception.error ..incorrect_modulus [expected actual]) - (i.= (//.divisor expected) actual))] - (in (..modular expected value)))))) - - (template [ ] - [(def: .public ( reference subject) - (All (_ %) (-> (Mod %) (Mod %) Bit)) - (let [[_ reference] (:representation reference) - [_ subject] (:representation subject)] - ( reference subject)))] - - [= i.=] - [< i.<] - [<= i.<=] - [> i.>] - [>= i.>=] - ) - - (implementation: .public equivalence - (All (_ %) (Equivalence (Mod %))) - - (def: = ..=)) - - (implementation: .public order - (All (_ %) (Order (Mod %))) - - (def: &equivalence ..equivalence) - (def: < ..<)) - - (template [ ] - [(def: .public ( param subject) - (All (_ %) (-> (Mod %) (Mod %) (Mod %))) - (let [[modulus param] (:representation param) - [_ subject] (:representation subject)] - (:abstraction [#modulus modulus - #value (|> subject - ( param) - (i.mod (//.divisor modulus)))])))] - - [+ i.+] - [- i.-] - [* i.*] - ) - - (template [ ] - [(implementation: .public ( modulus) - (All (_ %) (-> (Modulus %) (Monoid (Mod %)))) - - (def: identity - (..modular modulus )) - (def: composite - ))] - - [..+ +0 addition] - [..* +1 multiplication] - ) - - (def: .public (inverse modular) - (All (_ %) (-> (Mod %) (Maybe (Mod %)))) - (let [[modulus value] (:representation modular) - [[vk mk] gcd] (i.extended_gcd value (//.divisor modulus))] - (case gcd - +1 (#.Some (..modular modulus vk)) - _ #.None))) + [(def: .public (modular modulus value) + (All (_ %) (-> (Modulus %) Int (Mod %))) + (:abstraction [#modulus modulus + #value (i.mod (//.divisor modulus) value)])) + + (template [ ] + [(def: .public + (All (_ %) (-> (Mod %) )) + (|>> :representation ))] + + [modulus (Modulus %) product.left] + [value Int product.right] + ) + + (exception: .public [%] (incorrect_modulus {modulus (Modulus %)} + {parsed Int}) + (exception.report + ["Expected" (i\encoded (//.divisor modulus))] + ["Actual" (i\encoded parsed)])) + + (def: separator + " mod ") + + (def: intL + (Parser Int) + (<>.codec i.decimal + (.and (.one_of "-+") (.many .decimal)))) + + (implementation: .public (codec expected) + (All (_ %) (-> (Modulus %) (Codec Text (Mod %)))) + + (def: (encoded modular) + (let [[_ value] (:representation modular)] + ($_ text\composite + (i\encoded value) + ..separator + (i\encoded (//.divisor expected))))) + + (def: decoded + (.result + (do <>.monad + [[value _ actual] ($_ <>.and intL (.this ..separator) intL) + _ (<>.assertion (exception.error ..incorrect_modulus [expected actual]) + (i.= (//.divisor expected) actual))] + (in (..modular expected value)))))) + + (template [ ] + [(def: .public ( reference subject) + (All (_ %) (-> (Mod %) (Mod %) Bit)) + (let [[_ reference] (:representation reference) + [_ subject] (:representation subject)] + ( reference subject)))] + + [= i.=] + [< i.<] + [<= i.<=] + [> i.>] + [>= i.>=] + ) + + (implementation: .public equivalence + (All (_ %) (Equivalence (Mod %))) + + (def: = ..=)) + + (implementation: .public order + (All (_ %) (Order (Mod %))) + + (def: &equivalence ..equivalence) + (def: < ..<)) + + (template [ ] + [(def: .public ( param subject) + (All (_ %) (-> (Mod %) (Mod %) (Mod %))) + (let [[modulus param] (:representation param) + [_ subject] (:representation subject)] + (:abstraction [#modulus modulus + #value (|> subject + ( param) + (i.mod (//.divisor modulus)))])))] + + [+ i.+] + [- i.-] + [* i.*] + ) + + (template [ ] + [(implementation: .public ( modulus) + (All (_ %) (-> (Modulus %) (Monoid (Mod %)))) + + (def: identity + (..modular modulus )) + (def: composite + ))] + + [..+ +0 addition] + [..* +1 multiplication] + ) + + (def: .public (inverse modular) + (All (_ %) (-> (Mod %) (Maybe (Mod %)))) + (let [[modulus value] (:representation modular) + [[vk mk] gcd] (i.extended_gcd value (//.divisor modulus))] + (case gcd + +1 (#.Some (..modular modulus vk)) + _ #.None)))] ) (exception: .public [r% s%] (moduli_are_not_equal {reference (Modulus r%)} diff --git a/stdlib/source/library/lux/math/modulus.lux b/stdlib/source/library/lux/math/modulus.lux index 6879bd012..4a4b000df 100644 --- a/stdlib/source/library/lux/math/modulus.lux +++ b/stdlib/source/library/lux/math/modulus.lux @@ -21,31 +21,29 @@ (exception: .public zero_cannot_be_a_modulus) (abstract: .public (Modulus %) - {} - Int - (def: .public (modulus value) - (Ex (_ %) (-> Int (Try (Modulus %)))) - (if (i.= +0 value) - (exception.except ..zero_cannot_be_a_modulus []) - (#try.Success (:abstraction value)))) - - (def: .public divisor - (All (_ %) (-> (Modulus %) Int)) - (|>> :representation)) - - (def: .public (= reference subject) - (All (_ %r %s) (-> (Modulus %r) (Modulus %s) Bit)) - (i.= (:representation reference) - (:representation subject))) - - (def: .public (congruent? modulus reference subject) - (All (_ %) (-> (Modulus %) Int Int Bit)) - (|> subject - (i.- reference) - (i.% (:representation modulus)) - (i.= +0))) + [(def: .public (modulus value) + (Ex (_ %) (-> Int (Try (Modulus %)))) + (if (i.= +0 value) + (exception.except ..zero_cannot_be_a_modulus []) + (#try.Success (:abstraction value)))) + + (def: .public divisor + (All (_ %) (-> (Modulus %) Int)) + (|>> :representation)) + + (def: .public (= reference subject) + (All (_ %r %s) (-> (Modulus %r) (Modulus %s) Bit)) + (i.= (:representation reference) + (:representation subject))) + + (def: .public (congruent? modulus reference subject) + (All (_ %) (-> (Modulus %) Int Int Bit)) + (|> subject + (i.- reference) + (i.% (:representation modulus)) + (i.= +0)))] ) (syntax: .public (literal [divisor .int]) diff --git a/stdlib/source/library/lux/target/common_lisp.lux b/stdlib/source/library/lux/target/common_lisp.lux index db711eabf..a208ba0ff 100644 --- a/stdlib/source/library/lux/target/common_lisp.lux +++ b/stdlib/source/library/lux/target/common_lisp.lux @@ -21,450 +21,448 @@ (text.enclosed ["(" ")"])) (abstract: .public (Code brand) - {} - Text - (def: .public manual - (-> Text Code) - (|>> :abstraction)) - - (def: .public code - (-> (Code Any) Text) - (|>> :representation)) - - (template [ ] - [(with_expansions [ (template.identifier [ "'"])] - (`` (abstract: .public ( brand) {} Any)) - (`` (type: .public ( brand) - ( ( brand)))))] - - [Expression Code] - [Computation Expression] - [Access Computation] - [Var Access] - - [Input Code] - ) - - (template [ ] - [(with_expansions [ (template.identifier [ "'"])] - (`` (abstract: .public {} Any)) - (`` (type: .public ( ))))] - - [Label Code] - [Tag Expression] - [Literal Expression] - [Var/1 Var] - [Var/* Input] - ) - - (type: .public Lambda - (Record - [#input Var/* - #output (Expression Any)])) - - (def: .public nil - Literal - (:abstraction "()")) - - (template [ ] - [(def: .public - (-> Text Literal) - (|>> (format ) :abstraction))] - - ["'" symbol] - [":" keyword]) - - (def: .public bool - (-> Bit Literal) - (|>> (case> #0 ..nil - #1 (..symbol "t")))) - - (def: .public int - (-> Int Literal) - (|>> %.int :abstraction)) - - (def: .public float - (-> Frac Literal) - (|>> (cond> [(f.= f.positive_infinity)] - [(new> "(/ 1.0 0.0)" [])] - - [(f.= f.negative_infinity)] - [(new> "(/ -1.0 0.0)" [])] - - [f.not_a_number?] - [(new> "(/ 0.0 0.0)" [])] - - ... else - [%.frac]) + [(def: .public manual + (-> Text Code) + (|>> :abstraction)) + + (def: .public code + (-> (Code Any) Text) + (|>> :representation)) + + (template [ ] + [(with_expansions [ (template.identifier [ "'"])] + (`` (abstract: .public ( brand) Any [])) + (`` (type: .public ( brand) + ( ( brand)))))] + + [Expression Code] + [Computation Expression] + [Access Computation] + [Var Access] + + [Input Code] + ) + + (template [ ] + [(with_expansions [ (template.identifier [ "'"])] + (`` (abstract: .public Any [])) + (`` (type: .public ( ))))] + + [Label Code] + [Tag Expression] + [Literal Expression] + [Var/1 Var] + [Var/* Input] + ) + + (type: .public Lambda + (Record + [#input Var/* + #output (Expression Any)])) + + (def: .public nil + Literal + (:abstraction "()")) + + (template [ ] + [(def: .public + (-> Text Literal) + (|>> (format ) :abstraction))] + + ["'" symbol] + [":" keyword]) + + (def: .public bool + (-> Bit Literal) + (|>> (case> #0 ..nil + #1 (..symbol "t")))) + + (def: .public int + (-> Int Literal) + (|>> %.int :abstraction)) + + (def: .public float + (-> Frac Literal) + (|>> (cond> [(f.= f.positive_infinity)] + [(new> "(/ 1.0 0.0)" [])] + + [(f.= f.negative_infinity)] + [(new> "(/ -1.0 0.0)" [])] + + [f.not_a_number?] + [(new> "(/ 0.0 0.0)" [])] + + ... else + [%.frac]) + :abstraction)) + + (def: .public (double value) + (-> Frac Literal) + (:abstraction + (.cond (f.= f.positive_infinity value) + "(/ 1.0d0 0.0d0)" + + (f.= f.negative_infinity value) + "(/ -1.0d0 0.0d0)" + + (f.not_a_number? value) + "(/ 0.0d0 0.0d0)" + + ... else + (.let [raw (%.frac value)] + (.if (text.contains? "E" raw) + (text.replaced/1 "E" "d" raw) + (format raw "d0")))))) + + (def: safe + (-> Text Text) + (`` (|>> (~~ (template [ ] + [(text.replaced )] + + ["\" "\\"] + [text.tab "\t"] + [text.vertical_tab "\v"] + [text.null "\0"] + [text.back_space "\b"] + [text.form_feed "\f"] + [text.new_line "\n"] + [text.carriage_return "\r"] + [text.double_quote (format "\" text.double_quote)] + )) + ))) + + (def: .public string + (-> Text Literal) + (|>> ..safe + (text.enclosed' text.double_quote) + :abstraction)) + + (def: .public var + (-> Text Var/1) + (|>> :abstraction)) + + (def: .public args + (-> (List Var/1) Var/*) + (|>> (list\each ..code) + (text.interposed " ") + ..as_form + :abstraction)) + + (def: .public (args& singles rest) + (-> (List Var/1) Var/1 Var/*) + (|> (case singles + #.End + "" + + (#.Item _) + (|> singles + (list\each ..code) + (text.interposed " ") + (text.suffix " "))) + (format "&rest " (:representation rest)) + ..as_form :abstraction)) - (def: .public (double value) - (-> Frac Literal) - (:abstraction - (.cond (f.= f.positive_infinity value) - "(/ 1.0d0 0.0d0)" - - (f.= f.negative_infinity value) - "(/ -1.0d0 0.0d0)" + (def: form + (-> (List (Expression Any)) Expression) + (|>> (list\each ..code) + (text.interposed " ") + ..as_form + :abstraction)) + + (def: .public (call/* func) + (-> (Expression Any) (-> (List (Expression Any)) (Computation Any))) + (|>> (#.Item func) ..form)) + + (template [ ] + [(def: .public + (-> (List (Expression Any)) (Computation Any)) + (..call/* (..var )))] + + [vector/* "vector"] + [list/* "list"] + ) + + (def: .public (labels definitions body) + (-> (List [Var/1 Lambda]) (Expression Any) (Computation Any)) + (..form (list (..var "labels") + (..form (list\each (function (_ [def_name [def_args def_body]]) + (..form (list def_name (:transmutation def_args) def_body))) + definitions)) + body))) + + (def: .public (destructuring_bind [bindings expression] body) + (-> [Var/* (Expression Any)] (List (Expression Any)) (Computation Any)) + (..form (list& (..var "destructuring-bind") + (:transmutation bindings) expression + body))) + + (template [ + + +] + [(`` (def: .public ( [(~~ (template.spliced +))] function) + (-> [(~~ (template.spliced +))] (Expression Any) (Computation Any)) + (..call/* function (list (~~ (template.spliced +)))))) + + (`` (template [ ] + [(def: .public ( args) + (-> [(~~ (template.spliced +))] (Computation Any)) + ( args (..var )))] - (f.not_a_number? value) - "(/ 0.0d0 0.0d0)" + (~~ (template.spliced +))))] + + [call/0 [] [] + [[get_universal_time/0 "get-universal-time"] + [make_hash_table/0 "make-hash-table"]]] + [call/1 [in0] [(Expression Any)] + [[length/1 "length"] + [function/1 "function"] + [copy_seq/1 "copy-seq"] + [null/1 "null"] + [error/1 "error"] + [not/1 "not"] + [floor/1 "floor"] + [type_of/1 "type-of"] + [write_to_string/1 "write-to-string"] + [read_from_string/1 "read-from-string"] + [print/1 "print"] + [reverse/1 "reverse"] + [sxhash/1 "sxhash"] + [string_upcase/1 "string-upcase"] + [string_downcase/1 "string-downcase"] + [char_int/1 "char-int"] + [text/1 "text"] + [hash_table_size/1 "hash-table-size"] + [hash_table_rehash_size/1 "hash-table-rehash-size"] + [code_char/1 "code-char"] + [char_code/1 "char-code"] + [string/1 "string"] + [write_line/1 "write-line"] + [pprint/1 "pprint"] + [identity/1 "identity"]]] + [call/2 [in0 in1] [(Expression Any) (Expression Any)] + [[apply/2 "apply"] + [append/2 "append"] + [cons/2 "cons"] + [char/2 "char"] + [nth/2 "nth"] + [nthcdr/2 "nthcdr"] + [coerce/2 "coerce"] + [eq/2 "eq"] + [equal/2 "equal"] + [string=/2 "string="] + [=/2 "="] + [+/2 "+"] + [*/2 "*"]]] + [call/3 [in0 in1 in2] [(Expression Any) (Expression Any) (Expression Any)] + [[subseq/3 "subseq"] + [map/3 "map"] + [concatenate/3 "concatenate"] + [format/3 "format"]]] + ) + + (template [ + +] + [(`` (template [ ] + [(def: .public ( args) + (-> [(~~ (template.spliced +))] (Access Any)) + (:transmutation ( args (..var ))))] - ... else - (.let [raw (%.frac value)] - (.if (text.contains? "E" raw) - (text.replaced/1 "E" "d" raw) - (format raw "d0")))))) - - (def: safe - (-> Text Text) - (`` (|>> (~~ (template [ ] - [(text.replaced )] - - ["\" "\\"] - [text.tab "\t"] - [text.vertical_tab "\v"] - [text.null "\0"] - [text.back_space "\b"] - [text.form_feed "\f"] - [text.new_line "\n"] - [text.carriage_return "\r"] - [text.double_quote (format "\" text.double_quote)] - )) - ))) - - (def: .public string - (-> Text Literal) - (|>> ..safe - (text.enclosed' text.double_quote) - :abstraction)) - - (def: .public var - (-> Text Var/1) - (|>> :abstraction)) - - (def: .public args - (-> (List Var/1) Var/*) - (|>> (list\each ..code) - (text.interposed " ") - ..as_form - :abstraction)) - - (def: .public (args& singles rest) - (-> (List Var/1) Var/1 Var/*) - (|> (case singles + (~~ (template.spliced +))))] + + [call/1 [(Expression Any)] + [[car/1 "car"] + [cdr/1 "cdr"] + [cadr/1 "cadr"] + [cddr/1 "cddr"]]] + [call/2 [(Expression Any) (Expression Any)] + [[svref/2 "svref"] + [elt/2 "elt"] + [gethash/2 "gethash"]]] + ) + + (def: .public (make_hash_table/with_size size) + (-> (Expression Any) (Computation Any)) + (..call/* (..var "make-hash-table") + (list (..keyword "size") + size))) + + (def: .public (funcall/+ [func args]) + (-> [(Expression Any) (List (Expression Any))] (Computation Any)) + (..call/* (..var "funcall") (list& func args))) + + (def: .public (search/3 [reference space start]) + (-> [(Expression Any) (Expression Any) (Expression Any)] (Computation Any)) + (..call/* (..var "search") + (list reference + space + (..keyword "start2") start))) + + (def: .public (concatenate/2|string [left right]) + (-> [(Expression Any) (Expression Any)] (Computation Any)) + (concatenate/3 [(..symbol "string") left right])) + + (template [ ] + [(def: .public ( left right) + (-> (Expression Any) (Expression Any) (Computation Any)) + (..form (list (..var ) left right)))] + + [or "or"] + [and "and"] + ) + + (template [ ] + [(def: .public ( [param subject]) + (-> [(Expression Any) (Expression Any)] (Computation Any)) + (..form (list (..var ) subject param)))] + + [/2 ">"] + [>=/2 ">="] + [string (Expression Any) (Expression Any) (Expression Any) (Computation Any)) + (..form (list (..var "if") test then else))) + + (def: .public (when test then) + (-> (Expression Any) (Expression Any) (Computation Any)) + (..form (list (..var "when") test then))) + + (def: .public (lambda input body) + (-> Var/* (Expression Any) Literal) + (..form (list (..var "lambda") (:transmutation input) body))) + + (template [ ] + [(def: .public ( bindings body) + (-> (List [Var/1 (Expression Any)]) (List (Expression Any)) (Computation Any)) + (..form (list& (..var ) + (|> bindings + (list\each (function (_ [name value]) + (..form (list name value)))) + ..form) + body)))] + + [let "let"] + [let* "let*"] + ) + + (def: .public (defparameter name body) + (-> Var/1 (Expression Any) (Expression Any)) + (..form (list (..var "defparameter") name body))) + + (def: .public (defun name inputs body) + (-> Var/1 Var/* (Expression Any) (Expression Any)) + (..form (list (..var "defun") name (:transmutation inputs) body))) + + (template [ ] + [(def: .public + (-> (List (Expression Any)) (Computation Any)) + (|>> (list& (..var )) ..form))] + + [progn "progn"] + [tagbody "tagbody"] + [values/* "values"] + ) + + (def: .public (setq name value) + (-> Var/1 (Expression Any) (Expression Any)) + (..form (list (..var "setq") name value))) + + (def: .public (setf access value) + (-> (Access Any) (Expression Any) (Expression Any)) + (..form (list (..var "setf") access value))) + + (type: .public Handler + (Record + [#condition_type (Expression Any) + #condition Var/1 + #body (Expression Any)])) + + (def: .public (handler_case handlers body) + (-> (List Handler) (Expression Any) (Computation Any)) + (..form (list& (..var "handler-case") + body + (list\each (function (_ [type condition handler]) + (..form (list type + (:transmutation (..args (list condition))) + handler))) + handlers)))) + + (template [ ] + [(def: .public ( conditions expression) + (-> (List Text) (Expression Any) (Expression Any)) + (case conditions #.End - "" + expression - (#.Item _) - (|> singles - (list\each ..code) - (text.interposed " ") - (text.suffix " "))) - (format "&rest " (:representation rest)) - ..as_form - :abstraction)) - - (def: form - (-> (List (Expression Any)) Expression) - (|>> (list\each ..code) - (text.interposed " ") - ..as_form - :abstraction)) - - (def: .public (call/* func) - (-> (Expression Any) (-> (List (Expression Any)) (Computation Any))) - (|>> (#.Item func) ..form)) - - (template [ ] - [(def: .public - (-> (List (Expression Any)) (Computation Any)) - (..call/* (..var )))] - - [vector/* "vector"] - [list/* "list"] - ) - - (def: .public (labels definitions body) - (-> (List [Var/1 Lambda]) (Expression Any) (Computation Any)) - (..form (list (..var "labels") - (..form (list\each (function (_ [def_name [def_args def_body]]) - (..form (list def_name (:transmutation def_args) def_body))) - definitions)) - body))) - - (def: .public (destructuring_bind [bindings expression] body) - (-> [Var/* (Expression Any)] (List (Expression Any)) (Computation Any)) - (..form (list& (..var "destructuring-bind") - (:transmutation bindings) expression - body))) - - (template [ + + +] - [(`` (def: .public ( [(~~ (template.spliced +))] function) - (-> [(~~ (template.spliced +))] (Expression Any) (Computation Any)) - (..call/* function (list (~~ (template.spliced +)))))) - - (`` (template [ ] - [(def: .public ( args) - (-> [(~~ (template.spliced +))] (Computation Any)) - ( args (..var )))] - - (~~ (template.spliced +))))] - - [call/0 [] [] - [[get_universal_time/0 "get-universal-time"] - [make_hash_table/0 "make-hash-table"]]] - [call/1 [in0] [(Expression Any)] - [[length/1 "length"] - [function/1 "function"] - [copy_seq/1 "copy-seq"] - [null/1 "null"] - [error/1 "error"] - [not/1 "not"] - [floor/1 "floor"] - [type_of/1 "type-of"] - [write_to_string/1 "write-to-string"] - [read_from_string/1 "read-from-string"] - [print/1 "print"] - [reverse/1 "reverse"] - [sxhash/1 "sxhash"] - [string_upcase/1 "string-upcase"] - [string_downcase/1 "string-downcase"] - [char_int/1 "char-int"] - [text/1 "text"] - [hash_table_size/1 "hash-table-size"] - [hash_table_rehash_size/1 "hash-table-rehash-size"] - [code_char/1 "code-char"] - [char_code/1 "char-code"] - [string/1 "string"] - [write_line/1 "write-line"] - [pprint/1 "pprint"] - [identity/1 "identity"]]] - [call/2 [in0 in1] [(Expression Any) (Expression Any)] - [[apply/2 "apply"] - [append/2 "append"] - [cons/2 "cons"] - [char/2 "char"] - [nth/2 "nth"] - [nthcdr/2 "nthcdr"] - [coerce/2 "coerce"] - [eq/2 "eq"] - [equal/2 "equal"] - [string=/2 "string="] - [=/2 "="] - [+/2 "+"] - [*/2 "*"]]] - [call/3 [in0 in1 in2] [(Expression Any) (Expression Any) (Expression Any)] - [[subseq/3 "subseq"] - [map/3 "map"] - [concatenate/3 "concatenate"] - [format/3 "format"]]] - ) - - (template [ + +] - [(`` (template [ ] - [(def: .public ( args) - (-> [(~~ (template.spliced +))] (Access Any)) - (:transmutation ( args (..var ))))] - - (~~ (template.spliced +))))] - - [call/1 [(Expression Any)] - [[car/1 "car"] - [cdr/1 "cdr"] - [cadr/1 "cadr"] - [cddr/1 "cddr"]]] - [call/2 [(Expression Any) (Expression Any)] - [[svref/2 "svref"] - [elt/2 "elt"] - [gethash/2 "gethash"]]] - ) - - (def: .public (make_hash_table/with_size size) - (-> (Expression Any) (Computation Any)) - (..call/* (..var "make-hash-table") - (list (..keyword "size") - size))) - - (def: .public (funcall/+ [func args]) - (-> [(Expression Any) (List (Expression Any))] (Computation Any)) - (..call/* (..var "funcall") (list& func args))) - - (def: .public (search/3 [reference space start]) - (-> [(Expression Any) (Expression Any) (Expression Any)] (Computation Any)) - (..call/* (..var "search") - (list reference - space - (..keyword "start2") start))) - - (def: .public (concatenate/2|string [left right]) - (-> [(Expression Any) (Expression Any)] (Computation Any)) - (concatenate/3 [(..symbol "string") left right])) - - (template [ ] - [(def: .public ( left right) - (-> (Expression Any) (Expression Any) (Computation Any)) - (..form (list (..var ) left right)))] - - [or "or"] - [and "and"] - ) - - (template [ ] - [(def: .public ( [param subject]) - (-> [(Expression Any) (Expression Any)] (Computation Any)) - (..form (list (..var ) subject param)))] - - [/2 ">"] - [>=/2 ">="] - [string (Expression Any) (Expression Any) (Expression Any) (Computation Any)) - (..form (list (..var "if") test then else))) - - (def: .public (when test then) - (-> (Expression Any) (Expression Any) (Computation Any)) - (..form (list (..var "when") test then))) - - (def: .public (lambda input body) - (-> Var/* (Expression Any) Literal) - (..form (list (..var "lambda") (:transmutation input) body))) - - (template [ ] - [(def: .public ( bindings body) - (-> (List [Var/1 (Expression Any)]) (List (Expression Any)) (Computation Any)) - (..form (list& (..var ) - (|> bindings - (list\each (function (_ [name value]) - (..form (list name value)))) - ..form) - body)))] - - [let "let"] - [let* "let*"] - ) - - (def: .public (defparameter name body) - (-> Var/1 (Expression Any) (Expression Any)) - (..form (list (..var "defparameter") name body))) - - (def: .public (defun name inputs body) - (-> Var/1 Var/* (Expression Any) (Expression Any)) - (..form (list (..var "defun") name (:transmutation inputs) body))) - - (template [ ] - [(def: .public - (-> (List (Expression Any)) (Computation Any)) - (|>> (list& (..var )) ..form))] - - [progn "progn"] - [tagbody "tagbody"] - [values/* "values"] - ) - - (def: .public (setq name value) - (-> Var/1 (Expression Any) (Expression Any)) - (..form (list (..var "setq") name value))) - - (def: .public (setf access value) - (-> (Access Any) (Expression Any) (Expression Any)) - (..form (list (..var "setf") access value))) - - (type: .public Handler - (Record - [#condition_type (Expression Any) - #condition Var/1 - #body (Expression Any)])) - - (def: .public (handler_case handlers body) - (-> (List Handler) (Expression Any) (Computation Any)) - (..form (list& (..var "handler-case") - body - (list\each (function (_ [type condition handler]) - (..form (list type - (:transmutation (..args (list condition))) - handler))) - handlers)))) - - (template [ ] - [(def: .public ( conditions expression) - (-> (List Text) (Expression Any) (Expression Any)) - (case conditions - #.End - expression - - (#.Item single #.End) - (:abstraction - (format single " " (:representation expression))) - - _ - (:abstraction - (format (|> conditions (list\each ..symbol) - (list& (..symbol "or")) ..form - :representation) - " " (:representation expression)))))] - - [conditional+ "#+"] - [conditional- "#-"]) - - (def: .public label - (-> Text Label) - (|>> :abstraction)) - - (def: .public (block name body) - (-> Label (List (Expression Any)) (Computation Any)) - (..form (list& (..var "block") (:transmutation name) body))) - - (def: .public (return_from target value) - (-> Label (Expression Any) (Computation Any)) - (..form (list (..var "return-from") (:transmutation target) value))) - - (def: .public (return value) - (-> (Expression Any) (Computation Any)) - (..form (list (..var "return") value))) - - (def: .public (cond clauses else) - (-> (List [(Expression Any) (Expression Any)]) (Expression Any) (Computation Any)) - (..form (list& (..var "cond") - (list\composite (list\each (function (_ [test then]) - (..form (list test then))) - clauses) - (list (..form (list (..bool true) else))))))) - - (def: .public tag - (-> Text Tag) - (|>> :abstraction)) - - (def: .public go - (-> Tag (Expression Any)) - (|>> (list (..var "go")) - ..form)) - - (def: .public values_list/1 - (-> (Expression Any) (Expression Any)) - (|>> (list (..var "values-list")) - ..form)) - - (def: .public (multiple_value_setq bindings values) - (-> Var/* (Expression Any) (Expression Any)) - (..form (list (..var "multiple-value-setq") - (:transmutation bindings) - values))) + (#.Item single #.End) + (:abstraction + (format single " " (:representation expression))) + + _ + (:abstraction + (format (|> conditions (list\each ..symbol) + (list& (..symbol "or")) ..form + :representation) + " " (:representation expression)))))] + + [conditional+ "#+"] + [conditional- "#-"]) + + (def: .public label + (-> Text Label) + (|>> :abstraction)) + + (def: .public (block name body) + (-> Label (List (Expression Any)) (Computation Any)) + (..form (list& (..var "block") (:transmutation name) body))) + + (def: .public (return_from target value) + (-> Label (Expression Any) (Computation Any)) + (..form (list (..var "return-from") (:transmutation target) value))) + + (def: .public (return value) + (-> (Expression Any) (Computation Any)) + (..form (list (..var "return") value))) + + (def: .public (cond clauses else) + (-> (List [(Expression Any) (Expression Any)]) (Expression Any) (Computation Any)) + (..form (list& (..var "cond") + (list\composite (list\each (function (_ [test then]) + (..form (list test then))) + clauses) + (list (..form (list (..bool true) else))))))) + + (def: .public tag + (-> Text Tag) + (|>> :abstraction)) + + (def: .public go + (-> Tag (Expression Any)) + (|>> (list (..var "go")) + ..form)) + + (def: .public values_list/1 + (-> (Expression Any) (Expression Any)) + (|>> (list (..var "values-list")) + ..form)) + + (def: .public (multiple_value_setq bindings values) + (-> Var/* (Expression Any) (Expression Any)) + (..form (list (..var "multiple-value-setq") + (:transmutation bindings) + values)))] ) (def: .public (while condition body) diff --git a/stdlib/source/library/lux/target/js.lux b/stdlib/source/library/lux/target/js.lux index d6eff28b5..3f0233f62 100644 --- a/stdlib/source/library/lux/target/js.lux +++ b/stdlib/source/library/lux/target/js.lux @@ -29,392 +29,390 @@ (text.replaced text.new_line (format text.new_line text.tab)))) (abstract: .public (Code brand) - {} - Text - (def: .public code - (-> (Code Any) Text) - (|>> :representation)) - - (template [ +] - [(with_expansions [ (template.identifier [ "'"])] - (abstract: ( brand) {} Any) - (`` (type: .public (|> Any (~~ (template.spliced +))))))] - - [Expression [Code]] - [Computation [Expression' Code]] - [Location [Computation' Expression' Code]] - [Statement [Code]] - ) - - (template [ +] - [(with_expansions [ (template.identifier [ "'"])] - (abstract: {} Any) - (`` (type: .public (|> (~~ (template.spliced +))))))] - - [Var [Location' Computation' Expression' Code]] - [Access [Location' Computation' Expression' Code]] - [Literal [Computation' Expression' Code]] - [Loop [Statement' Code]] - [Label [Code]] - ) - - (template [ ] - [(def: .public Literal (:abstraction ))] - - [null "null"] - [undefined "undefined"] - ) - - (def: .public boolean - (-> Bit Literal) - (|>> (case> - #0 "false" - #1 "true") + [(def: .public code + (-> (Code Any) Text) + (|>> :representation)) + + (template [ +] + [(with_expansions [ (template.identifier [ "'"])] + (abstract: ( brand) Any []) + (`` (type: .public (|> Any (~~ (template.spliced +))))))] + + [Expression [Code]] + [Computation [Expression' Code]] + [Location [Computation' Expression' Code]] + [Statement [Code]] + ) + + (template [ +] + [(with_expansions [ (template.identifier [ "'"])] + (abstract: Any []) + (`` (type: .public (|> (~~ (template.spliced +))))))] + + [Var [Location' Computation' Expression' Code]] + [Access [Location' Computation' Expression' Code]] + [Literal [Computation' Expression' Code]] + [Loop [Statement' Code]] + [Label [Code]] + ) + + (template [ ] + [(def: .public Literal (:abstraction ))] + + [null "null"] + [undefined "undefined"] + ) + + (def: .public boolean + (-> Bit Literal) + (|>> (case> + #0 "false" + #1 "true") + :abstraction)) + + (def: .public (number value) + (-> Frac Literal) + (:abstraction + (.cond (f.not_a_number? value) + "NaN" + + (f.= f.positive_infinity value) + "Infinity" + + (f.= f.negative_infinity value) + "-Infinity" + + ... else + (|> value %.frac ..expression)))) + + (def: safe + (-> Text Text) + (`` (|>> (~~ (template [ ] + [(text.replaced )] + + ["\\" "\"] + ["\t" text.tab] + ["\v" text.vertical_tab] + ["\0" text.null] + ["\b" text.back_space] + ["\f" text.form_feed] + ["\n" text.new_line] + ["\r" text.carriage_return] + [(format "\" text.double_quote) + text.double_quote] + )) + ))) + + (def: .public string + (-> Text Literal) + (|>> ..safe + (text.enclosed [text.double_quote text.double_quote]) + :abstraction)) + + (def: argument_separator ", ") + (def: field_separator ": ") + (def: statement_suffix ";") + + (def: .public array + (-> (List Expression) Computation) + (|>> (list\each ..code) + (text.interposed ..argument_separator) + ..element + :abstraction)) + + (def: .public var + (-> Text Var) + (|>> :abstraction)) + + (def: .public (at index array_or_object) + (-> Expression Expression Access) + (:abstraction (format (:representation array_or_object) (..element (:representation index))))) + + (def: .public (the field object) + (-> Text Expression Access) + (:abstraction (format (:representation object) "." field))) + + (def: .public (apply/* function inputs) + (-> Expression (List Expression) Computation) + (|> inputs + (list\each ..code) + (text.interposed ..argument_separator) + ..expression + (format (:representation function)) :abstraction)) - (def: .public (number value) - (-> Frac Literal) - (:abstraction - (.cond (f.not_a_number? value) - "NaN" - - (f.= f.positive_infinity value) - "Infinity" - - (f.= f.negative_infinity value) - "-Infinity" - - ... else - (|> value %.frac ..expression)))) - - (def: safe - (-> Text Text) - (`` (|>> (~~ (template [ ] - [(text.replaced )] - - ["\\" "\"] - ["\t" text.tab] - ["\v" text.vertical_tab] - ["\0" text.null] - ["\b" text.back_space] - ["\f" text.form_feed] - ["\n" text.new_line] - ["\r" text.carriage_return] - [(format "\" text.double_quote) - text.double_quote] - )) - ))) - - (def: .public string - (-> Text Literal) - (|>> ..safe - (text.enclosed [text.double_quote text.double_quote]) + (def: .public (do method inputs object) + (-> Text (List Expression) Expression Computation) + (apply/* (..the method object) inputs)) + + (def: .public object + (-> (List [Text Expression]) Computation) + (|>> (list\each (.function (_ [key val]) + (format (:representation (..string key)) ..field_separator (:representation val)))) + (text.interposed ..argument_separator) + (text.enclosed ["{" "}"]) + ..expression + :abstraction)) + + (def: .public (, pre post) + (-> Expression Expression Computation) + (|> (format (:representation pre) ..argument_separator (:representation post)) + ..expression :abstraction)) - (def: argument_separator ", ") - (def: field_separator ": ") - (def: statement_suffix ";") + (def: .public (then pre post) + (-> Statement Statement Statement) + (:abstraction (format (:representation pre) + text.new_line + (:representation post)))) - (def: .public array - (-> (List Expression) Computation) - (|>> (list\each ..code) - (text.interposed ..argument_separator) - ..element + (def: block + (-> Statement Text) + (let [close (format text.new_line "}")] + (|>> :representation + ..nested + (text.enclosed ["{" + close])))) + + (def: .public (function! name inputs body) + (-> Var (List Var) Statement Statement) + (|> body + ..block + (format "function " (:representation name) + (|> inputs + (list\each ..code) + (text.interposed ..argument_separator) + ..expression) + " ") :abstraction)) - (def: .public var - (-> Text Var) - (|>> :abstraction)) - - (def: .public (at index array_or_object) - (-> Expression Expression Access) - (:abstraction (format (:representation array_or_object) (..element (:representation index))))) - - (def: .public (the field object) - (-> Text Expression Access) - (:abstraction (format (:representation object) "." field))) - - (def: .public (apply/* function inputs) - (-> Expression (List Expression) Computation) - (|> inputs - (list\each ..code) - (text.interposed ..argument_separator) - ..expression - (format (:representation function)) - :abstraction)) - - (def: .public (do method inputs object) - (-> Text (List Expression) Expression Computation) - (apply/* (..the method object) inputs)) - - (def: .public object - (-> (List [Text Expression]) Computation) - (|>> (list\each (.function (_ [key val]) - (format (:representation (..string key)) ..field_separator (:representation val)))) - (text.interposed ..argument_separator) - (text.enclosed ["{" "}"]) + (def: .public (function name inputs body) + (-> Var (List Var) Statement Computation) + (|> (..function! name inputs body) + :representation ..expression :abstraction)) - (def: .public (, pre post) - (-> Expression Expression Computation) - (|> (format (:representation pre) ..argument_separator (:representation post)) - ..expression - :abstraction)) - - (def: .public (then pre post) - (-> Statement Statement Statement) - (:abstraction (format (:representation pre) - text.new_line - (:representation post)))) - - (def: block - (-> Statement Text) - (let [close (format text.new_line "}")] - (|>> :representation - ..nested - (text.enclosed ["{" - close])))) - - (def: .public (function! name inputs body) - (-> Var (List Var) Statement Statement) - (|> body - ..block - (format "function " (:representation name) - (|> inputs - (list\each ..code) - (text.interposed ..argument_separator) - ..expression) - " ") - :abstraction)) - - (def: .public (function name inputs body) - (-> Var (List Var) Statement Computation) - (|> (..function! name inputs body) - :representation - ..expression - :abstraction)) - - (def: .public (closure inputs body) - (-> (List Var) Statement Computation) - (|> body - ..block - (format "function" - (|> inputs - (list\each ..code) - (text.interposed ..argument_separator) - ..expression) - " ") - ..expression - :abstraction)) - - (template [ ] - [(def: .public ( param subject) - (-> Expression Expression Computation) - (|> (format (:representation subject) " " " " (:representation param)) - ..expression - :abstraction))] - - [= "==="] - [< "<"] - [<= "<="] - [> ">"] - [>= ">="] - - [+ "+"] - [- "-"] - [* "*"] - [/ "/"] - [% "%"] - - [left_shift "<<"] - [arithmetic_right_shift ">>"] - [logic_right_shift ">>>"] - - [or "||"] - [and "&&"] - [bit_xor "^"] - [bit_or "|"] - [bit_and "&"] - ) - - (template [ ] - [(def: .public - (-> Expression Computation) - (|>> :representation (text.prefix ) ..expression :abstraction))] - - [not "!"] - [bit_not "~"] - [opposite "-"] - ) - - (template [ ] - [(def: .public ( value) - {#.doc "A 32-bit integer expression."} - (-> Computation) - (:abstraction (..expression (format ( value) "|0"))))] - - [to_i32 Expression :representation] - [i32 Int %.int] - ) - - (def: .public (int value) - (-> Int Literal) - (:abstraction (.if (i.< +0 value) - (%.int value) - (%.nat (.nat value))))) - - (def: .public (? test then else) - (-> Expression Expression Expression Computation) - (|> (format (:representation test) - " ? " (:representation then) - " : " (:representation else)) - ..expression - :abstraction)) - - (def: .public type_of - (-> Expression Computation) - (|>> :representation - (format "typeof ") + (def: .public (closure inputs body) + (-> (List Var) Statement Computation) + (|> body + ..block + (format "function" + (|> inputs + (list\each ..code) + (text.interposed ..argument_separator) + ..expression) + " ") ..expression :abstraction)) - (def: .public (new constructor inputs) - (-> Expression (List Expression) Computation) - (|> (format "new " (:representation constructor) - (|> inputs - (list\each ..code) - (text.interposed ..argument_separator) - ..expression)) - ..expression - :abstraction)) - - (def: .public statement - (-> Expression Statement) - (|>> :representation (text.suffix ..statement_suffix) :abstraction)) - - (def: .public use_strict - Statement - (:abstraction (format text.double_quote "use strict" text.double_quote ..statement_suffix))) - - (def: .public (declare name) - (-> Var Statement) - (:abstraction (format "var " (:representation name) ..statement_suffix))) - - (def: .public (define name value) - (-> Var Expression Statement) - (:abstraction (format "var " (:representation name) " = " (:representation value) ..statement_suffix))) - - (def: .public (set name value) - (-> Location Expression Statement) - (:abstraction (format (:representation name) " = " (:representation value) ..statement_suffix))) - - (def: .public (throw message) - (-> Expression Statement) - (:abstraction (format "throw " (:representation message) ..statement_suffix))) - - (def: .public (return value) - (-> Expression Statement) - (:abstraction (format "return " (:representation value) ..statement_suffix))) - - (def: .public (delete value) - (-> Location Statement) - (:abstraction (format "delete " (:representation value) ..statement_suffix))) - - (def: .public (if test then! else!) - (-> Expression Statement Statement Statement) - (:abstraction (format "if(" (:representation test) ") " - (..block then!) - " else " - (..block else!)))) - - (def: .public (when test then!) - (-> Expression Statement Statement) - (:abstraction (format "if(" (:representation test) ") " - (..block then!)))) - - (def: .public (while test body) - (-> Expression Statement Loop) - (:abstraction (format "while(" (:representation test) ") " - (..block body)))) - - (def: .public (do_while test body) - (-> Expression Statement Loop) - (:abstraction (format "do " (..block body) - " while(" (:representation test) ")" ..statement_suffix))) - - (def: .public (try body [exception catch]) - (-> Statement [Var Statement] Statement) - (:abstraction (format "try " - (..block body) - " catch(" (:representation exception) ") " - (..block catch)))) - - (def: .public (for var init condition update iteration) - (-> Var Expression Expression Expression Statement Loop) - (:abstraction (format "for(" (:representation (..define var init)) - " " (:representation condition) - ..statement_suffix " " (:representation update) - ")" - (..block iteration)))) - - (def: .public label - (-> Text Label) - (|>> :abstraction)) - - (def: .public (with_label label loop) - (-> Label Loop Statement) - (:abstraction (format (:representation label) ": " (:representation loop)))) - - (template [ <0> <1>] - [(def: .public <0> - Statement - (:abstraction (format ..statement_suffix))) - - (def: .public (<1> label) - (-> Label Statement) - (:abstraction (format " " (:representation label) ..statement_suffix)))] - - ["break" break break_at] - ["continue" continue continue_at] - ) - - (template [ ] - [(def: .public - (-> Location Expression) - (|>> :representation - (text.suffix ) + (template [ ] + [(def: .public ( param subject) + (-> Expression Expression Computation) + (|> (format (:representation subject) " " " " (:representation param)) + ..expression :abstraction))] - [++ "++"] - [-- "--"] - ) - - (def: .public (comment commentary on) - (All (_ kind) (-> Text (Code kind) (Code kind))) - (:abstraction (format "/* " commentary " */" " " (:representation on)))) - - (def: .public (switch input cases default) - (-> Expression (List [(List Literal) Statement]) (Maybe Statement) Statement) - (:abstraction (format "switch (" (:representation input) ") " - (|> (format (|> cases - (list\each (.function (_ [when then]) - (format (|> when - (list\each (|>> :representation (text.enclosed ["case " ":"]))) - (text.interposed text.new_line)) - (..nested (:representation then))))) - (text.interposed text.new_line)) - text.new_line - (case default - (#.Some default) - (format "default:" - (..nested (:representation default))) - - #.None "")) - :abstraction - ..block)))) + [= "==="] + [< "<"] + [<= "<="] + [> ">"] + [>= ">="] + + [+ "+"] + [- "-"] + [* "*"] + [/ "/"] + [% "%"] + + [left_shift "<<"] + [arithmetic_right_shift ">>"] + [logic_right_shift ">>>"] + + [or "||"] + [and "&&"] + [bit_xor "^"] + [bit_or "|"] + [bit_and "&"] + ) + + (template [ ] + [(def: .public + (-> Expression Computation) + (|>> :representation (text.prefix ) ..expression :abstraction))] + + [not "!"] + [bit_not "~"] + [opposite "-"] + ) + + (template [ ] + [(def: .public ( value) + {#.doc "A 32-bit integer expression."} + (-> Computation) + (:abstraction (..expression (format ( value) "|0"))))] + + [to_i32 Expression :representation] + [i32 Int %.int] + ) + + (def: .public (int value) + (-> Int Literal) + (:abstraction (.if (i.< +0 value) + (%.int value) + (%.nat (.nat value))))) + + (def: .public (? test then else) + (-> Expression Expression Expression Computation) + (|> (format (:representation test) + " ? " (:representation then) + " : " (:representation else)) + ..expression + :abstraction)) + + (def: .public type_of + (-> Expression Computation) + (|>> :representation + (format "typeof ") + ..expression + :abstraction)) + + (def: .public (new constructor inputs) + (-> Expression (List Expression) Computation) + (|> (format "new " (:representation constructor) + (|> inputs + (list\each ..code) + (text.interposed ..argument_separator) + ..expression)) + ..expression + :abstraction)) + + (def: .public statement + (-> Expression Statement) + (|>> :representation (text.suffix ..statement_suffix) :abstraction)) + + (def: .public use_strict + Statement + (:abstraction (format text.double_quote "use strict" text.double_quote ..statement_suffix))) + + (def: .public (declare name) + (-> Var Statement) + (:abstraction (format "var " (:representation name) ..statement_suffix))) + + (def: .public (define name value) + (-> Var Expression Statement) + (:abstraction (format "var " (:representation name) " = " (:representation value) ..statement_suffix))) + + (def: .public (set name value) + (-> Location Expression Statement) + (:abstraction (format (:representation name) " = " (:representation value) ..statement_suffix))) + + (def: .public (throw message) + (-> Expression Statement) + (:abstraction (format "throw " (:representation message) ..statement_suffix))) + + (def: .public (return value) + (-> Expression Statement) + (:abstraction (format "return " (:representation value) ..statement_suffix))) + + (def: .public (delete value) + (-> Location Statement) + (:abstraction (format "delete " (:representation value) ..statement_suffix))) + + (def: .public (if test then! else!) + (-> Expression Statement Statement Statement) + (:abstraction (format "if(" (:representation test) ") " + (..block then!) + " else " + (..block else!)))) + + (def: .public (when test then!) + (-> Expression Statement Statement) + (:abstraction (format "if(" (:representation test) ") " + (..block then!)))) + + (def: .public (while test body) + (-> Expression Statement Loop) + (:abstraction (format "while(" (:representation test) ") " + (..block body)))) + + (def: .public (do_while test body) + (-> Expression Statement Loop) + (:abstraction (format "do " (..block body) + " while(" (:representation test) ")" ..statement_suffix))) + + (def: .public (try body [exception catch]) + (-> Statement [Var Statement] Statement) + (:abstraction (format "try " + (..block body) + " catch(" (:representation exception) ") " + (..block catch)))) + + (def: .public (for var init condition update iteration) + (-> Var Expression Expression Expression Statement Loop) + (:abstraction (format "for(" (:representation (..define var init)) + " " (:representation condition) + ..statement_suffix " " (:representation update) + ")" + (..block iteration)))) + + (def: .public label + (-> Text Label) + (|>> :abstraction)) + + (def: .public (with_label label loop) + (-> Label Loop Statement) + (:abstraction (format (:representation label) ": " (:representation loop)))) + + (template [ <0> <1>] + [(def: .public <0> + Statement + (:abstraction (format ..statement_suffix))) + + (def: .public (<1> label) + (-> Label Statement) + (:abstraction (format " " (:representation label) ..statement_suffix)))] + + ["break" break break_at] + ["continue" continue continue_at] + ) + + (template [ ] + [(def: .public + (-> Location Expression) + (|>> :representation + (text.suffix ) + :abstraction))] + + [++ "++"] + [-- "--"] + ) + + (def: .public (comment commentary on) + (All (_ kind) (-> Text (Code kind) (Code kind))) + (:abstraction (format "/* " commentary " */" " " (:representation on)))) + + (def: .public (switch input cases default) + (-> Expression (List [(List Literal) Statement]) (Maybe Statement) Statement) + (:abstraction (format "switch (" (:representation input) ") " + (|> (format (|> cases + (list\each (.function (_ [when then]) + (format (|> when + (list\each (|>> :representation (text.enclosed ["case " ":"]))) + (text.interposed text.new_line)) + (..nested (:representation then))))) + (text.interposed text.new_line)) + text.new_line + (case default + (#.Some default) + (format "default:" + (..nested (:representation default))) + + #.None "")) + :abstraction + ..block))))] ) (def: .public (cond clauses else!) diff --git a/stdlib/source/library/lux/target/jvm/bytecode/address.lux b/stdlib/source/library/lux/target/jvm/bytecode/address.lux index 063c3eff6..2908238d5 100644 --- a/stdlib/source/library/lux/target/jvm/bytecode/address.lux +++ b/stdlib/source/library/lux/target/jvm/bytecode/address.lux @@ -24,53 +24,51 @@ ["[1][0]" signed {"+" [S4]}]]]]) (abstract: .public Address - {} - U2 - (def: .public value - (-> Address U2) - (|>> :representation)) + [(def: .public value + (-> Address U2) + (|>> :representation)) - (def: .public start - Address - (|> 0 ///unsigned.u2 try.trusted :abstraction)) + (def: .public start + Address + (|> 0 ///unsigned.u2 try.trusted :abstraction)) - (def: .public (move distance) - (-> U2 (-> Address (Try Address))) - (|>> :representation - (///unsigned.+/2 distance) - (\ try.functor each (|>> :abstraction)))) + (def: .public (move distance) + (-> U2 (-> Address (Try Address))) + (|>> :representation + (///unsigned.+/2 distance) + (\ try.functor each (|>> :abstraction)))) - (def: with_sign - (-> Address (Try S4)) - (|>> :representation ///unsigned.value .int ///signed.s4)) + (def: with_sign + (-> Address (Try S4)) + (|>> :representation ///unsigned.value .int ///signed.s4)) - (def: .public (jump from to) - (-> Address Address (Try Big_Jump)) - (do try.monad - [from (with_sign from) - to (with_sign to)] - (///signed.-/4 from to))) + (def: .public (jump from to) + (-> Address Address (Try Big_Jump)) + (do try.monad + [from (with_sign from) + to (with_sign to)] + (///signed.-/4 from to))) - (def: .public (after? reference subject) - (-> Address Address Bit) - (n.> (|> reference :representation ///unsigned.value) - (|> subject :representation ///unsigned.value))) + (def: .public (after? reference subject) + (-> Address Address Bit) + (n.> (|> reference :representation ///unsigned.value) + (|> subject :representation ///unsigned.value))) - (implementation: .public equivalence - (Equivalence Address) - - (def: (= reference subject) - (\ ///unsigned.equivalence = - (:representation reference) - (:representation subject)))) + (implementation: .public equivalence + (Equivalence Address) + + (def: (= reference subject) + (\ ///unsigned.equivalence = + (:representation reference) + (:representation subject)))) - (def: .public writer - (Writer Address) - (|>> :representation ///unsigned.writer/2)) + (def: .public writer + (Writer Address) + (|>> :representation ///unsigned.writer/2)) - (def: .public format - (Format Address) - (|>> :representation ///unsigned.value %.nat)) + (def: .public format + (Format Address) + (|>> :representation ///unsigned.value %.nat))] ) 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 9a111eb22..13f9343a7 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 @@ -29,65 +29,63 @@ (def: wide 2) (abstract: .public Registry - {} - U2 - (def: .public registry - (-> U2 Registry) - (|>> :abstraction)) + [(def: .public registry + (-> U2 Registry) + (|>> :abstraction)) - (def: (minimal type) - (-> (Type Method) Nat) - (let [[type_variables inputs output exceptions] (/////type/parser.method type)] - (|> inputs - (list\each (function (_ input) - (if (or (same? /////type.long input) - (same? /////type.double input)) - ..wide - ..normal))) - (list\mix n.+ 0)))) + (def: (minimal type) + (-> (Type Method) Nat) + (let [[type_variables inputs output exceptions] (/////type/parser.method type)] + (|> inputs + (list\each (function (_ input) + (if (or (same? /////type.long input) + (same? /////type.double input)) + ..wide + ..normal))) + (list\mix n.+ 0)))) - (template [ ] - [(def: .public - (-> (Type Method) (Try Registry)) - (|>> ..minimal - (n.+ ) - /////unsigned.u2 - (try\each ..registry)))] + (template [ ] + [(def: .public + (-> (Type Method) (Try Registry)) + (|>> ..minimal + (n.+ ) + /////unsigned.u2 + (try\each ..registry)))] - [0 static] - [1 virtual] - ) + [0 static] + [1 virtual] + ) - (def: .public equivalence - (Equivalence Registry) - (\ equivalence.functor each - (|>> :representation) - /////unsigned.equivalence)) + (def: .public equivalence + (Equivalence Registry) + (\ equivalence.functor each + (|>> :representation) + /////unsigned.equivalence)) - (def: .public writer - (Writer Registry) - (|>> :representation /////unsigned.writer/2)) + (def: .public writer + (Writer Registry) + (|>> :representation /////unsigned.writer/2)) - (def: .public (has needed) - (-> Registry Registry Registry) - (|>> :representation - (/////unsigned.max/2 (:representation needed)) - :abstraction)) + (def: .public (has needed) + (-> Registry Registry Registry) + (|>> :representation + (/////unsigned.max/2 (:representation needed)) + :abstraction)) - (template [ ] - [(def: .public - (-> Register Registry) - (let [extra (|> /////unsigned.u2 try.trusted)] - (|>> /////unsigned.lifted/2 - (/////unsigned.+/2 extra) - try.trusted - :abstraction)))] + (template [ ] + [(def: .public + (-> Register Registry) + (let [extra (|> /////unsigned.u2 try.trusted)] + (|>> /////unsigned.lifted/2 + (/////unsigned.+/2 extra) + try.trusted + :abstraction)))] - [for ..normal] - [for_wide ..wide] - ) + [for ..normal] + [for_wide ..wide] + )] ) (def: .public length 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 48cfba7a8..1118c3b22 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 @@ -18,53 +18,51 @@ ["[1][0]" unsigned {"+" [U2]}]]]) (abstract: .public Stack - {} - U2 - (template [ ] - [(def: .public - Stack - (|> /////unsigned.u2 maybe.trusted :abstraction))] + [(template [ ] + [(def: .public + Stack + (|> /////unsigned.u2 maybe.trusted :abstraction))] - [0 empty] - [1 catch] - ) + [0 empty] + [1 catch] + ) - (def: .public equivalence - (Equivalence Stack) - (\ equivalence.functor each - (|>> :representation) - /////unsigned.equivalence)) + (def: .public equivalence + (Equivalence Stack) + (\ equivalence.functor each + (|>> :representation) + /////unsigned.equivalence)) - (def: .public writer - (Writer Stack) - (|>> :representation /////unsigned.writer/2)) + (def: .public writer + (Writer Stack) + (|>> :representation /////unsigned.writer/2)) - (def: stack - (-> U2 Stack) - (|>> :abstraction)) + (def: stack + (-> U2 Stack) + (|>> :abstraction)) - (template [ ] - [(def: .public ( amount) - (-> U2 (-> Stack (Try Stack))) - (|>> :representation - ( amount) - (\ try.functor each ..stack)))] + (template [ ] + [(def: .public ( amount) + (-> U2 (-> Stack (Try Stack))) + (|>> :representation + ( amount) + (\ try.functor each ..stack)))] - [/////unsigned.+/2 push] - [/////unsigned.-/2 pop] - ) + [/////unsigned.+/2 push] + [/////unsigned.-/2 pop] + ) - (def: .public (max left right) - (-> Stack Stack Stack) - (:abstraction - (/////unsigned.max/2 (:representation left) - (:representation right)))) + (def: .public (max left right) + (-> Stack Stack Stack) + (:abstraction + (/////unsigned.max/2 (:representation left) + (:representation right)))) - (def: .public format - (Format Stack) - (|>> :representation /////unsigned.value %.nat)) + (def: .public format + (Format Stack) + (|>> :representation /////unsigned.value %.nat))] ) (def: .public length diff --git a/stdlib/source/library/lux/target/jvm/bytecode/instruction.lux b/stdlib/source/library/lux/target/jvm/bytecode/instruction.lux index 449eb0d19..9fe36c303 100644 --- a/stdlib/source/library/lux/target/jvm/bytecode/instruction.lux +++ b/stdlib/source/library/lux/target/jvm/bytecode/instruction.lux @@ -235,26 +235,24 @@ (|>> mutation ((trinary/211' opcode input0 input1 input2)))])]) (abstract: .public Primitive_Array_Type - {} - U1 - (def: code - (-> Primitive_Array_Type U1) - (|>> :representation)) - - (template [ ] - [(def: .public (|> ///unsigned.u1 try.trusted :abstraction))] - - [04 t_boolean] - [05 t_char] - [06 t_float] - [07 t_double] - [08 t_byte] - [09 t_short] - [10 t_int] - [11 t_long] - )) + [(def: code + (-> Primitive_Array_Type U1) + (|>> :representation)) + + (template [ ] + [(def: .public (|> ///unsigned.u1 try.trusted :abstraction))] + + [04 t_boolean] + [05 t_char] + [06 t_float] + [07 t_double] + [08 t_byte] + [09 t_short] + [10 t_int] + [11 t_long] + )]) ... https://docs.oracle.com/javase/specs/jvms/se8/html/jvms-6.html#jvms-6.5 (with_expansions [ (template [ ] diff --git a/stdlib/source/library/lux/target/jvm/constant.lux b/stdlib/source/library/lux/target/jvm/constant.lux index 742c1101e..ef1076787 100644 --- a/stdlib/source/library/lux/target/jvm/constant.lux +++ b/stdlib/source/library/lux/target/jvm/constant.lux @@ -42,27 +42,25 @@ binaryF.utf8/16) (abstract: .public Class - {} - (Index UTF8) - (def: .public index - (-> Class (Index UTF8)) - (|>> :representation)) - - (def: .public class - (-> (Index UTF8) Class) - (|>> :abstraction)) - - (def: .public class_equivalence - (Equivalence Class) - (\ equivalence.functor each - ..index - //index.equivalence)) - - (def: class_writer - (Writer Class) - (|>> :representation //index.writer)) + [(def: .public index + (-> Class (Index UTF8)) + (|>> :representation)) + + (def: .public class + (-> (Index UTF8) Class) + (|>> :abstraction)) + + (def: .public class_equivalence + (Equivalence Class) + (\ equivalence.functor each + ..index + //index.equivalence)) + + (def: class_writer + (Writer Class) + (|>> :representation //index.writer))] ) (import: java/lang/Float @@ -86,50 +84,48 @@ ("static" doubleToRawLongBits [double] long)]) (abstract: .public (Value kind) - {} - kind - (def: .public value - (All (_ kind) (-> (Value kind) kind)) - (|>> :representation)) - - (def: .public (value_equivalence Equivalence) - (All (_ kind) - (-> (Equivalence kind) - (Equivalence (Value kind)))) - (\ equivalence.functor each - (|>> :representation) - Equivalence)) - - (template [ ] - [(type: .public - (Value )) - - (def: .public - (-> ) - (|>> :abstraction))] - - [integer Integer I32] - [float Float java/lang/Float] - [long Long .Int] - [double Double Frac] - [string String (Index UTF8)] - ) - - (template [ ] - [(def: - (Writer ) - (`` (|>> :representation - (~~ (template.spliced )) - (~~ (template.spliced )))))] - - [integer_writer Integer [] [binaryF.bits/32]] - [float_writer Float [java/lang/Float::floatToRawIntBits ffi.int_to_long (:as I64)] [i32.i32 binaryF.bits/32]] - [long_writer Long [] [binaryF.bits/64]] - [double_writer Double [java/lang/Double::doubleToRawLongBits] [binaryF.bits/64]] - [string_writer String [] [//index.writer]] - ) + [(def: .public value + (All (_ kind) (-> (Value kind) kind)) + (|>> :representation)) + + (def: .public (value_equivalence Equivalence) + (All (_ kind) + (-> (Equivalence kind) + (Equivalence (Value kind)))) + (\ equivalence.functor each + (|>> :representation) + Equivalence)) + + (template [ ] + [(type: .public + (Value )) + + (def: .public + (-> ) + (|>> :abstraction))] + + [integer Integer I32] + [float Float java/lang/Float] + [long Long .Int] + [double Double Frac] + [string String (Index UTF8)] + ) + + (template [ ] + [(def: + (Writer ) + (`` (|>> :representation + (~~ (template.spliced )) + (~~ (template.spliced )))))] + + [integer_writer Integer [] [binaryF.bits/32]] + [float_writer Float [java/lang/Float::floatToRawIntBits ffi.int_to_long (:as I64)] [i32.i32 binaryF.bits/32]] + [long_writer Long [] [binaryF.bits/64]] + [double_writer Double [java/lang/Double::doubleToRawLongBits] [binaryF.bits/64]] + [string_writer String [] [//index.writer]] + )] ) (type: .public (Name_And_Type of) diff --git a/stdlib/source/library/lux/target/jvm/constant/tag.lux b/stdlib/source/library/lux/target/jvm/constant/tag.lux index ad56d1042..b774dfd4e 100644 --- a/stdlib/source/library/lux/target/jvm/constant/tag.lux +++ b/stdlib/source/library/lux/target/jvm/constant/tag.lux @@ -15,38 +15,36 @@ ["[1][0]" unsigned {"+" [U1]} ("u1//[0]" equivalence)]]]) (abstract: .public Tag - {} - U1 - (implementation: .public equivalence - (Equivalence Tag) - (def: (= reference sample) - (u1//= (:representation reference) - (:representation sample)))) + [(implementation: .public equivalence + (Equivalence Tag) + (def: (= reference sample) + (u1//= (:representation reference) + (:representation sample)))) - (template [ ] - [(def: .public - Tag - (|> ///unsigned.u1 try.trusted :abstraction))] + (template [ ] + [(def: .public + Tag + (|> ///unsigned.u1 try.trusted :abstraction))] - [01 utf8] - [03 integer] - [04 float] - [05 long] - [06 double] - [07 class] - [08 string] - [09 field] - [10 method] - [11 interface_method] - [12 name_and_type] - [15 method_handle] - [16 method_type] - [18 invoke_dynamic] - ) + [01 utf8] + [03 integer] + [04 float] + [05 long] + [06 double] + [07 class] + [08 string] + [09 field] + [10 method] + [11 interface_method] + [12 name_and_type] + [15 method_handle] + [16 method_type] + [18 invoke_dynamic] + ) - (def: .public writer - (Writer Tag) - (|>> :representation ///unsigned.writer/1)) + (def: .public writer + (Writer Tag) + (|>> :representation ///unsigned.writer/1))] ) diff --git a/stdlib/source/library/lux/target/jvm/encoding/name.lux b/stdlib/source/library/lux/target/jvm/encoding/name.lux index 7553285f2..390b7c95c 100644 --- a/stdlib/source/library/lux/target/jvm/encoding/name.lux +++ b/stdlib/source/library/lux/target/jvm/encoding/name.lux @@ -14,25 +14,23 @@ Text) (abstract: .public Internal - {} - Text - (def: .public internal - (-> External Internal) - (|>> (text.replaced ..external_separator - ..internal_separator) - :abstraction)) - - (def: .public read - (-> Internal Text) - (|>> :representation)) - - (def: .public external - (-> Internal External) - (|>> :representation - (text.replaced ..internal_separator - ..external_separator)))) + [(def: .public internal + (-> External Internal) + (|>> (text.replaced ..external_separator + ..internal_separator) + :abstraction)) + + (def: .public read + (-> Internal Text) + (|>> :representation)) + + (def: .public external + (-> Internal External) + (|>> :representation + (text.replaced ..internal_separator + ..external_separator)))]) (def: .public safe (-> Text External) diff --git a/stdlib/source/library/lux/target/jvm/encoding/signed.lux b/stdlib/source/library/lux/target/jvm/encoding/signed.lux index e2aa094dc..5a13c9619 100644 --- a/stdlib/source/library/lux/target/jvm/encoding/signed.lux +++ b/stdlib/source/library/lux/target/jvm/encoding/signed.lux @@ -23,87 +23,85 @@ abstract]]]) (abstract: .public (Signed brand) - {} - Int - (def: .public value - (-> (Signed Any) Int) - (|>> :representation)) + [(def: .public value + (-> (Signed Any) Int) + (|>> :representation)) - (implementation: .public equivalence - (All (_ brand) (Equivalence (Signed brand))) - (def: (= reference sample) - (i.= (:representation reference) (:representation sample)))) + (implementation: .public equivalence + (All (_ brand) (Equivalence (Signed brand))) + (def: (= reference sample) + (i.= (:representation reference) (:representation sample)))) - (implementation: .public order - (All (_ brand) (Order (Signed brand))) - - (def: &equivalence ..equivalence) - (def: (< reference sample) - (i.< (:representation reference) (:representation sample)))) + (implementation: .public order + (All (_ brand) (Order (Signed brand))) + + (def: &equivalence ..equivalence) + (def: (< reference sample) + (i.< (:representation reference) (:representation sample)))) - (exception: .public (value_exceeds_the_scope {value Int} - {scope Nat}) - (exception.report - ["Value" (%.int value)] - ["Scope (in bytes)" (%.nat scope)])) + (exception: .public (value_exceeds_the_scope {value Int} + {scope Nat}) + (exception.report + ["Value" (%.int value)] + ["Scope (in bytes)" (%.nat scope)])) - (template [ <+> <->] - [(with_expansions [ (template.identifier [ "'"])] - (abstract: .public {} Any) - (type: .public (Signed ))) + (template [ <+> <->] + [(with_expansions [ (template.identifier [ "'"])] + (abstract: .public Any []) + (type: .public (Signed ))) - (def: .public ) - - (def: .public - - (|> (n.* i64.bits_per_byte) -- i64.mask :abstraction)) - - (def: .public - (-> Int (Try )) - (let [positive (|> (n.* i64.bits_per_byte) i64.mask) - negative (|> positive .int (i.right_shifted 1) i64.not)] - (function (_ value) - (if (i.= (if (i.< +0 value) - (i64.or negative value) - (i64.and positive value)) - value) - (#try.Success (:abstraction value)) - (exception.except ..value_exceeds_the_scope [value ]))))) + (def: .public ) + + (def: .public + + (|> (n.* i64.bits_per_byte) -- i64.mask :abstraction)) + + (def: .public + (-> Int (Try )) + (let [positive (|> (n.* i64.bits_per_byte) i64.mask) + negative (|> positive .int (i.right_shifted 1) i64.not)] + (function (_ value) + (if (i.= (if (i.< +0 value) + (i64.or negative value) + (i64.and positive value)) + value) + (#try.Success (:abstraction value)) + (exception.except ..value_exceeds_the_scope [value ]))))) - (template [ ] - [(def: .public ( parameter subject) - (-> (Try )) - ( - ( (:representation parameter) - (:representation subject))))] + (template [ ] + [(def: .public ( parameter subject) + (-> (Try )) + ( + ( (:representation parameter) + (:representation subject))))] - [<+> i.+] - [<-> i.-] - )] + [<+> i.+] + [<-> i.-] + )] - [1 S1 bytes/1 s1 maximum/1 +/1 -/1] - [2 S2 bytes/2 s2 maximum/2 +/2 -/2] - [4 S4 bytes/4 s4 maximum/4 +/4 -/4] - ) + [1 S1 bytes/1 s1 maximum/1 +/1 -/1] + [2 S2 bytes/2 s2 maximum/2 +/2 -/2] + [4 S4 bytes/4 s4 maximum/4 +/4 -/4] + ) - (template [ ] - [(def: .public - (-> ) - (|>> :transmutation))] + (template [ ] + [(def: .public + (-> ) + (|>> :transmutation))] - [lifted/2 S1 S2] - [lifted/4 S2 S4] - ) + [lifted/2 S1 S2] + [lifted/4 S2 S4] + ) - (template [ ] - [(def: .public - (Writer ) - (|>> :representation ))] + (template [ ] + [(def: .public + (Writer ) + (|>> :representation ))] - [writer/1 S1 format.bits/8] - [writer/2 S2 format.bits/16] - [writer/4 S4 format.bits/32] - ) + [writer/1 S1 format.bits/8] + [writer/2 S2 format.bits/16] + [writer/4 S4 format.bits/32] + )] ) diff --git a/stdlib/source/library/lux/target/jvm/encoding/unsigned.lux b/stdlib/source/library/lux/target/jvm/encoding/unsigned.lux index 863aadea3..199ea697a 100644 --- a/stdlib/source/library/lux/target/jvm/encoding/unsigned.lux +++ b/stdlib/source/library/lux/target/jvm/encoding/unsigned.lux @@ -22,102 +22,100 @@ abstract]]]) (abstract: .public (Unsigned brand) - {} - Nat - (def: .public value - (-> (Unsigned Any) Nat) - (|>> :representation)) - - (implementation: .public equivalence - (All (_ brand) (Equivalence (Unsigned brand))) - (def: (= reference sample) - (n.= (:representation reference) - (:representation sample)))) - - (implementation: .public order - (All (_ brand) (Order (Unsigned brand))) - - (def: &equivalence ..equivalence) - (def: (< reference sample) - (n.< (:representation reference) - (:representation sample)))) - - (exception: .public (value_exceeds_the_maximum {type Name} - {value Nat} - {maximum (Unsigned Any)}) - (exception.report - ["Type" (%.name type)] - ["Value" (%.nat value)] - ["Maximum" (%.nat (:representation maximum))])) - - (exception: .public [brand] (subtraction_cannot_yield_negative_value - {type Name} - {parameter (Unsigned brand)} - {subject (Unsigned brand)}) - (exception.report - ["Type" (%.name type)] - ["Parameter" (%.nat (:representation parameter))] - ["Subject" (%.nat (:representation subject))])) - - (template [ <+> <-> ] - [(with_expansions [ (template.identifier [ "'"])] - (abstract: .public {} Any) - (type: .public (Unsigned ))) - - (def: .public ) - - (def: .public - - (|> (n.* i64.bits_per_byte) i64.mask :abstraction)) + [(def: .public value + (-> (Unsigned Any) Nat) + (|>> :representation)) + + (implementation: .public equivalence + (All (_ brand) (Equivalence (Unsigned brand))) + (def: (= reference sample) + (n.= (:representation reference) + (:representation sample)))) + + (implementation: .public order + (All (_ brand) (Order (Unsigned brand))) - (def: .public ( value) - (-> Nat (Try )) - (if (n.> (:representation ) value) - (exception.except ..value_exceeds_the_maximum [(name_of ) value ]) - (#try.Success (:abstraction value)))) - - (def: .public (<+> parameter subject) - (-> (Try )) - ( - (n.+ (:representation parameter) - (:representation subject)))) - - (def: .public (<-> parameter subject) - (-> (Try )) - (let [parameter' (:representation parameter) - subject' (:representation subject)] - (if (n.> subject' parameter') - (exception.except ..subtraction_cannot_yield_negative_value [(name_of ) parameter subject]) - (#try.Success (:abstraction (n.- parameter' subject')))))) - - (def: .public ( left right) - (-> ) - (:abstraction (n.max (:representation left) - (:representation right))))] - - [1 U1 bytes/1 u1 maximum/1 +/1 -/1 max/1] - [2 U2 bytes/2 u2 maximum/2 +/2 -/2 max/2] - [4 U4 bytes/4 u4 maximum/4 +/4 -/4 max/4] - ) - - (template [ ] - [(def: .public - (-> ) - (|>> :transmutation))] - - [lifted/2 U1 U2] - [lifted/4 U2 U4] - ) - - (template [ ] - [(def: .public - (Writer ) - (|>> :representation ))] - - [writer/1 U1 format.bits/8] - [writer/2 U2 format.bits/16] - [writer/4 U4 format.bits/32] - ) + (def: &equivalence ..equivalence) + (def: (< reference sample) + (n.< (:representation reference) + (:representation sample)))) + + (exception: .public (value_exceeds_the_maximum {type Name} + {value Nat} + {maximum (Unsigned Any)}) + (exception.report + ["Type" (%.name type)] + ["Value" (%.nat value)] + ["Maximum" (%.nat (:representation maximum))])) + + (exception: .public [brand] (subtraction_cannot_yield_negative_value + {type Name} + {parameter (Unsigned brand)} + {subject (Unsigned brand)}) + (exception.report + ["Type" (%.name type)] + ["Parameter" (%.nat (:representation parameter))] + ["Subject" (%.nat (:representation subject))])) + + (template [ <+> <-> ] + [(with_expansions [ (template.identifier [ "'"])] + (abstract: .public Any []) + (type: .public (Unsigned ))) + + (def: .public ) + + (def: .public + + (|> (n.* i64.bits_per_byte) i64.mask :abstraction)) + + (def: .public ( value) + (-> Nat (Try )) + (if (n.> (:representation ) value) + (exception.except ..value_exceeds_the_maximum [(name_of ) value ]) + (#try.Success (:abstraction value)))) + + (def: .public (<+> parameter subject) + (-> (Try )) + ( + (n.+ (:representation parameter) + (:representation subject)))) + + (def: .public (<-> parameter subject) + (-> (Try )) + (let [parameter' (:representation parameter) + subject' (:representation subject)] + (if (n.> subject' parameter') + (exception.except ..subtraction_cannot_yield_negative_value [(name_of ) parameter subject]) + (#try.Success (:abstraction (n.- parameter' subject')))))) + + (def: .public ( left right) + (-> ) + (:abstraction (n.max (:representation left) + (:representation right))))] + + [1 U1 bytes/1 u1 maximum/1 +/1 -/1 max/1] + [2 U2 bytes/2 u2 maximum/2 +/2 -/2 max/2] + [4 U4 bytes/4 u4 maximum/4 +/4 -/4 max/4] + ) + + (template [ ] + [(def: .public + (-> ) + (|>> :transmutation))] + + [lifted/2 U1 U2] + [lifted/4 U2 U4] + ) + + (template [ ] + [(def: .public + (Writer ) + (|>> :representation ))] + + [writer/1 U1 format.bits/8] + [writer/2 U2 format.bits/16] + [writer/4 U4 format.bits/32] + )] ) diff --git a/stdlib/source/library/lux/target/jvm/index.lux b/stdlib/source/library/lux/target/jvm/index.lux index 6a45de99d..cdf27baba 100644 --- a/stdlib/source/library/lux/target/jvm/index.lux +++ b/stdlib/source/library/lux/target/jvm/index.lux @@ -16,25 +16,23 @@ //unsigned.bytes/2) (abstract: .public (Index kind) - {} - U2 - (def: .public index - (All (_ kind) (-> U2 (Index kind))) - (|>> :abstraction)) + [(def: .public index + (All (_ kind) (-> U2 (Index kind))) + (|>> :abstraction)) - (def: .public value - (-> (Index Any) U2) - (|>> :representation)) + (def: .public value + (-> (Index Any) U2) + (|>> :representation)) - (def: .public equivalence - (All (_ kind) (Equivalence (Index kind))) - (\ equivalence.functor each - ..value - //unsigned.equivalence)) + (def: .public equivalence + (All (_ kind) (Equivalence (Index kind))) + (\ equivalence.functor each + ..value + //unsigned.equivalence)) - (def: .public writer - (All (_ kind) (Writer (Index kind))) - (|>> :representation //unsigned.writer/2)) + (def: .public writer + (All (_ kind) (Writer (Index kind))) + (|>> :representation //unsigned.writer/2))] ) diff --git a/stdlib/source/library/lux/target/jvm/modifier.lux b/stdlib/source/library/lux/target/jvm/modifier.lux index bb066ab29..48c0697d9 100644 --- a/stdlib/source/library/lux/target/jvm/modifier.lux +++ b/stdlib/source/library/lux/target/jvm/modifier.lux @@ -24,60 +24,58 @@ ["[1][0]" unsigned]]]) (abstract: .public (Modifier of) - {} - //unsigned.U2 - (def: .public code - (-> (Modifier Any) //unsigned.U2) - (|>> :representation)) + [(def: .public code + (-> (Modifier Any) //unsigned.U2) + (|>> :representation)) - (implementation: .public equivalence - (All (_ of) (Equivalence (Modifier of))) - - (def: (= reference sample) - (\ //unsigned.equivalence = - (:representation reference) - (:representation sample)))) + (implementation: .public equivalence + (All (_ of) (Equivalence (Modifier of))) + + (def: (= reference sample) + (\ //unsigned.equivalence = + (:representation reference) + (:representation sample)))) - (template: (!wrap value) - [(|> value - //unsigned.u2 - try.trusted - :abstraction)]) + (template: (!wrap value) + [(|> value + //unsigned.u2 + try.trusted + :abstraction)]) - (template: (!unwrap value) - [(|> value - :representation - //unsigned.value)]) + (template: (!unwrap value) + [(|> value + :representation + //unsigned.value)]) - (def: .public (has? sub super) - (All (_ of) (-> (Modifier of) (Modifier of) Bit)) - (let [sub (!unwrap sub)] - (|> (!unwrap super) - (i64.and sub) - (\ i64.equivalence = sub)))) + (def: .public (has? sub super) + (All (_ of) (-> (Modifier of) (Modifier of) Bit)) + (let [sub (!unwrap sub)] + (|> (!unwrap super) + (i64.and sub) + (\ i64.equivalence = sub)))) - (implementation: .public monoid - (All (_ of) (Monoid (Modifier of))) + (implementation: .public monoid + (All (_ of) (Monoid (Modifier of))) - (def: identity - (!wrap (hex "0000"))) - - (def: (composite left right) - (!wrap (i64.or (!unwrap left) (!unwrap right))))) + (def: identity + (!wrap (hex "0000"))) + + (def: (composite left right) + (!wrap (i64.or (!unwrap left) (!unwrap right))))) - (def: .public empty - Modifier - (\ ..monoid identity)) + (def: .public empty + Modifier + (\ ..monoid identity)) - (def: .public writer - (All (_ of) (Writer (Modifier of))) - (|>> :representation //unsigned.writer/2)) + (def: .public writer + (All (_ of) (Writer (Modifier of))) + (|>> :representation //unsigned.writer/2)) - (def: modifier - (-> Nat Modifier) - (|>> !wrap)) + (def: modifier + (-> Nat Modifier) + (|>> !wrap))] ) (syntax: .public (modifiers: [ofT .any diff --git a/stdlib/source/library/lux/target/jvm/modifier/inner.lux b/stdlib/source/library/lux/target/jvm/modifier/inner.lux index a3777c380..6327fefa8 100644 --- a/stdlib/source/library/lux/target/jvm/modifier/inner.lux +++ b/stdlib/source/library/lux/target/jvm/modifier/inner.lux @@ -5,7 +5,7 @@ abstract]]] [// {"+" [modifiers:]}]) -(abstract: .public Inner {} Any) +(abstract: .public Inner Any []) (modifiers: Inner ["0001" public] diff --git a/stdlib/source/library/lux/target/jvm/type.lux b/stdlib/source/library/lux/target/jvm/type.lux index 8cac8e4df..e3ec58a89 100644 --- a/stdlib/source/library/lux/target/jvm/type.lux +++ b/stdlib/source/library/lux/target/jvm/type.lux @@ -26,169 +26,169 @@ ["[1][0]" reflection {"+" [Reflection]}]]) (abstract: .public (Type category) - {} - - [(Signature category) (Descriptor category) (Reflection category)] - - (type: .public Argument - [Text (Type Value)]) - - (type: .public (Typed a) - [(Type Value) a]) - - (type: .public Constraint - (Record - [#name Text - #super_class (Type Class) - #super_interfaces (List (Type Class))])) - - (template [