aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/library/lux.lux
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib/source/library/lux.lux')
-rw-r--r--stdlib/source/library/lux.lux762
1 files changed, 487 insertions, 275 deletions
diff --git a/stdlib/source/library/lux.lux b/stdlib/source/library/lux.lux
index 6046012c7..efe42c285 100644
--- a/stdlib/source/library/lux.lux
+++ b/stdlib/source/library/lux.lux
@@ -219,12 +219,14 @@
#1)
(.def# tag
- (.is# {3 #0 Label Tag}
+ (.is# {3 #0 Label
+ Tag}
([_ it] (.as# Tag it)))
#0)
(.def# slot
- (.is# {3 #0 Label Slot}
+ (.is# {3 #0 Label
+ Slot}
([_ it] (.as# Slot it)))
#0)
@@ -431,57 +433,68 @@
#0)
(.def# bit$
- (.is# {#Function Bit Code}
+ (.is# {#Function Bit
+ Code}
([_ value] (_ann {#Bit value})))
#0)
(.def# nat$
- (.is# {#Function Nat Code}
+ (.is# {#Function Nat
+ Code}
([_ value] (_ann {#Nat value})))
#0)
(.def# int$
- (.is# {#Function Int Code}
+ (.is# {#Function Int
+ Code}
([_ value] (_ann {#Int value})))
#0)
(.def# rev$
- (.is# {#Function Rev Code}
+ (.is# {#Function Rev
+ Code}
([_ value] (_ann {#Rev value})))
#0)
(.def# frac$
- (.is# {#Function Frac Code}
+ (.is# {#Function Frac
+ Code}
([_ value] (_ann {#Frac value})))
#0)
(.def# text$
- (.is# {#Function Text Code}
+ (.is# {#Function Text
+ Code}
([_ text] (_ann {#Text text})))
#0)
(.def# symbol$
- (.is# {#Function Symbol Code}
+ (.is# {#Function Symbol
+ Code}
([_ name] (_ann {#Symbol name})))
#0)
(.def# local$
- (.is# {#Function Text Code}
+ (.is# {#Function Text
+ Code}
([_ name] (_ann {#Symbol ["" name]})))
#0)
(.def# form$
- (.is# {#Function {#Apply Code List} Code}
+ (.is# {#Function {#Apply Code List}
+ Code}
([_ tokens] (_ann {#Form tokens})))
#0)
(.def# variant$
- (.is# {#Function {#Apply Code List} Code}
+ (.is# {#Function {#Apply Code List}
+ Code}
([_ tokens] (_ann {#Variant tokens})))
#0)
(.def# tuple$
- (.is# {#Function {#Apply Code List} Code}
+ (.is# {#Function {#Apply Code List}
+ Code}
([_ tokens] (_ann {#Tuple tokens})))
#0)
@@ -945,14 +958,18 @@
... Base functions & macros
(.def# meta#in
- (.is# {#UnivQ {#End} {#Function {#Parameter 1} {#Apply {#Parameter 1} Meta}}}
+ (.is# {#UnivQ {#End}
+ {#Function {#Parameter 1}
+ {#Apply {#Parameter 1} Meta}}}
([_ val]
([_ state]
{#Right [state val]})))
#0)
(.def# failure
- (.is# {#UnivQ {#End} {#Function Text {#Apply {#Parameter 1} Meta}}}
+ (.is# {#UnivQ {#End}
+ {#Function Text
+ {#Apply {#Parameter 1} Meta}}}
([_ msg]
([_ state]
{#Left msg})))
@@ -971,7 +988,8 @@
#0)
(.def# symbol#encoded
- (.is# {#Function Symbol Text}
+ (.is# {#Function Symbol
+ Text}
([_ full_name]
({[module name]
({"" name
@@ -989,7 +1007,8 @@
... currently being defined. That name can then be fed into
... 'wrong_syntax_error' for easier maintenance of the error_messages.
(.def# wrong_syntax_error
- (.is# {#Function Symbol Text}
+ (.is# {#Function Symbol
+ Text}
([_ it]
(.text_composite# "Wrong syntax for " \'' (symbol#encoded it) \'' ".")))
#0)
@@ -1071,7 +1090,8 @@
#0)
(.def# as_macro
- (.is# {#Function Code Code}
+ (.is# {#Function Code
+ Code}
(function'' [expression]
(form$ {#Item (symbol$ [..prelude "as#"])
{#Item (symbol$ [..prelude "Macro"])
@@ -1141,12 +1161,14 @@
(def' .private (list#mix f init xs)
... (All (_ a b) (-> (-> b a a) a (List b) a))
- {#UnivQ {#End} {#UnivQ {#End} {#Function {#Function {#Parameter 1}
- {#Function {#Parameter 3}
- {#Parameter 3}}}
- {#Function {#Parameter 3}
- {#Function ($ List {#Parameter 1})
- {#Parameter 3}}}}}}
+ {#UnivQ {#End}
+ {#UnivQ {#End}
+ {#Function {#Function {#Parameter 1}
+ {#Function {#Parameter 3}
+ {#Parameter 3}}}
+ {#Function {#Parameter 3}
+ {#Function ($ List {#Parameter 1})
+ {#Parameter 3}}}}}}
({{#End}
init
@@ -1156,7 +1178,8 @@
(def' .private (list#reversed list)
{#UnivQ {#End}
- {#Function ($ List {#Parameter 1}) ($ List {#Parameter 1})}}
+ {#Function ($ List {#Parameter 1})
+ ($ List {#Parameter 1})}}
(list#mix (.is# {#UnivQ {#End}
{#Function {#Parameter 1} {#Function ($ List {#Parameter 1}) ($ List {#Parameter 1})}}}
(function'' [head tail] {#Item head tail}))
@@ -1232,7 +1255,8 @@
(def' .private (list#size list)
{#UnivQ {#End}
- {#Function ($ List {#Parameter 1}) Nat}}
+ {#Function ($ List {#Parameter 1})
+ Nat}}
(list#mix (function'' [_ acc] (.i64_+# 1 acc)) 0 list))
(def' .private (let$ binding value body)
@@ -1252,11 +1276,13 @@
{#End}}}}))
(def' .private (UnivQ$ body)
- {#Function Code Code}
+ {#Function Code
+ Code}
(variant$ {#Item (symbol$ [..prelude "#UnivQ"]) {#Item ..|#End| {#Item body {#End}}}}))
(def' .private (ExQ$ body)
- {#Function Code Code}
+ {#Function Code
+ Code}
(variant$ {#Item (symbol$ [..prelude "#ExQ"]) {#Item ..|#End| {#Item body {#End}}}}))
(def' .private quantification_level
@@ -1264,11 +1290,13 @@
(.text_composite# \'' "quantification_level" \''))
(def' .private quantified
- {#Function Code Code}
+ {#Function Code
+ Code}
(let$ (local$ ..quantification_level) (nat$ 0)))
(def' .private (quantified_type_parameter idx)
- {#Function Nat Code}
+ {#Function Nat
+ Code}
(variant$ {#Item (symbol$ [..prelude "#Parameter"])
{#Item (form$ {#Item (symbol$ [..prelude "i64_+#"])
{#Item (local$ ..quantification_level)
@@ -1277,11 +1305,13 @@
{#End}}}))
(def' .private (next_level depth)
- {#Function Nat Nat}
+ {#Function Nat
+ Nat}
(.i64_+# 2 depth))
(def' .private (self_id? id)
- {#Function Nat Bit}
+ {#Function Nat
+ Bit}
(.i64_=# id (.as# Nat
(.int_*# +2
(.int_/# +2
@@ -1339,7 +1369,8 @@
permission))
(def' .private (with_correct_quantification body)
- {#Function Code Code}
+ {#Function Code
+ Code}
(form$ {#Item (symbol$ [prelude "__adjusted_quantified_type__"])
{#Item (local$ ..quantification_level)
{#Item (nat$ 0)
@@ -1361,7 +1392,8 @@
(local$ ..quantification_level)))
(def' .private (initialized_quantification? lux)
- {#Function Lux Bit}
+ {#Function Lux
+ Bit}
({[..#info _ ..#source _ ..#current_module _ ..#modules _
..#scopes scopes ..#type_context _ ..#host _
..#seed _ ..#expected _ ..#location _ ..#extensions _
@@ -1544,7 +1576,9 @@
..Tuple)
(def' .private (pairs xs)
- (All (_ a) (-> ($ List a) ($ Maybe ($ List (Tuple a a)))))
+ (All (_ of)
+ (-> ($ List of)
+ ($ Maybe ($ List (Tuple of of)))))
({{#Item x {#Item y xs'}}
({{#Some tail}
{#Some {#Item [x y] tail}}
@@ -1583,8 +1617,9 @@
tokens)))
(def' .private (any? p xs)
- (All (_ a)
- (-> (-> a Bit) ($ List a) Bit))
+ (All (_ of)
+ (-> (-> of Bit) ($ List of)
+ Bit))
({{#End}
#0
@@ -1595,13 +1630,15 @@
xs))
(def' .private (with_location @ content)
- (-> Location Code Code)
+ (-> Location Code
+ Code)
(let' [[module line column] @]
(tuple$ (list (tuple$ (list (text$ module) (nat$ line) (nat$ column)))
content))))
(def' .private (untemplated_list tokens)
- (-> ($ List Code) Code)
+ (-> ($ List Code)
+ Code)
({{#End}
|#End|
@@ -1610,13 +1647,16 @@
tokens))
(def' .private (list#composite xs ys)
- (All (_ a) (-> ($ List a) ($ List a) ($ List a)))
+ (All (_ of)
+ (-> ($ List of) ($ List of)
+ ($ List of)))
(list#mix (function' [head tail] {#Item head tail})
ys
(list#reversed xs)))
(def' .private (right_associativity op a1 a2)
- (-> Code Code Code Code)
+ (-> Code Code Code
+ Code)
({[_ {#Form parts}]
(form$ (list#composite parts (list a1 a2)))
@@ -1625,8 +1665,9 @@
op))
(def' .private (function#flipped func)
- (All (_ a b c)
- (-> (-> a b c) (-> b a c)))
+ (All (_ left right output)
+ (-> (-> left right output)
+ (-> right left output)))
(function' [right left]
(func left right)))
@@ -1760,11 +1801,11 @@
tokens)))
(def' .private (monad#each m f xs)
- (All (_ m a b)
- (-> ($ Monad m)
- (-> a ($ m b))
- ($ List a)
- ($ m ($ List b))))
+ (All (_ ! input output)
+ (-> ($ Monad !)
+ (-> input ($ ! output))
+ ($ List input)
+ ($ ! ($ List output))))
(let' [[..#in in ..#then _] m]
({{#End}
(in {#End})
@@ -1804,12 +1845,12 @@
{#End})))
(def' .private (monad#mix m f y xs)
- (All (_ m a b)
- (-> ($ Monad m)
- (-> a b ($ m b))
- b
- ($ List a)
- ($ m b)))
+ (All (_ ! mix input)
+ (-> ($ Monad !)
+ (-> input mix ($ ! mix))
+ mix
+ ($ List input)
+ ($ ! mix)))
(let' [[..#in in ..#then _] m]
({{#End}
(in y)
@@ -1834,11 +1875,13 @@
(def' .private Property_List
Type
- (All (_ a) ($ List (Tuple Text a))))
+ (All (_ of)
+ ($ List (Tuple Text of))))
(def' .private (property#value k property_list)
- (All (_ a)
- (-> Text ($ Property_List a) ($ Maybe a)))
+ (All (_ of)
+ (-> Text ($ Property_List of)
+ ($ Maybe of)))
({{#Item [[k' v] property_list']}
(if (text#= k k')
{#Some v}
@@ -1849,8 +1892,9 @@
property_list))
(def' .private (property#with k v property_list)
- (All (_ a)
- (-> Text a ($ Property_List a) ($ Property_List a)))
+ (All (_ of)
+ (-> Text of ($ Property_List of)
+ ($ Property_List of)))
({{#Item [k' v'] property_list'}
(if (text#= k k')
(list#partial [k v] property_list')
@@ -1861,7 +1905,8 @@
property_list))
(def' .private (global_symbol full_name state)
- (-> Symbol ($ Meta Symbol))
+ (-> Symbol
+ ($ Meta Symbol))
(let' [[module name] full_name
[..#info info ..#source source ..#current_module _ ..#modules modules
..#scopes scopes ..#type_context types ..#host host
@@ -1888,14 +1933,16 @@
(property#value module modules))))
(def' .private (|List<Code>| expression)
- (-> Code Code)
+ (-> Code
+ Code)
(let' [type (variant$ (list (symbol$ [..prelude "#Apply"])
(symbol$ [..prelude "Code"])
(symbol$ [..prelude "List"])))]
(form$ (list (symbol$ [..prelude "is#"]) type expression))))
(def' .private (untemplated_text value)
- (-> Text Code)
+ (-> Text
+ Code)
(with_location ..dummy_location
(variant$ (list (symbol$ [..prelude "#Text"]) (text$ value)))))
@@ -1905,11 +1952,13 @@
{#Nominal "#Macro/UnQuote" {#End}}})
(def' .public (unquote it)
- (-> Macro UnQuote)
+ (-> Macro
+ UnQuote)
(.as# UnQuote it))
(def' .public (unquote_macro it)
- (-> UnQuote Macro')
+ (-> UnQuote
+ Macro')
(.as# Macro' it))
(def' .public Spliced_UnQuote
@@ -1918,16 +1967,19 @@
{#Nominal "#Macro/Spliced_UnQuote" {#End}}})
(def' .public (spliced_unquote it)
- (-> Macro Spliced_UnQuote)
+ (-> Macro
+ Spliced_UnQuote)
(.as# Spliced_UnQuote it))
(def' .public (spliced_unquote_macro it)
- (-> Spliced_UnQuote Macro')
+ (-> Spliced_UnQuote
+ Macro')
(.as# Macro' it))
(def' .private (list#one f xs)
- (All (_ a b)
- (-> (-> a ($ Maybe b)) ($ List a) ($ Maybe b)))
+ (All (_ input output)
+ (-> (-> input ($ Maybe output)) ($ List input)
+ ($ Maybe output)))
({{#End}
{#None}
@@ -1941,7 +1993,8 @@
xs))
(def' .private (in_env name state)
- (-> Text Lux ($ Maybe Type))
+ (-> Text Lux
+ ($ Maybe Type))
(let' [[..#info info ..#source source ..#current_module _ ..#modules modules
..#scopes scopes ..#type_context types ..#host host
..#seed seed ..#expected expected ..#location location ..#extensions extensions
@@ -1962,7 +2015,8 @@
scopes)))
(def' .private (available? expected_module current_module exported?)
- (-> Text ($ Maybe Text) Bit Bit)
+ (-> Text ($ Maybe Text) Bit
+ Bit)
(if exported?
#1
({{.#None}
@@ -1973,7 +2027,8 @@
current_module)))
(def' .private (definition_value name state)
- (-> Symbol ($ Meta (Tuple Type Any)))
+ (-> Symbol
+ ($ Meta (Tuple Type Any)))
(let' [[expected_module expected_short] name
[..#info info
..#source source
@@ -2015,7 +2070,8 @@
(property#value expected_module modules))))
(def' .private (global_value global lux)
- (-> Symbol ($ Meta ($ Maybe (Tuple Type Any))))
+ (-> Symbol
+ ($ Meta ($ Maybe (Tuple Type Any))))
(let' [[module short] global]
({{#Right [lux' type,value]}
{#Right [lux' {#Some type,value}]}
@@ -2034,13 +2090,15 @@
module))))
(def' .private (and' left right)
- (-> Bit Bit Bit)
+ (-> Bit Bit
+ Bit)
(if left
right
#0))
(def' .private (symbol#= left right)
- (-> Symbol Symbol Bit)
+ (-> Symbol Symbol
+ Bit)
(let' [[moduleL shortL] left
[moduleR shortR] right]
(all and'
@@ -2048,13 +2106,15 @@
(text#= shortL shortR))))
(def' .private (every? ?)
- (All (_ a)
- (-> (-> a Bit) ($ List a) Bit))
+ (All (_ of)
+ (-> (-> of Bit) ($ List of)
+ Bit))
(list#mix (function' [_2 _1] (if _1 (? _2) #0)) #1))
(def' .private (zipped_2 xs ys)
- (All (_ a b)
- (-> ($ List a) ($ List b) ($ List (Tuple a b))))
+ (All (_ left right)
+ (-> ($ List left) ($ List right)
+ ($ List (Tuple left right))))
({{#Item x xs'}
({{#Item y ys'}
(list#partial [x y] (zipped_2 xs' ys'))
@@ -2068,7 +2128,8 @@
xs))
(def' .private (type#= left right)
- (-> Type Type Bit)
+ (-> Type Type
+ Bit)
({[{#Nominal nameL parametersL} {#Nominal nameR parametersR}]
(all and'
(text#= nameL nameR)
@@ -2129,7 +2190,8 @@
[left right]))
(def' .private (one_expansion it)
- (-> ($ Meta ($ List Code)) ($ Meta Code))
+ (-> ($ Meta ($ List Code))
+ ($ Meta Code))
(do meta#monad
[it it]
({{#Item it {#End}}
@@ -2154,7 +2216,8 @@
state))
(def' .private (normal name)
- (-> Symbol ($ Meta Symbol))
+ (-> Symbol
+ ($ Meta Symbol))
({["" name]
(do meta#monad
[module_name ..current_module_name]
@@ -2221,7 +2284,8 @@
(untemplated_composite "#Tuple"))
(def' .private (untemplated replace? subst token)
- (-> Bit Text Code ($ Meta Code))
+ (-> Bit Text Code
+ ($ Meta Code))
({[_ [@token {#Bit value}]]
(meta#in (with_location ..dummy_location
(variant$ (list (symbol$ [..prelude "#Bit"]) (bit$ value)))))
@@ -2318,7 +2382,7 @@
(failure (wrong_syntax_error [..prelude "`"]))}
tokens)))
-(def' .public syntax_quote Macro `)
+(def' .public complete_quote Macro `)
(def' .public `'
Macro
@@ -2326,13 +2390,15 @@
({{#Item template {#End}}
(do meta#monad
[=template (untemplated #1 "" template)]
- (in (list (form$ (list (symbol$ [..prelude "is#"]) (symbol$ [..prelude "Code"]) =template)))))
+ (in (list (form$ (list (symbol$ [..prelude "is#"])
+ (symbol$ [..prelude "Code"])
+ =template)))))
_
(failure (wrong_syntax_error [..prelude "`'"]))}
tokens)))
-(def' .public partial_quote Macro `')
+(def' .public incomplete_quote Macro `')
(def' .public '
Macro
@@ -2340,13 +2406,15 @@
({{#Item template {#End}}
(do meta#monad
[=template (untemplated #0 "" template)]
- (in (list (form$ (list (symbol$ [..prelude "is#"]) (symbol$ [..prelude "Code"]) =template)))))
+ (in (list (form$ (list (symbol$ [..prelude "is#"])
+ (symbol$ [..prelude "Code"])
+ =template)))))
_
(failure (wrong_syntax_error [..prelude "'"]))}
tokens)))
-(def' .public literal_quote Macro ')
+(def' .public quote Macro ')
(def' .public ,
UnQuote
@@ -2377,7 +2445,7 @@
(failure (wrong_syntax_error [..prelude ",'"]))}
tokens))))
-(def' .public literally UnQuote ,')
+(def' .public verbatim UnQuote ,')
(def' .public ,*
Spliced_UnQuote
@@ -2482,12 +2550,14 @@
tokens)))
(def' .private (function#composite f g)
- (All (_ a b c)
- (-> (-> b c) (-> a b) (-> a c)))
+ (All (_ start middle end)
+ (-> (-> middle end) (-> start middle)
+ (-> start end)))
(function' [x] (f (g x))))
(def' .private (symbol_name x)
- (-> Code ($ Maybe Symbol))
+ (-> Code
+ ($ Maybe Symbol))
({[_ {#Symbol sname}]
{#Some sname}
@@ -2496,7 +2566,8 @@
x))
(def' .private (symbol_short x)
- (-> Code ($ Maybe Text))
+ (-> Code
+ ($ Maybe Text))
({[_ {#Symbol "" sname}]
{#Some sname}
@@ -2505,7 +2576,8 @@
x))
(def' .private (tuple_list tuple)
- (-> Code ($ Maybe ($ List Code)))
+ (-> Code
+ ($ Maybe ($ List Code)))
({[_ {#Tuple members}]
{#Some members}
@@ -2514,7 +2586,8 @@
tuple))
(def' .private (realized_template env template)
- (-> Replacement_Environment Code Code)
+ (-> Replacement_Environment Code
+ Code)
({[_ {#Symbol "" sname}]
({{#Some subst}
subst
@@ -2537,7 +2610,8 @@
template))
(def' .private (high_bits value)
- (-> ($ I64 Any) I64)
+ (-> ($ I64 Any)
+ I64)
(.i64_right# 32 value))
(def' .private low_mask
@@ -2545,11 +2619,13 @@
(|> 1 (.i64_left# 32) (.i64_-# 1)))
(def' .private (low_bits value)
- (-> ($ I64 Any) I64)
+ (-> ($ I64 Any)
+ I64)
(.i64_and# low_mask value))
(def' .private (n#< reference sample)
- (-> Nat Nat Bit)
+ (-> Nat Nat
+ Bit)
(let' [referenceH (high_bits reference)
sampleH (high_bits sample)]
(if (.int_<# referenceH sampleH)
@@ -2560,8 +2636,9 @@
#0))))
(def' .private (list#conjoint xs)
- (All (_ a)
- (-> ($ List ($ List a)) ($ List a)))
+ (All (_ of)
+ (-> ($ List ($ List of))
+ ($ List of)))
(list#mix list#composite {#End} (list#reversed xs)))
(def' .public symbol
@@ -2600,7 +2677,8 @@
tokens)))
(def' .private (n#/ param subject)
- (-> Nat Nat Nat)
+ (-> Nat Nat
+ Nat)
(if (.int_<# +0 (.as# Int param))
(if (n#< param subject)
0
@@ -2617,23 +2695,27 @@
(.i64_+# 1 quotient)))))
(def' .private (n#% param subject)
- (-> Nat Nat Nat)
+ (-> Nat Nat
+ Nat)
(let' [flat (.int_*# (.as# Int param)
(.as# Int (n#/ param subject)))]
(.i64_-# flat subject)))
(def' .private (n#min left right)
- (-> Nat Nat Nat)
+ (-> Nat Nat
+ Nat)
(if (n#< right left)
left
right))
(def' .private (bit#encoded x)
- (-> Bit Text)
+ (-> Bit
+ Text)
(if x "#1" "#0"))
(def' .private (digit::format digit)
- (-> Nat Text)
+ (-> Nat
+ Text)
({[0] "0"
[1] "1" [2] "2" [3] "3"
[4] "4" [5] "5" [6] "6"
@@ -2642,7 +2724,8 @@
digit))
(def' .private (nat#encoded value)
- (-> Nat Text)
+ (-> Nat
+ Text)
({[0] "0"
_ (let' [loop (.is# (-> Nat Text Text)
(function' again [input output]
@@ -2655,13 +2738,15 @@
value))
(def' .private (int#abs value)
- (-> Int Int)
+ (-> Int
+ Int)
(if (.int_<# +0 value)
(.int_*# -1 value)
value))
(def' .private (int#encoded value)
- (-> Int Text)
+ (-> Int
+ Text)
(if (.i64_=# +0 value)
"+0"
(let' [sign (if (.int_<# value +0)
@@ -2678,15 +2763,18 @@
(|> value (.int_%# +10) int#abs (.as# Nat) digit::format)))))
(def' .private (frac#encoded x)
- (-> Frac Text)
+ (-> Frac
+ Text)
(.f64_encoded# x))
(def' .public (not x)
- (-> Bit Bit)
+ (-> Bit
+ Bit)
(if x #0 #1))
(def' .private (macro_type? type)
- (-> Type Bit)
+ (-> Type
+ Bit)
({{#Named ["library/lux" "Macro"] {#Nominal "#Macro" {#End}}}
#1
@@ -2695,8 +2783,7 @@
type))
(def' .private (named_macro' modules current_module module name)
- (-> ($ List (Tuple Text Module))
- Text Text Text
+ (-> ($ List (Tuple Text Module)) Text Text Text
($ Maybe Macro))
(do maybe#monad
[$module (property#value module modules)
@@ -2720,7 +2807,8 @@
(.is# Global gdef))))
(def' .private (named_macro full_name)
- (-> Symbol ($ Meta ($ Maybe Macro)))
+ (-> Symbol
+ ($ Meta ($ Maybe Macro)))
(<| (function' [lux])
(meta#let lux [current_module current_module_name])
(let' [[module name] full_name
@@ -2732,7 +2820,8 @@
(meta#return lux (named_macro' modules current_module module name))))
(def' .private (macro? name)
- (-> Symbol ($ Meta Bit))
+ (-> Symbol
+ ($ Meta Bit))
(<| (function' [lux])
(meta#let lux [name (normal name)])
(meta#let lux [output (named_macro name)])
@@ -2741,8 +2830,9 @@
output))))
(def' .private (list#interposed sep xs)
- (All (_ a)
- (-> a ($ List a) ($ List a)))
+ (All (_ of)
+ (-> of ($ List of)
+ ($ List of)))
({{#End}
xs
@@ -2754,11 +2844,13 @@
xs))
(def' .private (text#encoded original)
- (-> Text Text)
+ (-> Text
+ Text)
(.text_composite# \'' original \''))
(def' .private (code#encoded code)
- (-> Code Text)
+ (-> Code
+ Text)
({[_ {#Bit value}]
(bit#encoded value)
@@ -2812,7 +2904,8 @@
code))
(def' .private (single_expansion token)
- (-> Code ($ Meta ($ List Code)))
+ (-> Code
+ ($ Meta ($ List Code)))
({[_ {#Form {#Item [_ {#Symbol name}] args}}]
(<| (function' [lux])
(meta#let lux [name' (normal name)])
@@ -2829,7 +2922,8 @@
token))
(def' .private (complete_expansion token)
- (-> Code ($ Meta ($ List Code)))
+ (-> Code
+ ($ Meta ($ List Code)))
({[_ {#Form {#Item [_ {#Symbol name}] args}}]
(<| (function' [lux])
(meta#let lux [name' (normal name)])
@@ -2878,8 +2972,9 @@
?macro)))
(def' .private (in_module module meta)
- (All (_ a)
- (-> Text ($ Meta a) ($ Meta a)))
+ (All (_ of)
+ (-> Text ($ Meta of)
+ ($ Meta of)))
(function' [lux]
({[..#info info ..#source source
..#current_module current_module ..#modules modules
@@ -2917,7 +3012,8 @@
lux)))
(def' .private (total_expansion syntax)
- (-> Code ($ Meta ($ List Code)))
+ (-> Code
+ ($ Meta ($ List Code)))
({[_ {#Form {#Item head tail}}]
({[@name {#Symbol name}]
(..total_expansion' total_expansion @name name tail)
@@ -2943,7 +3039,8 @@
syntax))
(def' .private (normal_type type)
- (-> Code ($ Meta Code))
+ (-> Code
+ ($ Meta Code))
({[_ {#Variant {#Item [_ {#Symbol symbol}] parts}}]
(<| (function' [lux])
(meta#let lux [parts (monad#each#meta normal_type parts)])
@@ -3001,7 +3098,8 @@
type))
(def' .private (with_quantification' body lux)
- (-> ($ Meta Code) ($ Meta Code))
+ (-> ($ Meta Code)
+ ($ Meta Code))
(let' [[..#info info/pre
..#source source/pre
..#current_module current_module/pre
@@ -3113,24 +3211,28 @@
tokens)))
(def' .private (empty? xs)
- (All (_ a)
- (-> ($ List a) Bit))
+ (All (_ of)
+ (-> ($ List of)
+ Bit))
({{#End} #1
_ #0}
xs))
-(with_template [<name> <type> <value>]
- [(def' .private (<name> xy)
- (All (_ a b)
- (-> (Tuple a b) <type>))
- (let' [[x y] xy]
- <value>))]
+(with_template [<name> <side>]
+ [(def' .private (<name> left,right)
+ (All (_ left right)
+ (-> (Tuple left right)
+ <side>))
+ (let' [[left right] left,right]
+ <side>))]
- [product#left a x]
- [product#right b y])
+ [product#left left]
+ [product#right right]
+ )
(def' .private (generated_symbol prefix state)
- (-> Text ($ Meta Code))
+ (-> Text
+ ($ Meta Code))
({[..#info info ..#source source ..#current_module _ ..#modules modules
..#scopes scopes ..#type_context types ..#host host
..#seed seed ..#expected expected
@@ -3146,7 +3248,9 @@
(with_template [<name> <tag>]
[(def' .private (<name> type)
- (type_literal (-> Type (List Type)))
+ (type_literal
+ (-> Type
+ (List Type)))
({{<tag> left right}
(list#partial left (<name> right))
@@ -3160,7 +3264,9 @@
)
(def' .private (flat_application type)
- (type_literal (-> Type [Type (List Type)]))
+ (type_literal
+ (-> Type
+ [Type (List Type)]))
({{#Apply head func'}
(let' [[func tail] (flat_application func')]
[func {#Item head tail}])
@@ -3170,7 +3276,8 @@
type))
(def' .private (type#encoded type)
- (-> Type Text)
+ (-> Type
+ Text)
({{#Nominal name params}
(.text_composite#
"(Nominal " (text#encoded name)
@@ -3216,7 +3323,10 @@
type))
(def' .private (meta#try it)
- (type_literal (All (_ a) (-> (Meta a) (Meta (Either Text a)))))
+ (type_literal
+ (All (_ of)
+ (-> (Meta of)
+ (Meta (Either Text of)))))
(function' [state]
({{#Left error}
{#Right [state {#Left error}]}
@@ -3226,7 +3336,8 @@
(it state))))
(def' .private (anonymous_type it)
- (-> Type Type)
+ (-> Type
+ Type)
({{#Named _ it}
(anonymous_type it)
@@ -3235,8 +3346,11 @@
it))
(def' .private static'
- (type_literal (-> Bit Code (Meta Code)))
- (let' [simple_literal (is (-> Symbol (Meta Code))
+ (type_literal
+ (-> Bit Code
+ (Meta Code)))
+ (let' [simple_literal (is (-> Symbol
+ (Meta Code))
(function' [name]
(do meta#monad
[type+value (meta#try (definition_value name))]
@@ -3322,17 +3436,19 @@
{#Nominal "#Macro/Pattern" {#End}}})
(def' .public (pattern it)
- (-> Macro Pattern)
+ (-> Macro
+ Pattern)
(.as# Pattern it))
(def' .public (pattern_macro it)
- (-> Pattern Macro')
+ (-> Pattern
+ Macro')
(.as# Macro' it))
(def' .private (when_expansion#macro when_expansion pattern body branches)
- (type_literal (-> (-> (List Code) (Meta (List Code)))
- Code Code (List Code)
- (Meta (List Code))))
+ (type_literal
+ (-> (-> (List Code) (Meta (List Code))) Code Code (List Code)
+ (Meta (List Code))))
(do meta#monad
[pattern (one_expansion (total_expansion pattern))
pattern (static' #1 pattern)
@@ -3340,7 +3456,9 @@
(in (list#partial pattern body branches))))
(def' .private (when_expansion branches)
- (type_literal (-> (List Code) (Meta (List Code))))
+ (type_literal
+ (-> (List Code)
+ (Meta (List Code))))
({{#Item [@composite {#Form {#Item [@symbol {#Symbol global}] parameters}}]
{#Item body
branches'}}
@@ -3405,7 +3523,9 @@
(failure "Wrong syntax for pattern#or")))))
(def' .private (symbol? code)
- (type_literal (-> Code Bit))
+ (type_literal
+ (-> Code
+ Bit))
(when code
[_ {#Symbol _}]
#1
@@ -3467,12 +3587,15 @@
Type
{#Named [..prelude "Parser"]
(type_literal
- (All (_ a)
+ (All (_ of)
(-> (List Code)
- (Maybe [(List Code) a]))))})
+ (Maybe [(List Code) of]))))})
(def' .private (parsed parser tokens)
- (type_literal (All (_ a) (-> (Parser a) (List Code) (Maybe a))))
+ (type_literal
+ (All (_ of)
+ (-> (Parser of) (List Code)
+ (Maybe of))))
(when (parser tokens)
{#Some [(list) it]}
{#Some it}
@@ -3482,16 +3605,17 @@
(def' .private (inP it tokens)
(type_literal
- (All (_ a)
- (-> a (Parser a))))
+ (All (_ of)
+ (-> of
+ (Parser of))))
{#Some [tokens it]})
(def' .private (orP leftP rightP tokens)
(type_literal
- (All (_ l r)
- (-> (Parser l)
- (Parser r)
- (Parser (Or l r)))))
+ (All (_ left right)
+ (-> (Parser left)
+ (Parser right)
+ (Parser (Or left right)))))
(when (leftP tokens)
{#Some [tokens left]}
{#Some [tokens {#Left left}]}
@@ -3506,10 +3630,10 @@
(def' .private (eitherP leftP rightP tokens)
(type_literal
- (All (_ a)
- (-> (Parser a)
- (Parser a)
- (Parser a))))
+ (All (_ of)
+ (-> (Parser of)
+ (Parser of)
+ (Parser of))))
(when (leftP tokens)
{#None}
(rightP tokens)
@@ -3519,10 +3643,10 @@
(def' .private (andP leftP rightP tokens)
(type_literal
- (All (_ l r)
- (-> (Parser l)
- (Parser r)
- (Parser [l r]))))
+ (All (_ left right)
+ (-> (Parser left)
+ (Parser right)
+ (Parser (And left right)))))
(do maybe#monad
[left (leftP tokens)
.let [[tokens left] left]
@@ -3532,10 +3656,10 @@
(def' .private (afterP leftP rightP tokens)
(type_literal
- (All (_ l r)
- (-> (Parser l)
- (Parser r)
- (Parser r))))
+ (All (_ _ of)
+ (-> (Parser _)
+ (Parser of)
+ (Parser of))))
(do maybe#monad
[left (leftP tokens)
.let [[tokens left] left]]
@@ -3543,9 +3667,9 @@
(def' .private (someP itP tokens)
(type_literal
- (All (_ a)
- (-> (Parser a)
- (Parser (List a)))))
+ (All (_ of)
+ (-> (Parser of)
+ (Parser (List of)))))
(when (itP tokens)
{#Some [tokens head]}
(do maybe#monad
@@ -3558,9 +3682,9 @@
(def' .private (manyP itP tokens)
(type_literal
- (All (_ a)
- (-> (Parser a)
- (Parser (List a)))))
+ (All (_ of)
+ (-> (Parser of)
+ (Parser (List of)))))
(do maybe#monad
[it (itP tokens)
.let [[tokens head] it]
@@ -3570,9 +3694,9 @@
(def' .private (maybeP itP tokens)
(type_literal
- (All (_ a)
- (-> (Parser a)
- (Parser (Maybe a)))))
+ (All (_ of)
+ (-> (Parser of)
+ (Parser (Maybe of)))))
(when (itP tokens)
{#Some [tokens it]}
{#Some [tokens {#Some it}]}
@@ -3582,8 +3706,9 @@
(def' .private (tupleP itP tokens)
(type_literal
- (All (_ a)
- (-> (Parser a) (Parser a))))
+ (All (_ of)
+ (-> (Parser of)
+ (Parser of))))
(when tokens
(list#partial [_ {#Tuple input}] tokens')
(do maybe#monad
@@ -3595,8 +3720,9 @@
(def' .private (formP itP tokens)
(type_literal
- (All (_ a)
- (-> (Parser a) (Parser a))))
+ (All (_ of)
+ (-> (Parser of)
+ (Parser of))))
(when tokens
(list#partial [_ {#Form input}] tokens')
(do maybe#monad
@@ -3607,7 +3733,8 @@
{#None}))
(def' .private (bindingP tokens)
- (type_literal (Parser [Text Code]))
+ (type_literal
+ (Parser [Text Code]))
(when tokens
(list#partial [_ {#Symbol ["" name]}] value &rest)
{#Some [&rest [name value]]}
@@ -3616,7 +3743,8 @@
{#None}))
(def' .private (endP tokens)
- (type_literal (Parser Any))
+ (type_literal
+ (Parser Any))
(when tokens
(list)
{#Some [tokens []]}
@@ -3625,7 +3753,8 @@
{#None}))
(def' .private (anyP tokens)
- (type_literal (Parser Code))
+ (type_literal
+ (Parser Code))
(when tokens
(list#partial code tokens')
{#Some [tokens' code]}
@@ -3634,7 +3763,9 @@
{#None}))
(def' .private (localP tokens)
- (type_literal (-> (List Code) (Maybe [(List Code) Text])))
+ (type_literal
+ (-> (List Code)
+ (Maybe [(List Code) Text])))
(when tokens
(list#partial [_ {#Symbol ["" local]}] tokens')
{#Some [tokens' local]}
@@ -3643,7 +3774,9 @@
{#None}))
(def' .private (symbolP tokens)
- (type_literal (-> (List Code) (Maybe [(List Code) Symbol])))
+ (type_literal
+ (-> (List Code)
+ (Maybe [(List Code) Symbol])))
(when tokens
(list#partial [_ {#Symbol it}] tokens')
{#Some [tokens' it]}
@@ -3653,7 +3786,9 @@
(with_template [<parser> <item_type> <item_parser>]
[(def' .private (<parser> tokens)
- (type_literal (-> (List Code) (Maybe (List <item_type>))))
+ (type_literal
+ (-> (List Code)
+ (Maybe (List <item_type>))))
(when tokens
{#End}
{#Some {#End}}
@@ -3671,7 +3806,8 @@
(with_template [<parser> <parameter_type> <parameters_parser>]
[(def' .private (<parser> tokens)
- (type_literal (Parser [Text (List <parameter_type>)]))
+ (type_literal
+ (Parser [Text (List <parameter_type>)]))
(when tokens
(list#partial [_ {#Form local_declaration}] tokens')
(do maybe#monad
@@ -3691,7 +3827,9 @@
)
(def' .private (export_policyP tokens)
- (type_literal (-> (List Code) [(List Code) Code]))
+ (type_literal
+ (-> (List Code)
+ [(List Code) Code]))
(when tokens
(list#partial candidate tokens')
(when candidate
@@ -3712,7 +3850,10 @@
(with_template [<parser> <parameter_type> <local>]
[(def' .private (<parser> tokens)
- (type_literal (-> (List Code) (Maybe [(List Code) [Code Text (List <parameter_type>)]])))
+ (type_literal
+ (-> (List Code)
+ (Maybe [(List Code)
+ [Code Text (List <parameter_type>)]])))
(do maybe#monad
[.let' [[tokens export_policy] (export_policyP tokens)]
% (<local> tokens)
@@ -3724,7 +3865,10 @@
)
(def' .private (bodyP tokens)
- (type_literal (-> (List Code) (Maybe [(List Code) [(Maybe Code) Code]])))
+ (type_literal
+ (-> (List Code)
+ (Maybe [(List Code)
+ [(Maybe Code) Code]])))
(when tokens
... TB
(list#partial type body tokens')
@@ -3738,7 +3882,13 @@
{#None}))
(def' .private (definitionP tokens)
- (type_literal (-> (List Code) (Maybe [Code Text (List Code) (Maybe Code) Code])))
+ (type_literal
+ (-> (List Code)
+ (Maybe [Code
+ Text
+ (List Code)
+ (Maybe Code)
+ Code])))
(do maybe#monad
[% (enhanced_declarationP tokens)
.let' [[tokens [export_policy name parameters]] %]
@@ -3791,11 +3941,13 @@
)
(def (index part text)
- (-> Text Text (Maybe Nat))
+ (-> Text Text
+ (Maybe Nat))
(.text_index# 0 part text))
(def .public (panic! message)
- (-> Text Nothing)
+ (-> Text
+ Nothing)
(.error# message))
(def maybe#else
@@ -3815,7 +3967,8 @@
{#Left (..wrong_syntax_error (symbol ..maybe#else))})))
(def (text#all_split_by splitter input)
- (-> Text Text (List Text))
+ (-> Text Text
+ (List Text))
(when (..index splitter input)
{#None}
(list input)
@@ -3829,8 +3982,9 @@
(.text_clip# after_offset after_length input))))))
(def (item idx xs)
- (All (_ a)
- (-> Nat (List a) (Maybe a)))
+ (All (_ of)
+ (-> Nat (List of)
+ (Maybe of)))
(when xs
{#End}
{#None}
@@ -3842,7 +3996,8 @@
... https://en.wikipedia.org/wiki/Lambda_calculus#%CE%B2-reduction
(def (reduced env type)
- (-> (List Type) Type Type)
+ (-> (List Type) Type
+ Type)
(when type
{#Sum left right}
{#Sum (reduced env left) (reduced env right)}
@@ -3888,7 +4043,8 @@
))
(def (applied_type param type_fn)
- (-> Type Type (Maybe Type))
+ (-> Type Type
+ (Maybe Type))
(when type_fn
{#UnivQ env body}
{#Some (reduced (list#partial type_fn param env) body)}
@@ -3934,7 +4090,8 @@
{#Some (list type)}))
(def (module name)
- (-> Text (Meta Module))
+ (-> Text
+ (Meta Module))
(function (_ state)
(let [[..#info info ..#source source ..#current_module _ ..#modules modules
..#scopes scopes ..#type_context types ..#host host
@@ -3948,7 +4105,8 @@
{#Left (.text_composite# "Unknown module: " name)}))))
(def (type_slot [module name])
- (-> Symbol (Meta [Bit Label]))
+ (-> Symbol
+ (Meta [Bit Label]))
(do meta#monad
[=module (..module module)
.let [[..#module_hash _
@@ -3964,7 +4122,8 @@
(failure (.text_composite# "Unknown slot: " (symbol#encoded [module name]))))))
(def (slot_family expected_module expected_record)
- (-> Text Type (Meta (Maybe (List Symbol))))
+ (-> Text Type
+ (Meta (Maybe (List Symbol))))
(do meta#monad
[module (..module expected_module)
actual_module ..current_module_name
@@ -4002,7 +4161,8 @@
definitions))))
(def (record_slots type)
- (-> Type (Meta (Maybe [(List Symbol) (List Type)])))
+ (-> Type
+ (Meta (Maybe [(List Symbol) (List Type)])))
(when type
{#Apply arg func}
(record_slots func)
@@ -4090,7 +4250,8 @@
(in (list (tuple$ (list#conjoint members)))))))
(def (text#interposed separator parts)
- (-> Text (List Text) Text)
+ (-> Text (List Text)
+ Text)
(when parts
{#End}
""
@@ -4101,15 +4262,10 @@
head
tail)))
-(def (function#identity value)
- (All (_ a)
- (-> a a))
- value)
-
(def (everyP itP tokens)
- (All (_ a)
- (-> (-> (List Code) (Maybe [(List Code) a]))
- (-> (List Code) (Maybe (List a)))))
+ (All (_ of)
+ (-> (-> (List Code) (Maybe [(List Code) of]))
+ (-> (List Code) (Maybe (List of)))))
(when tokens
{#Item _}
(do maybe#monad
@@ -4127,7 +4283,8 @@
{#Some (list)}))
(def (whenP tokens)
- (-> (List Code) (Maybe [(List Code) [Text Code]]))
+ (-> (List Code)
+ (Maybe [(List Code) [Text Code]]))
(when tokens
(list#partial [_ {#Variant (list [_ {#Symbol ["" niladic]}])}] tokens')
{#Some [tokens' [niladic (` .Any)]]}
@@ -4151,7 +4308,8 @@
(failure (..wrong_syntax_error (symbol ..Variant))))))
(def (slotP tokens)
- (-> (List Code) (Maybe [(List Code) [Text Code]]))
+ (-> (List Code)
+ (Maybe [(List Code) [Text Code]]))
(when tokens
(list#partial [_ {#Symbol ["" slot]}] type tokens')
{#Some [tokens' [slot type]]}
@@ -4177,7 +4335,8 @@
(failure (..wrong_syntax_error (symbol ..Record))))))
(def (typeP tokens)
- (-> (List Code) (Maybe [Code Text (List Text) Code]))
+ (-> (List Code)
+ (Maybe [Code Text (List Text) Code]))
(do maybe#monad
[% (declarationP tokens)
.let' [[tokens [export_policy name parameters]] %]
@@ -4187,7 +4346,8 @@
(in [export_policy name parameters definition])))
(def (textP tokens)
- (-> (List Code) (Maybe [(List Code) Text]))
+ (-> (List Code)
+ (Maybe [(List Code) Text]))
(when tokens
(list#partial [_ {#Text it}] tokens')
{#Some [tokens' it]}
@@ -4196,7 +4356,8 @@
{#None}))
(def (type_declaration it)
- (-> Code (Meta (Tuple Code (Maybe (Either (List Text) (List Text))))))
+ (-> Code
+ (Meta [Code (Maybe (Either (List Text) (List Text)))]))
({[_ {#Form {#Item [_ {#Symbol declarer}] parameters}}]
(do meta#monad
[declaration (single_expansion (form$ (list#partial (symbol$ declarer) parameters)))]
@@ -4228,8 +4389,9 @@
it))
(def (enumeration' idx xs)
- (All (_ a)
- (-> Nat (List a) (List [Nat a])))
+ (All (_ of)
+ (-> Nat (List of)
+ (List [Nat of])))
(when xs
{#Item x xs'}
{#Item [idx x] (enumeration' (.i64_+# 1 idx) xs')}
@@ -4238,12 +4400,14 @@
{#End}))
(def (enumeration xs)
- (All (_ a)
- (-> (List a) (List [Nat a])))
+ (All (_ of)
+ (-> (List of)
+ (List [Nat of])))
(enumeration' 0 xs))
(def (label_definitions module export_policy associated_type label_type family labels)
- (-> Text Code Code Code Code (List Text) (List Code))
+ (-> Text Code Code Code Code (List Text)
+ (List Code))
(when (list#reversed labels)
(list single)
(list (` (def (, export_policy) (, (local$ single))
@@ -4332,7 +4496,8 @@
(formP (andP symbolP (someP anyP))))
(def (referrals_parser aliased?)
- (-> Bit (Parser (List Referral)))
+ (-> Bit
+ (Parser (List Referral)))
(all eitherP
(manyP referral_parser)
(afterP endP
@@ -4342,12 +4507,14 @@
(inP (list))))
(def (text#split_at' at x)
- (-> Nat Text [Text Text])
+ (-> Nat Text
+ [Text Text])
[(.text_clip# 0 at x)
(.text_clip# at (|> x .text_size# (.i64_-# at)) x)])
(def (text#split_by token sample)
- (-> Text Text (Maybe [Text Text]))
+ (-> Text Text
+ (Maybe [Text Text]))
(do ..maybe#monad
[index (..index token sample)
.let [[pre post'] (text#split_at' index sample)
@@ -4355,7 +4522,8 @@
(in [pre post])))
(def (replaced pattern replacement template)
- (-> Text Text Text Text)
+ (-> Text Text Text
+ Text)
((is (-> Text Text Text)
(function (again left right)
(when (..text#split_by pattern right)
@@ -4367,11 +4535,13 @@
"" template))
(def (alias_stand_in index)
- (-> Nat Text)
+ (-> Nat
+ Text)
(.text_composite# "[" (nat#encoded index) "]"))
(def (module_alias context aliased)
- (-> (List Text) Text Text)
+ (-> (List Text) Text
+ Text)
(product#right
(list#mix (function (_ replacement [index aliased])
[(.i64_+# 1 index)
@@ -4386,7 +4556,8 @@
"\")
(def (normal_parallel_path' hierarchy root)
- (-> Text Text Text)
+ (-> Text Text
+ Text)
(when [(text#split_by ..module_separator hierarchy)
(text#split_by ..parallel_hierarchy_sigil root)]
[{#Some [_ hierarchy']}
@@ -4399,7 +4570,8 @@
_ (.text_composite# root ..module_separator hierarchy))))
(def (normal_parallel_path hierarchy root)
- (-> Text Text (Maybe Text))
+ (-> Text Text
+ (Maybe Text))
(when (text#split_by ..parallel_hierarchy_sigil root)
{#Some ["" root']}
{#Some (normal_parallel_path' hierarchy root')}
@@ -4408,7 +4580,8 @@
{#None}))
(def (relative_ups relatives input)
- (-> Nat Text Nat)
+ (-> Nat Text
+ Nat)
(when (.text_index# relatives ..module_separator input)
{#None}
relatives
@@ -4419,7 +4592,9 @@
relatives)))
(def (list#after amount list)
- (All (_ a) (-> Nat (List a) (List a)))
+ (All (_ of)
+ (-> Nat (List of)
+ (List of)))
(when [amount list]
(pattern#or [0 _]
[_ {#End}])
@@ -4433,7 +4608,8 @@
(.int_char# +10))
(def (absolute_module_name nested? relative_root module)
- (-> Bit Text Text (Meta Text))
+ (-> Bit Text Text
+ (Meta Text))
(when (relative_ups 0 module)
0
(meta#in (if nested?
@@ -4459,7 +4635,8 @@
" Relative Root: " relative_root \n))))))
(def (imports_parser nested? relative_root context imports)
- (-> Bit Text (List Text) (List Code) (Meta (List Importation)))
+ (-> Bit Text (List Text) (List Code)
+ (Meta (List Importation)))
(do meta#monad
[imports' (monad#each#meta (is (-> Code (Meta (List Importation)))
(function (_ token)
@@ -4528,7 +4705,8 @@
(in (list#conjoint imports'))))
(def (exported_definitions module state)
- (-> Text (Meta (List Text)))
+ (-> Text
+ (Meta (List Text)))
(let [[current_module modules] (when state
[..#info info ..#source source ..#current_module current_module ..#modules modules
..#scopes scopes ..#type_context types ..#host host
@@ -4573,8 +4751,9 @@
))
(def (list#only p xs)
- (All (_ a)
- (-> (-> a Bit) (List a) (List a)))
+ (All (_ of)
+ (-> (-> of Bit) (List of)
+ (List of)))
(when xs
{#End}
(list)
@@ -4585,7 +4764,8 @@
(list#only p xs'))))
(def (is_member? whens name)
- (-> (List Text) Text Bit)
+ (-> (List Text) Text
+ Bit)
(let [output (list#mix (function (_ when prev)
(or prev
(text#= when name)))
@@ -4594,7 +4774,8 @@
output))
(def (test_referrals current_module imported_module all_defs referred_defs)
- (-> Text Text (List Text) (List Text) (Meta (List Any)))
+ (-> Text Text (List Text) (List Text)
+ (Meta (List Any)))
(monad#each#meta (is (-> Text (Meta Any))
(function (_ _def)
(if (is_member? all_defs _def)
@@ -4603,7 +4784,8 @@
referred_defs))
(def (alias_definition imported_module def)
- (-> Text Text Code)
+ (-> Text Text
+ Code)
(` (.def# (, (local$ def))
(, (symbol$ [imported_module def]))
.private)))
@@ -4659,7 +4841,8 @@
(failure (..wrong_syntax_error (symbol ..except))))))
(def (definition_type name state)
- (-> Symbol Lux (Maybe Type))
+ (-> Symbol Lux
+ (Maybe Type))
(let [[expected_module expected_short] name
[..#info info ..#source source ..#current_module _ ..#modules modules
..#scopes scopes ..#type_context types ..#host host
@@ -4690,7 +4873,8 @@
{#None})))))
(def (type_variable idx bindings)
- (-> Nat (List [Nat (Maybe Type)]) (Maybe Type))
+ (-> Nat (List [Nat (Maybe Type)])
+ (Maybe Type))
(when bindings
{#End}
{#End}
@@ -4701,7 +4885,8 @@
(type_variable idx bindings'))))
(def (clean_type variables it)
- (-> (List [Nat (Maybe Type)]) Type Type)
+ (-> (List [Nat (Maybe Type)]) Type
+ Type)
(when it
{#Nominal name parameters}
{#Nominal name (list#each (clean_type variables) parameters)}
@@ -4751,7 +4936,8 @@
(clean_type variables it))))
(def (type_definition full_name)
- (-> Symbol (Meta Type))
+ (-> Symbol
+ (Meta Type))
(do meta#monad
[.let [[module name] full_name]
current_module current_module_name]
@@ -4788,7 +4974,9 @@
temp)))))
(def (list#all choice items)
- (All (_ a b) (-> (-> a (Maybe b)) (List a) (List b)))
+ (All (_ input output)
+ (-> (-> input (Maybe output)) (List input)
+ (List output)))
(when items
{#Item head tail}
(when (choice head)
@@ -4805,7 +4993,8 @@
[(List Symbol) (List Type)])
(def (open_layer alias [tags members])
- (-> Text Implementation_Interface (Meta [Code (List [Symbol Implementation_Interface])]))
+ (-> Text Implementation_Interface
+ (Meta [Code (List [Symbol Implementation_Interface])]))
(do meta#monad
[pattern (monad#each#meta (function (_ [slot slot_type])
(do meta#monad
@@ -4827,7 +5016,8 @@
pattern)])))
(def (open_layers alias interfaces body)
- (-> Text (List Implementation_Interface) Code (Meta [Code Code]))
+ (-> Text (List Implementation_Interface) Code
+ (Meta [Code Code]))
(do meta#monad
[layer (monad#each#meta (open_layer alias) interfaces)
.let [pattern (tuple$ (list#each product#left layer))
@@ -4898,13 +5088,14 @@
_
(failure (..wrong_syntax_error (symbol ..cond))))))
-(type (Try value)
+(type (Try of)
(Variant
{#Failure Text}
- {#Success value}))
+ {#Success of}))
(def (access_pattern g!_ g!output lefts right? members)
- (-> Code Code Nat Bit (List Type) (Try (List Code)))
+ (-> Code Code Nat Bit (List Type)
+ (Try (List Code)))
(when ((is (-> Nat (List Type) (List Code)
(List Code))
(function (again index input output)
@@ -4971,7 +5162,8 @@
(failure (..wrong_syntax_error (symbol ..the))))))
(def (open_declaration imported_module alias tags my_tag_index [module short] source type)
- (-> Text Text (List Symbol) Nat Symbol Code Type (Meta (List Code)))
+ (-> Text Text (List Symbol) Nat Symbol Code Type
+ (Meta (List Code)))
(do meta#monad
[output (record_slots type)
g!_ (..generated_symbol "g!_")
@@ -4999,7 +5191,8 @@
#0)))))))
(def (implementation_declarations imported_module alias implementation)
- (-> Text Text Symbol (Meta (List Code)))
+ (-> Text Text Symbol
+ (Meta (List Code)))
(do meta#monad
[interface (type_definition implementation)
output (record_slots interface)]
@@ -5018,7 +5211,8 @@
" : " (type#encoded interface))))))
(def (localized module global)
- (-> Text Symbol Symbol)
+ (-> Text Symbol
+ Symbol)
(when global
["" local]
[module local]
@@ -5085,14 +5279,16 @@
(failure (..wrong_syntax_error (symbol ..use))))))
(def (imported_by? import_name module_name)
- (-> Text Text (Meta Bit))
+ (-> Text Text
+ (Meta Bit))
(do meta#monad
[module (module module_name)
.let [[..#module_hash _ ..#module_aliases _ ..#definitions _ ..#imports imports ..#module_state _] module]]
(in (is_member? imports import_name))))
(def (referrals module_name extra)
- (-> Text (List Code) (Meta (List Referral)))
+ (-> Text (List Code)
+ (Meta (List Referral)))
(do meta#monad
[extra,referral (when (referrals_parser #0 extra)
{#Some extra,referral}
@@ -5341,8 +5537,9 @@
(with_template [<name> <extension>]
[(def .public <name>
- (All (_ s)
- (-> (I64 s) (I64 s)))
+ (All (_ of)
+ (-> (I64 of)
+ (I64 of)))
(|>> (<extension> 1)))]
[++ .i64_+#]
@@ -5350,8 +5547,9 @@
)
(def (interleaved xs ys)
- (All (_ a)
- (-> (List a) (List a) (List a)))
+ (All (_ of)
+ (-> (List of) (List of)
+ (List of)))
(when xs
{#End}
{#End}
@@ -5365,7 +5563,8 @@
(list#partial x y (interleaved xs' ys')))))
(def (type_code type)
- (-> Type Code)
+ (-> Type
+ Code)
(when type
{#Nominal name params}
(` {.#Nominal (, (text$ name)) (, (untemplated_list (list#each type_code params)))})
@@ -5437,7 +5636,8 @@
(failure (..wrong_syntax_error (symbol ..loop)))))))
(def .public with_expansions
- (let [with_expansions' (is (-> Text (List Code) Code (List Code))
+ (let [with_expansions' (is (-> Text (List Code) Code
+ (List Code))
(function (with_expansions' label tokens target)
(when target
(pattern#or [_ {#Bit _}]
@@ -5546,7 +5746,8 @@
(failure (..wrong_syntax_error (symbol ..type_of))))))
(def .public template
- (let [templateP (is (-> (List Code) (Maybe [Text (List Text) (List Code)]))
+ (let [templateP (is (-> (List Code)
+ (Maybe [Text (List Text) (List Code)]))
(function (_ tokens)
(do maybe#monad
[% (local_declarationP tokens)
@@ -5555,10 +5756,12 @@
.let' [[tokens templates] %]
_ (endP tokens)]
(in [name parameters templates]))))
- simple_replacement_environment (is (-> (List Text) Replacement_Environment)
+ simple_replacement_environment (is (-> (List Text)
+ Replacement_Environment)
(list#each (function (_ arg)
[arg (` ((,' ,) (, (local$ arg))))])))
- instantiated_template (is (-> Replacement_Environment Code Code)
+ instantiated_template (is (-> Replacement_Environment Code
+ Code)
(function (_ replacement_environment template)
(` (`' (, (with_replacements replacement_environment
template))))))]
@@ -5586,7 +5789,9 @@
(with_template [<name> <to>]
[(def .public <name>
(template (<name> it)
- [(..|> it (..is (..I64 ..Any)) (..as <to>))]))]
+ [(..|> it
+ (..is (..I64 ..Any))
+ (..as <to>))]))]
[i64 ..I64]
[nat ..Nat]
@@ -5615,7 +5820,8 @@
(let [target (is (Meta Text)
(function (_ compiler)
{#Right [compiler (the [#info #target] compiler)]}))
- platform_name (is (-> Code (Meta Text))
+ platform_name (is (-> Code
+ (Meta Text))
(function (_ choice)
(when choice
[_ {#Text platform}]
@@ -5637,7 +5843,8 @@
_
(failure (.text_composite# "Invalid target platform syntax: " (..code#encoded choice)
\n "Must be either a text literal or a symbol.")))))
- target_pick (is (-> Text (List [Code Code]) (Maybe Code) (Meta (List Code)))
+ target_pick (is (-> Text (List [Code Code]) (Maybe Code)
+ (Meta (List Code)))
(function (target_pick target options default)
(when options
{#End}
@@ -5694,7 +5901,8 @@
(these (def .public parameter "")))
(def .public require
- (let [refer_code (is (-> Text Text (List Referral) Code)
+ (let [refer_code (is (-> Text Text (List Referral)
+ Code)
(function (_ imported_module alias referrals)
(` (..refer (, (text$ imported_module))
(, (text$ alias))
@@ -5706,11 +5914,13 @@
[current_module ..current_module_name
imports (imports_parser #0 current_module {#End} _imports)
.let [=imports (|> imports
- (list#each (is (-> Importation Code)
+ (list#each (is (-> Importation
+ Code)
(function (_ [module_name m_alias =refer])
(` [(, (text$ module_name)) (, (text$ (..maybe#else "" m_alias)))]))))
tuple$)
- =refers (list#each (is (-> Importation Code)
+ =refers (list#each (is (-> Importation
+ Code)
(function (_ [module_name m_alias =refer])
(refer_code module_name (..maybe#else "" m_alias) =refer)))
imports)
@@ -5820,7 +6030,8 @@
(..failure (..wrong_syntax_error (symbol ..try))))))
(def (methodP tokens)
- (-> (List Code) (Maybe [(List Code) [Text Code]]))
+ (-> (List Code)
+ (Maybe [(List Code) [Text Code]]))
(when tokens
(list#partial [_ {#Form (list [_ {#Symbol [..prelude "is#"]}]
type
@@ -5844,7 +6055,8 @@
(failure (..wrong_syntax_error (symbol ..Interface)))))))
(def .public Rec
- (let [recursive_type (is (-> Code Code Text Code Code)
+ (let [recursive_type (is (-> Code Code Text Code
+ Code)
(function (recursive_type g!self g!dummy name body)
(` {.#Apply (..Nominal "")
(.All ((, g!self) (, g!dummy))