aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/library/lux/tool/compiler
diff options
context:
space:
mode:
authorEduardo Julian2021-09-08 03:08:13 -0400
committerEduardo Julian2021-09-08 03:08:13 -0400
commit392582885500d8201bbe502943ca4b02c5c77ac0 (patch)
tree6e7410546048547560c767dba9c303d3f2f9597a /stdlib/source/library/lux/tool/compiler
parent609cc6c16e75c13d87183c38245136fa038b0496 (diff)
Normalized the syntax of "abstract:" and "actor:".
Diffstat (limited to 'stdlib/source/library/lux/tool/compiler')
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/archive.lux400
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/archive/artifact.lux240
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/archive/document.lux72
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/archive/key.lux14
4 files changed, 359 insertions, 367 deletions
diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive.lux b/stdlib/source/library/lux/tool/compiler/meta/archive.lux
index 96a8683de..d57f4a08b 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/archive.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/archive.lux
@@ -75,213 +75,211 @@
"")
(abstract: .public Archive
- {}
-
(Record
[#next ID
#resolver (Dictionary Module [ID (Maybe [Descriptor (Document Any) Output])])])
- (def: next
- (-> Archive ID)
- (|>> :representation (value@ #next)))
-
- (def: .public empty
- Archive
- (:abstraction [#next 0
- #resolver (dictionary.empty text.hash)]))
-
- (def: .public (id module archive)
- (-> Module Archive (Try ID))
- (let [(^slots [#..resolver]) (:representation archive)]
- (case (dictionary.value module resolver)
- (#.Some [id _])
- (#try.Success id)
-
- #.None
- (exception.except ..unknown_document [module
- (dictionary.keys resolver)]))))
-
- (def: .public (reserve module archive)
- (-> Module Archive (Try [ID Archive]))
- (let [(^slots [#..next #..resolver]) (:representation archive)]
- (case (dictionary.value module resolver)
- (#.Some _)
- (exception.except ..module_has_already_been_reserved [module])
-
- #.None
- (#try.Success [next
- (|> archive
+ [(def: next
+ (-> Archive ID)
+ (|>> :representation (value@ #next)))
+
+ (def: .public empty
+ Archive
+ (:abstraction [#next 0
+ #resolver (dictionary.empty text.hash)]))
+
+ (def: .public (id module archive)
+ (-> Module Archive (Try ID))
+ (let [(^slots [#..resolver]) (:representation archive)]
+ (case (dictionary.value module resolver)
+ (#.Some [id _])
+ (#try.Success id)
+
+ #.None
+ (exception.except ..unknown_document [module
+ (dictionary.keys resolver)]))))
+
+ (def: .public (reserve module archive)
+ (-> Module Archive (Try [ID Archive]))
+ (let [(^slots [#..next #..resolver]) (:representation archive)]
+ (case (dictionary.value module resolver)
+ (#.Some _)
+ (exception.except ..module_has_already_been_reserved [module])
+
+ #.None
+ (#try.Success [next
+ (|> archive
+ :representation
+ (revised@ #..resolver (dictionary.has module [next #.None]))
+ (revised@ #..next ++)
+ :abstraction)]))))
+
+ (def: .public (has module [descriptor document output] archive)
+ (-> Module [Descriptor (Document Any) Output] Archive (Try Archive))
+ (let [(^slots [#..resolver]) (:representation archive)]
+ (case (dictionary.value module resolver)
+ (#.Some [id #.None])
+ (#try.Success (|> archive
:representation
- (revised@ #..resolver (dictionary.has module [next #.None]))
- (revised@ #..next ++)
- :abstraction)]))))
-
- (def: .public (has module [descriptor document output] archive)
- (-> Module [Descriptor (Document Any) Output] Archive (Try Archive))
- (let [(^slots [#..resolver]) (:representation archive)]
- (case (dictionary.value module resolver)
- (#.Some [id #.None])
- (#try.Success (|> archive
- :representation
- (revised@ #..resolver (dictionary.has module [id (#.Some [descriptor document output])]))
- :abstraction))
-
- (#.Some [id (#.Some [existing_descriptor existing_document existing_output])])
- (if (same? document existing_document)
- ... TODO: Find out why this code allows for the same module to be added more than once. It looks fishy...
- (#try.Success archive)
- (exception.except ..cannot_replace_document [module existing_document document]))
-
- #.None
- (exception.except ..module_must_be_reserved_before_it_can_be_added [module]))))
-
- (def: .public (find module archive)
- (-> Module Archive (Try [Descriptor (Document Any) Output]))
- (let [(^slots [#..resolver]) (:representation archive)]
- (case (dictionary.value module resolver)
- (#.Some [id (#.Some entry)])
- (#try.Success entry)
-
- (#.Some [id #.None])
- (exception.except ..module_is_only_reserved [module])
-
- #.None
- (exception.except ..unknown_document [module
- (dictionary.keys resolver)]))))
-
- (def: .public (archived? archive module)
- (-> Archive Module Bit)
- (case (..find module archive)
- (#try.Success _)
- bit.yes
-
- (#try.Failure _)
- bit.no))
-
- (def: .public archived
- (-> Archive (List Module))
- (|>> :representation
- (value@ #resolver)
- dictionary.entries
- (list.all (function (_ [module [id descriptor+document]])
- (case descriptor+document
- (#.Some _) (#.Some module)
- #.None #.None)))))
-
- (def: .public (reserved? archive module)
- (-> Archive Module Bit)
- (let [(^slots [#..resolver]) (:representation archive)]
- (case (dictionary.value module resolver)
- (#.Some [id _])
- bit.yes
-
- #.None
- bit.no)))
-
- (def: .public reserved
- (-> Archive (List Module))
- (|>> :representation
- (value@ #resolver)
- dictionary.keys))
-
- (def: .public reservations
- (-> Archive (List [Module ID]))
- (|>> :representation
- (value@ #resolver)
- dictionary.entries
- (list\each (function (_ [module [id _]])
- [module id]))))
-
- (def: .public (merged additions archive)
- (-> Archive Archive Archive)
- (let [[+next +resolver] (:representation additions)]
- (|> archive
- :representation
- (revised@ #next (n.max +next))
- (revised@ #resolver (function (_ resolver)
- (list\mix (function (_ [module [id entry]] resolver)
- (case entry
- (#.Some _)
- (dictionary.has module [id entry] resolver)
-
- #.None
- resolver))
- resolver
- (dictionary.entries +resolver))))
- :abstraction)))
-
- (type: Reservation
- [Module ID])
-
- (type: Frozen
- [Version ID (List Reservation)])
-
- (def: reader
- (Parser ..Frozen)
- ($_ <>.and
- <binary>.nat
- <binary>.nat
- (<binary>.list (<>.and <binary>.text <binary>.nat))))
-
- (def: writer
- (Writer ..Frozen)
- ($_ binary.and
- binary.nat
- binary.nat
- (binary.list (binary.and binary.text binary.nat))))
-
- (def: .public (export version archive)
- (-> Version Archive Binary)
- (let [(^slots [#..next #..resolver]) (:representation archive)]
- (|> resolver
+ (revised@ #..resolver (dictionary.has module [id (#.Some [descriptor document output])]))
+ :abstraction))
+
+ (#.Some [id (#.Some [existing_descriptor existing_document existing_output])])
+ (if (same? document existing_document)
+ ... TODO: Find out why this code allows for the same module to be added more than once. It looks fishy...
+ (#try.Success archive)
+ (exception.except ..cannot_replace_document [module existing_document document]))
+
+ #.None
+ (exception.except ..module_must_be_reserved_before_it_can_be_added [module]))))
+
+ (def: .public (find module archive)
+ (-> Module Archive (Try [Descriptor (Document Any) Output]))
+ (let [(^slots [#..resolver]) (:representation archive)]
+ (case (dictionary.value module resolver)
+ (#.Some [id (#.Some entry)])
+ (#try.Success entry)
+
+ (#.Some [id #.None])
+ (exception.except ..module_is_only_reserved [module])
+
+ #.None
+ (exception.except ..unknown_document [module
+ (dictionary.keys resolver)]))))
+
+ (def: .public (archived? archive module)
+ (-> Archive Module Bit)
+ (case (..find module archive)
+ (#try.Success _)
+ bit.yes
+
+ (#try.Failure _)
+ bit.no))
+
+ (def: .public archived
+ (-> Archive (List Module))
+ (|>> :representation
+ (value@ #resolver)
dictionary.entries
(list.all (function (_ [module [id descriptor+document]])
(case descriptor+document
- (#.Some _) (#.Some [module id])
- #.None #.None)))
- [version next]
- (binary.result ..writer))))
-
- (exception: .public (version_mismatch {expected Version} {actual Version})
- (exception.report
- ["Expected" (%.nat expected)]
- ["Actual" (%.nat actual)]))
-
- (exception: .public corrupt_data)
-
- (def: (correct_modules? reservations)
- (-> (List Reservation) Bit)
- (n.= (list.size reservations)
- (|> reservations
- (list\each product.left)
- (set.of_list text.hash)
- set.size)))
-
- (def: (correct_ids? reservations)
- (-> (List Reservation) Bit)
- (n.= (list.size reservations)
- (|> reservations
- (list\each product.right)
- (set.of_list n.hash)
- set.size)))
-
- (def: (correct_reservations? reservations)
- (-> (List Reservation) Bit)
- (and (correct_modules? reservations)
- (correct_ids? reservations)))
-
- (def: .public (import expected binary)
- (-> Version Binary (Try Archive))
- (do try.monad
- [[actual next reservations] (<binary>.result ..reader binary)
- _ (exception.assertion ..version_mismatch [expected actual]
- (n\= expected actual))
- _ (exception.assertion ..corrupt_data []
- (correct_reservations? reservations))]
- (in (:abstraction
- [#next next
- #resolver (list\mix (function (_ [module id] archive)
- (dictionary.has module [id #.None] archive))
- (value@ #resolver (:representation ..empty))
- reservations)]))))
+ (#.Some _) (#.Some module)
+ #.None #.None)))))
+
+ (def: .public (reserved? archive module)
+ (-> Archive Module Bit)
+ (let [(^slots [#..resolver]) (:representation archive)]
+ (case (dictionary.value module resolver)
+ (#.Some [id _])
+ bit.yes
+
+ #.None
+ bit.no)))
+
+ (def: .public reserved
+ (-> Archive (List Module))
+ (|>> :representation
+ (value@ #resolver)
+ dictionary.keys))
+
+ (def: .public reservations
+ (-> Archive (List [Module ID]))
+ (|>> :representation
+ (value@ #resolver)
+ dictionary.entries
+ (list\each (function (_ [module [id _]])
+ [module id]))))
+
+ (def: .public (merged additions archive)
+ (-> Archive Archive Archive)
+ (let [[+next +resolver] (:representation additions)]
+ (|> archive
+ :representation
+ (revised@ #next (n.max +next))
+ (revised@ #resolver (function (_ resolver)
+ (list\mix (function (_ [module [id entry]] resolver)
+ (case entry
+ (#.Some _)
+ (dictionary.has module [id entry] resolver)
+
+ #.None
+ resolver))
+ resolver
+ (dictionary.entries +resolver))))
+ :abstraction)))
+
+ (type: Reservation
+ [Module ID])
+
+ (type: Frozen
+ [Version ID (List Reservation)])
+
+ (def: reader
+ (Parser ..Frozen)
+ ($_ <>.and
+ <binary>.nat
+ <binary>.nat
+ (<binary>.list (<>.and <binary>.text <binary>.nat))))
+
+ (def: writer
+ (Writer ..Frozen)
+ ($_ binary.and
+ binary.nat
+ binary.nat
+ (binary.list (binary.and binary.text binary.nat))))
+
+ (def: .public (export version archive)
+ (-> Version Archive Binary)
+ (let [(^slots [#..next #..resolver]) (:representation archive)]
+ (|> resolver
+ dictionary.entries
+ (list.all (function (_ [module [id descriptor+document]])
+ (case descriptor+document
+ (#.Some _) (#.Some [module id])
+ #.None #.None)))
+ [version next]
+ (binary.result ..writer))))
+
+ (exception: .public (version_mismatch {expected Version} {actual Version})
+ (exception.report
+ ["Expected" (%.nat expected)]
+ ["Actual" (%.nat actual)]))
+
+ (exception: .public corrupt_data)
+
+ (def: (correct_modules? reservations)
+ (-> (List Reservation) Bit)
+ (n.= (list.size reservations)
+ (|> reservations
+ (list\each product.left)
+ (set.of_list text.hash)
+ set.size)))
+
+ (def: (correct_ids? reservations)
+ (-> (List Reservation) Bit)
+ (n.= (list.size reservations)
+ (|> reservations
+ (list\each product.right)
+ (set.of_list n.hash)
+ set.size)))
+
+ (def: (correct_reservations? reservations)
+ (-> (List Reservation) Bit)
+ (and (correct_modules? reservations)
+ (correct_ids? reservations)))
+
+ (def: .public (import expected binary)
+ (-> Version Binary (Try Archive))
+ (do try.monad
+ [[actual next reservations] (<binary>.result ..reader binary)
+ _ (exception.assertion ..version_mismatch [expected actual]
+ (n\= expected actual))
+ _ (exception.assertion ..corrupt_data []
+ (correct_reservations? reservations))]
+ (in (:abstraction
+ [#next next
+ #resolver (list\mix (function (_ [module id] archive)
+ (dictionary.has module [id #.None] archive))
+ (value@ #resolver (:representation ..empty))
+ reservations)]))))]
)
diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive/artifact.lux b/stdlib/source/library/lux/tool/compiler/meta/archive/artifact.lux
index e0bb8536f..e3ad0fd89 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/archive/artifact.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/archive/artifact.lux
@@ -40,129 +40,127 @@
#category Category]))
(abstract: .public Registry
- {}
-
(Record
[#artifacts (Row Artifact)
#resolver (Dictionary Text ID)])
- (def: .public empty
- Registry
- (:abstraction [#artifacts row.empty
- #resolver (dictionary.empty text.hash)]))
-
- (def: .public artifacts
- (-> Registry (Row Artifact))
- (|>> :representation (value@ #artifacts)))
-
- (def: next
- (-> Registry ID)
- (|>> ..artifacts row.size))
-
- (def: .public (resource registry)
- (-> Registry [ID Registry])
- (let [id (..next registry)]
- [id
- (|> registry
- :representation
- (revised@ #artifacts (row.suffix [#id id
- #category #Anonymous]))
- :abstraction)]))
-
- (template [<tag> <create> <fetch>]
- [(def: .public (<create> name registry)
- (-> Text Registry [ID Registry])
- (let [id (..next registry)]
- [id
- (|> registry
- :representation
- (revised@ #artifacts (row.suffix [#id id
- #category (<tag> name)]))
- (revised@ #resolver (dictionary.has name id))
- :abstraction)]))
-
- (def: .public (<fetch> registry)
- (-> Registry (List Text))
- (|> registry
- :representation
- (value@ #artifacts)
- row.list
- (list.all (|>> (value@ #category)
- (case> (<tag> name) (#.Some name)
- _ #.None)))))]
-
- [#Definition definition definitions]
- [#Analyser analyser analysers]
- [#Synthesizer synthesizer synthesizers]
- [#Generator generator generators]
- [#Directive directive directives]
- [#Custom custom customs]
- )
-
- (def: .public (remember name registry)
- (-> Text Registry (Maybe ID))
- (|> (:representation registry)
- (value@ #resolver)
- (dictionary.value name)))
-
- (def: .public writer
- (Writer Registry)
- (let [category (: (Writer Category)
- (function (_ value)
- (case value
- (^template [<nat> <tag> <writer>]
- [(<tag> value) ((binary.and binary.nat <writer>) [<nat> value])])
- ([0 #Anonymous binary.any]
- [1 #Definition binary.text]
- [2 #Analyser binary.text]
- [3 #Synthesizer binary.text]
- [4 #Generator binary.text]
- [5 #Directive binary.text]
- [6 #Custom binary.text]))))
- artifacts (: (Writer (Row Category))
- (binary.row/64 category))]
- (|>> :representation
- (value@ #artifacts)
- (row\each (value@ #category))
- artifacts)))
-
- (exception: .public (invalid_category {tag Nat})
- (exception.report
- ["Tag" (%.nat tag)]))
-
- (def: .public parser
- (Parser Registry)
- (let [category (: (Parser Category)
- (do [! <>.monad]
- [tag <binary>.nat]
- (case tag
- (^template [<nat> <tag> <parser>]
- [<nat> (\ ! each (|>> <tag>) <parser>)])
- ([0 #Anonymous <binary>.any]
- [1 #Definition <binary>.text]
- [2 #Analyser <binary>.text]
- [3 #Synthesizer <binary>.text]
- [4 #Generator <binary>.text]
- [5 #Directive <binary>.text]
- [6 #Custom <binary>.text])
-
- _ (<>.failure (exception.error ..invalid_category [tag])))))]
- (|> (<binary>.row/64 category)
- (\ <>.monad each (row\mix (function (_ artifact registry)
- (product.right
- (case artifact
- #Anonymous
- (..resource registry)
-
- (^template [<tag> <create>]
- [(<tag> name)
- (<create> name registry)])
- ([#Definition ..definition]
- [#Analyser ..analyser]
- [#Synthesizer ..synthesizer]
- [#Generator ..generator]
- [#Directive ..directive]
- [#Custom ..custom])
- )))
- ..empty)))))
+ [(def: .public empty
+ Registry
+ (:abstraction [#artifacts row.empty
+ #resolver (dictionary.empty text.hash)]))
+
+ (def: .public artifacts
+ (-> Registry (Row Artifact))
+ (|>> :representation (value@ #artifacts)))
+
+ (def: next
+ (-> Registry ID)
+ (|>> ..artifacts row.size))
+
+ (def: .public (resource registry)
+ (-> Registry [ID Registry])
+ (let [id (..next registry)]
+ [id
+ (|> registry
+ :representation
+ (revised@ #artifacts (row.suffix [#id id
+ #category #Anonymous]))
+ :abstraction)]))
+
+ (template [<tag> <create> <fetch>]
+ [(def: .public (<create> name registry)
+ (-> Text Registry [ID Registry])
+ (let [id (..next registry)]
+ [id
+ (|> registry
+ :representation
+ (revised@ #artifacts (row.suffix [#id id
+ #category (<tag> name)]))
+ (revised@ #resolver (dictionary.has name id))
+ :abstraction)]))
+
+ (def: .public (<fetch> registry)
+ (-> Registry (List Text))
+ (|> registry
+ :representation
+ (value@ #artifacts)
+ row.list
+ (list.all (|>> (value@ #category)
+ (case> (<tag> name) (#.Some name)
+ _ #.None)))))]
+
+ [#Definition definition definitions]
+ [#Analyser analyser analysers]
+ [#Synthesizer synthesizer synthesizers]
+ [#Generator generator generators]
+ [#Directive directive directives]
+ [#Custom custom customs]
+ )
+
+ (def: .public (remember name registry)
+ (-> Text Registry (Maybe ID))
+ (|> (:representation registry)
+ (value@ #resolver)
+ (dictionary.value name)))
+
+ (def: .public writer
+ (Writer Registry)
+ (let [category (: (Writer Category)
+ (function (_ value)
+ (case value
+ (^template [<nat> <tag> <writer>]
+ [(<tag> value) ((binary.and binary.nat <writer>) [<nat> value])])
+ ([0 #Anonymous binary.any]
+ [1 #Definition binary.text]
+ [2 #Analyser binary.text]
+ [3 #Synthesizer binary.text]
+ [4 #Generator binary.text]
+ [5 #Directive binary.text]
+ [6 #Custom binary.text]))))
+ artifacts (: (Writer (Row Category))
+ (binary.row/64 category))]
+ (|>> :representation
+ (value@ #artifacts)
+ (row\each (value@ #category))
+ artifacts)))
+
+ (exception: .public (invalid_category {tag Nat})
+ (exception.report
+ ["Tag" (%.nat tag)]))
+
+ (def: .public parser
+ (Parser Registry)
+ (let [category (: (Parser Category)
+ (do [! <>.monad]
+ [tag <binary>.nat]
+ (case tag
+ (^template [<nat> <tag> <parser>]
+ [<nat> (\ ! each (|>> <tag>) <parser>)])
+ ([0 #Anonymous <binary>.any]
+ [1 #Definition <binary>.text]
+ [2 #Analyser <binary>.text]
+ [3 #Synthesizer <binary>.text]
+ [4 #Generator <binary>.text]
+ [5 #Directive <binary>.text]
+ [6 #Custom <binary>.text])
+
+ _ (<>.failure (exception.error ..invalid_category [tag])))))]
+ (|> (<binary>.row/64 category)
+ (\ <>.monad each (row\mix (function (_ artifact registry)
+ (product.right
+ (case artifact
+ #Anonymous
+ (..resource registry)
+
+ (^template [<tag> <create>]
+ [(<tag> name)
+ (<create> name registry)])
+ ([#Definition ..definition]
+ [#Analyser ..analyser]
+ [#Synthesizer ..synthesizer]
+ [#Generator ..generator]
+ [#Directive ..directive]
+ [#Custom ..custom])
+ )))
+ ..empty)))))]
)
diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive/document.lux b/stdlib/source/library/lux/tool/compiler/meta/archive/document.lux
index 6e56f7f8b..ddb71ac93 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/archive/document.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/archive/document.lux
@@ -26,50 +26,48 @@
["Actual" (signature.description actual)]))
(abstract: .public (Document d)
- {}
-
(Record
[#signature Signature
#content d])
- (def: .public (read key document)
- (All (_ d) (-> (Key d) (Document Any) (Try d)))
- (let [[document//signature document//content] (:representation document)]
- (if (\ signature.equivalence =
- (key.signature key)
- document//signature)
- (#try.Success (:sharing [e]
- (Key e)
- key
-
- e
- (:expected document//content)))
- (exception.except ..invalid_signature [(key.signature key)
- document//signature]))))
+ [(def: .public (read key document)
+ (All (_ d) (-> (Key d) (Document Any) (Try d)))
+ (let [[document//signature document//content] (:representation document)]
+ (if (\ signature.equivalence =
+ (key.signature key)
+ document//signature)
+ (#try.Success (:sharing [e]
+ (Key e)
+ key
+
+ e
+ (:expected document//content)))
+ (exception.except ..invalid_signature [(key.signature key)
+ document//signature]))))
- (def: .public (write key content)
- (All (_ d) (-> (Key d) d (Document d)))
- (:abstraction [#signature (key.signature key)
- #content content]))
+ (def: .public (write key content)
+ (All (_ d) (-> (Key d) d (Document d)))
+ (:abstraction [#signature (key.signature key)
+ #content content]))
- (def: .public (check key document)
- (All (_ d) (-> (Key d) (Document Any) (Try (Document d))))
- (do try.monad
- [_ (..read key document)]
- (in (:expected document))))
+ (def: .public (check key document)
+ (All (_ d) (-> (Key d) (Document Any) (Try (Document d))))
+ (do try.monad
+ [_ (..read key document)]
+ (in (:expected document))))
- (def: .public signature
- (-> (Document Any) Signature)
- (|>> :representation (value@ #signature)))
+ (def: .public signature
+ (-> (Document Any) Signature)
+ (|>> :representation (value@ #signature)))
- (def: .public (writer content)
- (All (_ d) (-> (Writer d) (Writer (Document d))))
- (let [writer (binary.and signature.writer
- content)]
- (|>> :representation writer)))
+ (def: .public (writer content)
+ (All (_ d) (-> (Writer d) (Writer (Document d))))
+ (let [writer (binary.and signature.writer
+ content)]
+ (|>> :representation writer)))
- (def: .public parser
- (All (_ d) (-> (Parser d) (Parser (Document d))))
- (|>> (<>.and signature.parser)
- (\ <>.monad each (|>> :abstraction))))
+ (def: .public parser
+ (All (_ d) (-> (Parser d) (Parser (Document d))))
+ (|>> (<>.and signature.parser)
+ (\ <>.monad each (|>> :abstraction))))]
)
diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive/key.lux b/stdlib/source/library/lux/tool/compiler/meta/archive/key.lux
index e6cac3246..b31b18353 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/archive/key.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/archive/key.lux
@@ -7,15 +7,13 @@
[signature {"+" [Signature]}]])
(abstract: .public (Key k)
- {}
-
Signature
- (def: .public signature
- (-> (Key Any) Signature)
- (|>> :representation))
+ [(def: .public signature
+ (-> (Key Any) Signature)
+ (|>> :representation))
- (def: .public (key signature sample)
- (All (_ d) (-> Signature d (Key d)))
- (:abstraction signature))
+ (def: .public (key signature sample)
+ (All (_ d) (-> Signature d (Key d)))
+ (:abstraction signature))]
)