aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/library/lux.lux
diff options
context:
space:
mode:
authorEduardo Julian2022-08-11 04:15:07 -0400
committerEduardo Julian2022-08-11 04:15:07 -0400
commit065e8a4d8122d4616b570496915d2c0e2c78cd6b (patch)
treef2bbdc3e40b796b34026ab04c9a478d8a3f082d5 /stdlib/source/library/lux.lux
parent68d78235694c633c956bb9e8a007cad7d65370bc (diff)
Re-named the "case" macro to "when".
Diffstat (limited to 'stdlib/source/library/lux.lux')
-rw-r--r--stdlib/source/library/lux.lux376
1 files changed, 188 insertions, 188 deletions
diff --git a/stdlib/source/library/lux.lux b/stdlib/source/library/lux.lux
index 16fb17d92..84f0ddf14 100644
--- a/stdlib/source/library/lux.lux
+++ b/stdlib/source/library/lux.lux
@@ -2997,17 +2997,17 @@
(-> Pattern Macro')
("lux type as" Macro' it))
-(def' .private (case_expansion#macro case_expansion pattern body branches)
+(def' .private (when_expansion#macro when_expansion pattern body branches)
(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)
- branches (case_expansion branches)]
+ branches (when_expansion branches)]
(in (list#partial pattern body branches))))
-(def' .private (case_expansion branches)
+(def' .private (when_expansion branches)
(type_literal (-> (List Code) (Meta (List Code))))
({{#Item [@composite {#Form {#Item [@symbol {#Symbol global}] parameters}}]
{#Item body
@@ -3020,46 +3020,46 @@
(do meta#monad
[branches'' ((pattern_macro ("lux type as" Pattern value))
(list#partial (form$ parameters) body branches'))]
- (case_expansion branches''))
- (case_expansion#macro case_expansion [@composite {#Form {#Item [@symbol {#Symbol global}] parameters}}] body branches'))
+ (when_expansion branches''))
+ (when_expansion#macro when_expansion [@composite {#Form {#Item [@symbol {#Symbol global}] parameters}}] body branches'))
{#None}
- (case_expansion#macro case_expansion [@composite {#Form {#Item [@symbol {#Symbol global}] parameters}}] body branches')}
+ (when_expansion#macro when_expansion [@composite {#Form {#Item [@symbol {#Symbol global}] parameters}}] body branches')}
?type,value))
{#Item pattern {#Item body branches'}}
- (case_expansion#macro case_expansion pattern body branches')
+ (when_expansion#macro when_expansion pattern body branches')
{#End}
(meta#in (list))
_
- (failure (all text#composite "'case' expects an even number of tokens: " (|> branches
+ (failure (all text#composite "'when' expects an even number of tokens: " (|> branches
(list#each code#encoded)
(list#interposed " ")
list#reversed
(list#mix text#composite ""))))}
branches))
-(def' .public case
+(def' .public when
Macro
(macro (_ tokens)
({{#Item value branches}
(do meta#monad
- [expansion (case_expansion branches)]
+ [expansion (when_expansion branches)]
(in (list (` ((, (variant$ expansion)) (, value))))))
_
- (failure (..wrong_syntax_error (symbol ..case)))}
+ (failure (..wrong_syntax_error (symbol ..when)))}
tokens)))
(def' .private pattern#or
Pattern
(pattern
(macro (_ tokens)
- (case tokens
+ (when tokens
(list#partial [_ {#Form patterns}] body branches)
- (case patterns
+ (when patterns
{#End}
(failure "pattern#or cannot have 0 patterns")
@@ -3073,7 +3073,7 @@
(def' .private (symbol? code)
(type_literal (-> Code Bit))
- (case code
+ (when code
[_ {#Symbol _}]
#1
@@ -3083,9 +3083,9 @@
(def' .public let
Macro
(macro (_ tokens)
- (case tokens
+ (when tokens
(list [_ {#Tuple bindings}] body)
- (case (..pairs bindings)
+ (when (..pairs bindings)
{#Some bindings}
(|> bindings
list#reversed
@@ -3094,7 +3094,7 @@
(let' [[l r] lr]
(if (symbol? l)
(` ({(, l) (, body')} (, r)))
- (` (case (, r) (, l) (, body')))))))
+ (` (when (, r) (, l) (, body')))))))
body)
list
meta#in)
@@ -3108,8 +3108,8 @@
(def' .public function
Macro
(macro (_ tokens)
- (case (is (Maybe [Text Code (List Code) Code])
- (case tokens
+ (when (is (Maybe [Text Code (List Code) Code])
+ (when tokens
(list [_ {#Form (list#partial [_ {#Symbol ["" name]}] head tail)}] body)
{#Some name head tail body}
@@ -3123,7 +3123,7 @@
(if (symbol? arg)
(` ([(, g!name) (, arg)] (, body')))
(` ([(, g!name) (, g!blank)]
- (.case (, g!blank) (, arg) (, body'))))))))]
+ (.when (, g!blank) (, arg) (, body'))))))))]
(meta#in (list (nest (..local$ g!name) head
(list#mix (nest g!blank) body (list#reversed tail))))))
@@ -3138,7 +3138,7 @@
(def' .private (parsed parser tokens)
(type_literal (All (_ a) (-> (Parser a) (List Code) (Maybe a))))
- (case (parser tokens)
+ (when (parser tokens)
{#Some [(list) it]}
{#Some it}
@@ -3157,12 +3157,12 @@
(-> (Parser l)
(Parser r)
(Parser (Or l r)))))
- (case (leftP tokens)
+ (when (leftP tokens)
{#Some [tokens left]}
{#Some [tokens {#Left left}]}
_
- (case (rightP tokens)
+ (when (rightP tokens)
{#Some [tokens right]}
{#Some [tokens {#Right right}]}
@@ -3175,7 +3175,7 @@
(-> (Parser a)
(Parser a)
(Parser a))))
- (case (leftP tokens)
+ (when (leftP tokens)
{#None}
(rightP tokens)
@@ -3211,7 +3211,7 @@
(All (_ a)
(-> (Parser a)
(Parser (List a)))))
- (case (itP tokens)
+ (when (itP tokens)
{#Some [tokens head]}
(do maybe#monad
[it (someP itP tokens)
@@ -3238,7 +3238,7 @@
(All (_ a)
(-> (Parser a)
(Parser (Maybe a)))))
- (case (itP tokens)
+ (when (itP tokens)
{#Some [tokens it]}
{#Some [tokens {#Some it}]}
@@ -3249,7 +3249,7 @@
(type_literal
(All (_ a)
(-> (Parser a) (Parser a))))
- (case tokens
+ (when tokens
(list#partial [_ {#Tuple input}] tokens')
(do maybe#monad
[it (parsed itP input)]
@@ -3262,7 +3262,7 @@
(type_literal
(All (_ a)
(-> (Parser a) (Parser a))))
- (case tokens
+ (when tokens
(list#partial [_ {#Form input}] tokens')
(do maybe#monad
[it (parsed itP input)]
@@ -3273,7 +3273,7 @@
(def' .private (bindingP tokens)
(type_literal (Parser [Text Code]))
- (case tokens
+ (when tokens
(list#partial [_ {#Symbol ["" name]}] value &rest)
{#Some [&rest [name value]]}
@@ -3282,7 +3282,7 @@
(def' .private (endP tokens)
(type_literal (Parser Any))
- (case tokens
+ (when tokens
(list)
{#Some [tokens []]}
@@ -3291,7 +3291,7 @@
(def' .private (anyP tokens)
(type_literal (Parser Code))
- (case tokens
+ (when tokens
(list#partial code tokens')
{#Some [tokens' code]}
@@ -3300,7 +3300,7 @@
(def' .private (localP tokens)
(type_literal (-> (List Code) (Maybe [(List Code) Text])))
- (case tokens
+ (when tokens
(list#partial [_ {#Symbol ["" local]}] tokens')
{#Some [tokens' local]}
@@ -3309,7 +3309,7 @@
(def' .private (symbolP tokens)
(type_literal (-> (List Code) (Maybe [(List Code) Symbol])))
- (case tokens
+ (when tokens
(list#partial [_ {#Symbol it}] tokens')
{#Some [tokens' it]}
@@ -3319,7 +3319,7 @@
(with_template [<parser> <item_type> <item_parser>]
[(def' .private (<parser> tokens)
(type_literal (-> (List Code) (Maybe (List <item_type>))))
- (case tokens
+ (when tokens
{#End}
{#Some {#End}}
@@ -3337,7 +3337,7 @@
(with_template [<parser> <parameter_type> <parameters_parser>]
[(def' .private (<parser> tokens)
(type_literal (Parser [Text (List <parameter_type>)]))
- (case tokens
+ (when tokens
(list#partial [_ {#Form local_declaration}] tokens')
(do maybe#monad
[% (localP local_declaration)
@@ -3357,9 +3357,9 @@
(def' .private (export_policyP tokens)
(type_literal (-> (List Code) [(List Code) Code]))
- (case tokens
+ (when tokens
(list#partial candidate tokens')
- (case candidate
+ (when candidate
[_ {#Bit it}]
[tokens' candidate]
@@ -3390,7 +3390,7 @@
(def' .private (bodyP tokens)
(type_literal (-> (List Code) (Maybe [(List Code) [(Maybe Code) Code]])))
- (case tokens
+ (when tokens
... TB
(list#partial type body tokens')
{#Some [tokens' [{#Some type} body]]}
@@ -3415,16 +3415,16 @@
(def' .public def
Macro
(macro (_ tokens)
- (case (definitionP tokens)
+ (when (definitionP tokens)
{#Some [export_policy name parameters ?type body]}
- (let [body (case parameters
+ (let [body (when parameters
{#End}
body
_
(` (function ((, (..local$ name)) (,* parameters))
(, body))))
- body (case ?type
+ body (when ?type
{#Some type}
(` (is (, type)
(, body)))
@@ -3441,7 +3441,7 @@
(with_template [<name> <form> <message>]
[(def .public <name>
(macro (_ tokens)
- (case (list#reversed tokens)
+ (when (list#reversed tokens)
(list#partial last init)
(meta#in (list (list#mix (is (-> Code Code Code)
(function (_ pre post) (` <form>)))
@@ -3464,10 +3464,10 @@
(def maybe#else
(macro (_ tokens state)
- (case tokens
+ (when tokens
(list else maybe)
(let [g!temp (is Code [dummy_location {#Symbol ["" ""]}])
- code (` (case (, maybe)
+ code (` (when (, maybe)
{.#Some (, g!temp)}
(, g!temp)
@@ -3480,7 +3480,7 @@
(def (text#all_split_by splitter input)
(-> Text Text (List Text))
- (case (..index splitter input)
+ (when (..index splitter input)
{#None}
(list input)
@@ -3496,7 +3496,7 @@
(def (item idx xs)
(All (_ a)
(-> Nat (List a) (Maybe a)))
- (case xs
+ (when xs
{#End}
{#None}
@@ -3508,7 +3508,7 @@
... https://en.wikipedia.org/wiki/Lambda_calculus#%CE%B2-reduction
(def (reduced env type)
(-> (List Type) Type Type)
- (case type
+ (when type
{#Sum left right}
{#Sum (reduced env left) (reduced env right)}
@@ -3519,7 +3519,7 @@
{#Apply (reduced env arg) (reduced env func)}
{#UnivQ ?local_env ?local_def}
- (case ?local_env
+ (when ?local_env
{#End}
{#UnivQ env ?local_def}
@@ -3527,7 +3527,7 @@
type)
{#ExQ ?local_env ?local_def}
- (case ?local_env
+ (when ?local_env
{#End}
{#ExQ env ?local_def}
@@ -3538,7 +3538,7 @@
{#Function (reduced env ?input) (reduced env ?output)}
{#Parameter idx}
- (case (item idx env)
+ (when (item idx env)
{#Some parameter}
parameter
@@ -3554,7 +3554,7 @@
(def (applied_type param type_fn)
(-> Type Type (Maybe Type))
- (case type_fn
+ (when type_fn
{#UnivQ env body}
{#Some (reduced (list#partial type_fn param env) body)}
@@ -3574,7 +3574,7 @@
(def (interface_methods type)
(-> Type (Maybe (List Type)))
- (case type
+ (when type
{#Product _}
{#Some (flat_tuple type)}
@@ -3605,7 +3605,7 @@
..#scopes scopes ..#type_context types ..#host host
..#seed seed ..#expected expected ..#location location ..#extensions extensions
..#scope_type_vars scope_type_vars ..#eval _eval] state]
- (case (property#value name modules)
+ (when (property#value name modules)
{#Some module}
{#Right state module}
@@ -3621,7 +3621,7 @@
..#definitions definitions
..#imports _
..#module_state _] =module]]
- (case (property#value name definitions)
+ (when (property#value name definitions)
{#Some {#Slot [exported type group index]}}
(meta#in [index
(list#each (function (_ slot)
@@ -3635,7 +3635,7 @@
(def (record_slots type)
(-> Type (Meta (Maybe [(List Symbol) (List Type)])))
- (case type
+ (when type
{#Apply arg func}
(record_slots func)
@@ -3653,9 +3653,9 @@
..#definitions definitions
..#imports _
..#module_state _] =module]]
- (case (property#value name definitions)
+ (when (property#value name definitions)
{#Some {#Type [exported? {#Named _ _type} {#Right slots}]}}
- (case (interface_methods _type)
+ (when (interface_methods _type)
{#Some members}
(meta#in {#Some [(list#each (function (_ slot) [module slot])
{#Item slots})
@@ -3677,7 +3677,7 @@
..#scopes scopes ..#type_context types ..#host host
..#seed seed ..#expected expected ..#location location ..#extensions extensions
..#scope_type_vars scope_type_vars ..#eval _eval] state]
- (case expected
+ (when expected
{#Some type}
{#Right state type}
@@ -3691,7 +3691,7 @@
implementation_type ..expected_type
tags+type (record_slots implementation_type)
tags (is (Meta (List Symbol))
- (case tags+type
+ (when tags+type
{#Some [tags _]}
(meta#in tags)
@@ -3707,9 +3707,9 @@
members (monad#each meta#monad
(is (-> Code (Meta (List Code)))
(function (_ token)
- (case token
+ (when token
[_ {#Form (list [_ {#Text "lux def"}] [_ {#Symbol ["" slot_name]}] value export_policy)}]
- (case (property#value slot_name tag_mappings)
+ (when (property#value slot_name tag_mappings)
{#Some tag}
(in (list tag value))
@@ -3723,7 +3723,7 @@
(def (text#interposed separator parts)
(-> Text (List Text) Text)
- (case parts
+ (when parts
{#End}
""
@@ -3742,12 +3742,12 @@
(All (_ a)
(-> (-> (List Code) (Maybe [(List Code) a]))
(-> (List Code) (Maybe (List a)))))
- (case tokens
+ (when tokens
{#Item _}
(do maybe#monad
[% (itP tokens)
.let [[tokens' head] %]
- tail (case tokens'
+ tail (when tokens'
{#Item _}
(everyP itP tokens')
@@ -3758,33 +3758,33 @@
{#End}
{#Some (list)}))
-(def (caseP tokens)
+(def (whenP tokens)
(-> (List Code) (Maybe [(List Code) [Text Code]]))
- (case tokens
+ (when tokens
(list#partial [_ {#Variant (list [_ {#Symbol ["" niladic]}])}] tokens')
{#Some [tokens' [niladic (` .Any)]]}
- (list#partial [_ {#Variant (list#partial [_ {#Symbol ["" polyadic]}] caseT)}] tokens')
- {#Some [tokens' [polyadic (` (..Tuple (,* caseT)))]]}
+ (list#partial [_ {#Variant (list#partial [_ {#Symbol ["" polyadic]}] whenT)}] tokens')
+ {#Some [tokens' [polyadic (` (..Tuple (,* whenT)))]]}
_
{#None}))
(def .public Variant
(macro (_ tokens)
- (case (everyP caseP tokens)
- {#Some cases}
- (meta#in (list (` (..Union (,* (list#each product#right cases))))
- (variant$ (list#each (function (_ case)
- (text$ (product#left case)))
- cases))))
+ (when (everyP whenP tokens)
+ {#Some whens}
+ (meta#in (list (` (..Union (,* (list#each product#right whens))))
+ (variant$ (list#each (function (_ when)
+ (text$ (product#left when)))
+ whens))))
{#None}
(failure (..wrong_syntax_error (symbol ..Variant))))))
(def (slotP tokens)
(-> (List Code) (Maybe [(List Code) [Text Code]]))
- (case tokens
+ (when tokens
(list#partial [_ {#Symbol ["" slot]}] type tokens')
{#Some [tokens' [slot type]]}
@@ -3793,9 +3793,9 @@
(def .public Record
(macro (_ tokens)
- (case tokens
+ (when tokens
(list [_ {#Tuple record}])
- (case (everyP slotP record)
+ (when (everyP slotP record)
{#Some slots}
(meta#in (list (` (..Tuple (,* (list#each product#right slots))))
(tuple$ (list#each (function (_ slot)
@@ -3820,7 +3820,7 @@
(def (textP tokens)
(-> (List Code) (Maybe [(List Code) Text]))
- (case tokens
+ (when tokens
(list#partial [_ {#Text it}] tokens')
{#Some [tokens' it]}
@@ -3832,9 +3832,9 @@
({[_ {#Form {#Item [_ {#Symbol declarer}] parameters}}]
(do meta#monad
[declaration (single_expansion (form$ (list#partial (symbol$ declarer) parameters)))]
- (case declaration
+ (when declaration
(list type [_ {#Variant tags}])
- (case (everyP textP tags)
+ (when (everyP textP tags)
{#Some tags}
(meta#in [type {#Some {#Left tags}}])
@@ -3842,7 +3842,7 @@
(failure "Improper type-definition syntax"))
(list type [_ {#Tuple slots}])
- (case (everyP textP slots)
+ (when (everyP textP slots)
{#Some slots}
(meta#in [type {#Some {#Right slots}}])
@@ -3861,7 +3861,7 @@
(def .public type
(macro (_ tokens)
- (case (typeP tokens)
+ (when (typeP tokens)
{#Some [export_policy name args type_codes]}
(do meta#monad
[type+labels?? (..type_declaration type_codes)
@@ -3869,23 +3869,23 @@
.let' [type_name (local$ name)
[type labels??] type+labels??
type' (is (Maybe Code)
- (case args
+ (when args
{#End}
{#Some type}
_
{#Some (` (.All ((, type_name) (,* (list#each local$ args)))
(, type)))}))]]
- (case type'
+ (when type'
{#Some type''}
(let [typeC (` {.#Named [(, (text$ module_name))
(, (text$ name))]
(..type_literal (, type''))})]
- (meta#in (list (case labels??
+ (meta#in (list (when labels??
{#Some labels}
(` ("lux def type tagged" (, type_name)
(, typeC)
- (, (case labels
+ (, (when labels
{#Left tags}
(` {(,* (list#each text$ tags))})
@@ -3945,7 +3945,7 @@
(-> Text Text Text Text)
((is (-> Text Text Text)
(function (again left right)
- (case (..text#split_by pattern right)
+ (when (..text#split_by pattern right)
{#Some [pre post]}
(again (all "lux text concat" left pre replacement) post)
@@ -3974,20 +3974,20 @@
(def (normal_parallel_path' hierarchy root)
(-> Text Text Text)
- (case [(text#split_by ..module_separator hierarchy)
+ (when [(text#split_by ..module_separator hierarchy)
(text#split_by ..parallel_hierarchy_sigil root)]
[{#Some [_ hierarchy']}
{#Some ["" root']}]
(normal_parallel_path' hierarchy' root')
_
- (case root
+ (when root
"" hierarchy
_ (all text#composite root ..module_separator hierarchy))))
(def (normal_parallel_path hierarchy root)
(-> Text Text (Maybe Text))
- (case (text#split_by ..parallel_hierarchy_sigil root)
+ (when (text#split_by ..parallel_hierarchy_sigil root)
{#Some ["" root']}
{#Some (normal_parallel_path' hierarchy root')}
@@ -3996,7 +3996,7 @@
(def (relative_ups relatives input)
(-> Nat Text Nat)
- (case ("lux text index" relatives ..module_separator input)
+ (when ("lux text index" relatives ..module_separator input)
{#None}
relatives
@@ -4007,7 +4007,7 @@
(def (list#after amount list)
(All (_ a) (-> Nat (List a) (List a)))
- (case [amount list]
+ (when [amount list]
(pattern#or [0 _]
[_ {#End}])
list
@@ -4017,7 +4017,7 @@
(def (absolute_module_name nested? relative_root module)
(-> Bit Text Text (Meta Text))
- (case (relative_ups 0 module)
+ (when (relative_ups 0 module)
0
(meta#in (if nested?
(all "lux text concat" relative_root ..module_separator module)
@@ -4033,7 +4033,7 @@
list#reversed
(text#interposed ..module_separator))
clean ("lux text clip" relatives (|> module "lux text size" ("lux i64 -" relatives)) module)
- output (case ("lux text size" clean)
+ output (when ("lux text size" clean)
0 prefix
_ (all text#composite prefix ..module_separator clean))]
(meta#in output))
@@ -4048,17 +4048,17 @@
[imports' (monad#each meta#monad
(is (-> Code (Meta (List Importation)))
(function (_ token)
- (case token
+ (when token
... Nested
[_ {#Tuple (list#partial [_ {#Symbol ["" module_name]}] extra)}]
(do meta#monad
- [absolute_module_name (case (normal_parallel_path relative_root module_name)
+ [absolute_module_name (when (normal_parallel_path relative_root module_name)
{#Some parallel_path}
(in parallel_path)
{#None}
(..absolute_module_name nested? relative_root module_name))
- extra,referral (case (referrals_parser #0 extra)
+ extra,referral (when (referrals_parser #0 extra)
{#Some extra,referral}
(in extra,referral)
@@ -4066,7 +4066,7 @@
(failure ""))
.let [[extra referral] extra,referral]
sub_imports (imports_parser #1 absolute_module_name context extra)]
- (in (case referral
+ (in (when referral
{#End}
sub_imports
@@ -4078,13 +4078,13 @@
[_ {#Tuple (list#partial [_ {#Text alias}] [_ {#Symbol ["" module_name]}] extra)}]
(do meta#monad
- [absolute_module_name (case (normal_parallel_path relative_root module_name)
+ [absolute_module_name (when (normal_parallel_path relative_root module_name)
{#Some parallel_path}
(in parallel_path)
{#None}
(..absolute_module_name nested? relative_root module_name))
- extra,referral (case (referrals_parser #1 extra)
+ extra,referral (when (referrals_parser #1 extra)
{#Some extra,referral}
(in extra,referral)
@@ -4093,7 +4093,7 @@
.let [[extra referral] extra,referral]
.let [module_alias (..module_alias {#Item module_name context} alias)]
sub_imports (imports_parser #1 absolute_module_name {#Item module_alias context} extra)]
- (in (case referral
+ (in (when referral
{#End}
sub_imports
@@ -4115,18 +4115,18 @@
(def (exported_definitions module state)
(-> Text (Meta (List Text)))
- (let [[current_module modules] (case state
+ (let [[current_module modules] (when state
[..#info info ..#source source ..#current_module current_module ..#modules modules
..#scopes scopes ..#type_context types ..#host host
..#seed seed ..#expected expected ..#location location ..#extensions extensions
..#scope_type_vars scope_type_vars ..#eval _eval]
[current_module modules])]
- (case (property#value module modules)
+ (when (property#value module modules)
{#Some =module}
(let [to_alias (list#each (is (-> [Text Global]
(List Text))
(function (_ [name definition])
- (case definition
+ (when definition
{#Alias _}
(list)
@@ -4152,7 +4152,7 @@
{#None}
{#Left (all text#composite
"Unknown module: " (text#encoded module) \n
- "Current module: " (case current_module
+ "Current module: " (when current_module
{#Some current_module}
(text#encoded current_module)
@@ -4168,7 +4168,7 @@
(def (list#only p xs)
(All (_ a)
(-> (-> a Bit) (List a) (List a)))
- (case xs
+ (when xs
{#End}
(list)
@@ -4177,13 +4177,13 @@
{#Item x (list#only p xs')}
(list#only p xs'))))
-(def (is_member? cases name)
+(def (is_member? whens name)
(-> (List Text) Text Bit)
- (let [output (list#mix (function (_ case prev)
+ (let [output (list#mix (function (_ when prev)
(or prev
- (text#= case name)))
+ (text#= when name)))
#0
- cases)]
+ whens)]
output))
(def (test_referrals current_module imported_module all_defs referred_defs)
@@ -4202,7 +4202,7 @@
(def .public only
(macro (_ tokens)
- (case (..parsed (all ..andP
+ (when (..parsed (all ..andP
..textP
..textP
..textP
@@ -4233,7 +4233,7 @@
(def .public except
(macro (_ tokens)
- (case (..parsed (all ..andP
+ (when (..parsed (all ..andP
..textP
..textP
..textP
@@ -4257,7 +4257,7 @@
..#scopes scopes ..#type_context types ..#host host
..#seed seed ..#expected expected ..#location location ..#extensions extensions
..#scope_type_vars scope_type_vars ..#eval _eval] state]
- (case (property#value expected_module modules)
+ (when (property#value expected_module modules)
{#None}
{#None}
@@ -4266,12 +4266,12 @@
..#module_aliases _
..#imports _
..#module_state _]}
- (case (property#value expected_short definitions)
+ (when (property#value expected_short definitions)
{#None}
{#None}
{#Some definition}
- (case definition
+ (when definition
{#Alias real_name}
(definition_type real_name state)
@@ -4289,7 +4289,7 @@
(def (type_variable idx bindings)
(-> Nat (List [Nat (Maybe Type)]) (Maybe Type))
- (case bindings
+ (when bindings
{#End}
{#End}
@@ -4306,31 +4306,31 @@
(function (_ compiler)
(let [temp (is (Either Text [Lux Type])
(if (text#= "" module)
- (case (in_env name compiler)
+ (when (in_env name compiler)
{#Some implementation_type}
{#Right [compiler implementation_type]}
_
- (case (definition_type [current_module name] compiler)
+ (when (definition_type [current_module name] compiler)
{#Some implementation_type}
{#Right [compiler implementation_type]}
_
{#Left (all text#composite "Unknown var: " (symbol#encoded full_name))}))
- (case (definition_type full_name compiler)
+ (when (definition_type full_name compiler)
{#Some implementation_type}
{#Right [compiler implementation_type]}
_
{#Left (all text#composite "Unknown var: " (symbol#encoded full_name))})))]
- (case temp
+ (when temp
{#Right [compiler {#Var type_id}]}
(let [[..#info _ ..#source _ ..#current_module _ ..#modules _
..#scopes _ ..#type_context type_context ..#host _
..#seed _ ..#expected _ ..#location _ ..#extensions extensions
..#scope_type_vars _ ..#eval _eval] compiler
[..#ex_counter _ ..#var_counter _ ..#var_bindings var_bindings] type_context]
- (case (type_variable type_id var_bindings)
+ (when (type_variable type_id var_bindings)
{#None}
temp
@@ -4343,9 +4343,9 @@
(def (list#all choice items)
(All (_ a b) (-> (-> a (Maybe b)) (List a) (List b)))
- (case items
+ (when items
{#Item head tail}
- (case (choice head)
+ (when (choice head)
{#Some head}
{#Item head (list#all choice tail)}
@@ -4389,7 +4389,7 @@
next (|> layer
(list#each product#right)
list#conjoint)]]
- (case next
+ (when next
{#End}
(in [pattern body])
@@ -4398,19 +4398,19 @@
[.let [sub_value (tuple$ (list#each (|>> product#left symbol$) next))]
sub_pattern,sub_body (open_layers alias (list#each product#right next) body)
.let [[sub_pattern sub_body] sub_pattern,sub_body]]
- (in [pattern (` (case (, sub_value)
+ (in [pattern (` (when (, sub_value)
(, sub_pattern)
(, sub_body)))])))))
(def .public open
(pattern
(macro (_ tokens)
- (case tokens
+ (when tokens
(list#partial [_ {#Form (list [_ {#Text alias}])}] body branches)
(do meta#monad
[g!temp (..generated_symbol "temp")]
(in (list#partial g!temp
- (` (..case (, g!temp)
+ (` (..when (, g!temp)
(..open (, g!temp) (, (text$ alias)))
(, body)))
branches)))
@@ -4421,7 +4421,7 @@
(do meta#monad
[init_type (type_definition name)
implementation_evidence (record_slots init_type)]
- (case implementation_evidence
+ (when implementation_evidence
{#None}
(failure (text#composite "Can only 'open' implementations: " (type#encoded init_type)))
@@ -4436,9 +4436,9 @@
(def .public cond
(macro (_ tokens)
- (case (list#reversed tokens)
+ (when (list#reversed tokens)
(list#partial else branches')
- (case (pairs branches')
+ (when (pairs branches')
{#Some branches'}
(meta#in (list (list#mix (is (-> [Code Code] Code Code)
(function (_ branch else)
@@ -4456,7 +4456,7 @@
(def (enumeration' idx xs)
(All (_ a)
(-> Nat (List a) (List [Nat a])))
- (case xs
+ (when xs
{#Item x xs'}
{#Item [idx x] (enumeration' ("lux i64 +" 1 idx) xs')}
@@ -4470,7 +4470,7 @@
(def .public the
(macro (_ tokens)
- (case tokens
+ (when tokens
(list [_ {#Symbol slot'}] record)
(do meta#monad
[slot (normal slot')
@@ -4478,7 +4478,7 @@
.let [[idx tags exported? type] output]
g!_ (..generated_symbol "_")
g!output (..generated_symbol "")]
- (case (interface_methods type)
+ (when (interface_methods type)
{#Some members}
(let [pattern (|> (zipped_2 tags (enumeration members))
(list#each (is (-> [Symbol [Nat Type]] (List Code))
@@ -4524,7 +4524,7 @@
g!_)))
tuple$)
source+ (` ({(, pattern) (, g!output)} (, source)))]]
- (case output
+ (when output
{#Some [tags' members']}
(do meta#monad
[decls' (monad#each meta#monad
@@ -4544,7 +4544,7 @@
(do meta#monad
[interface (type_definition implementation)
output (record_slots interface)]
- (case output
+ (when output
{#Some [slots terms]}
(do meta#monad
[.let [g!implementation (symbol$ implementation)]
@@ -4561,7 +4561,7 @@
(def (localized module global)
(-> Text Symbol Symbol)
- (case global
+ (when global
["" local]
[module local]
@@ -4570,7 +4570,7 @@
(def .public use
(macro (_ tokens)
- (case (..parsed (all ..andP
+ (when (..parsed (all ..andP
(..maybeP (all ..andP
..textP
..textP
@@ -4581,13 +4581,13 @@
tokens)
{.#Some [current_module,imported_module,import_alias alias implementations]}
(let [[current_module imported_module import_alias]
- (case current_module,imported_module,import_alias
+ (when current_module,imported_module,import_alias
{#Some [current_module imported_module import_alias]}
[current_module imported_module import_alias]
{#None}
["" "" ""])]
- (case implementations
+ (when implementations
{#Left implementations}
(do meta#monad
[declarations (|> implementations
@@ -4600,7 +4600,7 @@
[pre_defs,implementations (is (Meta [(List Code) (List Code)])
(monad#mix meta#monad
(function (_ it [pre_defs implementations])
- (case it
+ (when it
[_ {#Symbol _}]
(in [pre_defs
{#Item it implementations}])
@@ -4636,7 +4636,7 @@
(def (referrals module_name extra)
(-> Text (List Code) (Meta (List Referral)))
(do meta#monad
- [extra,referral (case (referrals_parser #0 extra)
+ [extra,referral (when (referrals_parser #0 extra)
{#Some extra,referral}
(in extra,referral)
@@ -4644,7 +4644,7 @@
(failure ""))
.let [[extra referral] extra,referral]
current_module current_module_name]
- (case extra
+ (when extra
{#End}
(in referral)
@@ -4659,7 +4659,7 @@
(def .public refer
(macro (_ tokens)
- (case tokens
+ (when tokens
(list#partial [_ {#Text imported_module}] [_ {#Text alias}] options)
(do meta#monad
[referrals (..referrals imported_module options)
@@ -4677,7 +4677,7 @@
(def .public with
(macro (_ tokens)
- (case (..parsed (..andP ..anyP ..anyP)
+ (when (..parsed (..andP ..anyP ..anyP)
tokens)
{.#Some [implementation expression]}
(meta#in (list (` (..let [(..open (, (text$ (alias_stand_in 0)))) (, implementation)]
@@ -4688,7 +4688,7 @@
(def .public at
(macro (_ tokens)
- (case tokens
+ (when tokens
(list implementation [_ {#Symbol member}])
(meta#in (list (` (..with (, implementation) (, (symbol$ member))))))
@@ -4700,13 +4700,13 @@
(def .public has
(macro (_ tokens)
- (case tokens
+ (when tokens
(list [_ {#Symbol slot'}] value record)
(do meta#monad
[slot (normal slot')
output (..type_slot slot)
.let [[idx tags exported? type] output]]
- (case (interface_methods type)
+ (when (interface_methods type)
{#Some members}
(do meta#monad
[pattern' (monad#each meta#monad
@@ -4738,7 +4738,7 @@
(failure "has can only use records.")))
(list [_ {#Tuple slots}] value record)
- (case slots
+ (when slots
{#End}
(failure (..wrong_syntax_error (symbol ..has)))
@@ -4784,13 +4784,13 @@
(def .public revised
(macro (_ tokens)
- (case tokens
+ (when tokens
(list [_ {#Symbol slot'}] fun record)
(do meta#monad
[slot (normal slot')
output (..type_slot slot)
.let [[idx tags exported? type] output]]
- (case (interface_methods type)
+ (when (interface_methods type)
{#Some members}
(do meta#monad
[pattern' (monad#each meta#monad
@@ -4822,7 +4822,7 @@
(failure "revised can only use records.")))
(list [_ {#Tuple slots}] fun record)
- (case slots
+ (when slots
{#End}
(failure (..wrong_syntax_error (symbol ..revised)))
@@ -4855,12 +4855,12 @@
(def .private with_template#pattern
(pattern
(macro (_ tokens)
- (case tokens
+ (when tokens
(list#partial [_ {#Form (list [_ {#Tuple bindings}]
[_ {#Tuple templates}])}]
[_ {#Form data}]
branches)
- (case (is (Maybe (List Code))
+ (when (is (Maybe (List Code))
(do maybe#monad
[bindings' (monad#each maybe#monad symbol_short bindings)
data' (monad#each maybe#monad tuple_list data)]
@@ -4896,12 +4896,12 @@
(def (interleaved xs ys)
(All (_ a)
(-> (List a) (List a) (List a)))
- (case xs
+ (when xs
{#End}
{#End}
{#Item x xs'}
- (case ys
+ (when ys
{#End}
{#End}
@@ -4910,7 +4910,7 @@
(def (type_code type)
(-> Type Code)
- (case type
+ (when type
{#Primitive name params}
(` {.#Primitive (, (text$ name)) (, (untemplated_list (list#each type_code params)))})
@@ -4941,22 +4941,22 @@
(def .public loop
(macro (_ tokens)
- (let [?params (case tokens
+ (let [?params (when tokens
(list [_ {#Form (list name [_ {#Tuple bindings}])}] body)
{#Some [name bindings body]}
_
{#None})]
- (case ?params
+ (when ?params
{#Some [name bindings body]}
- (case (pairs bindings)
+ (when (pairs bindings)
{#Some pairs}
(let [vars (list#each product#left pairs)
inits (list#each product#right pairs)]
(if (every? symbol? inits)
(do meta#monad
[inits' (is (Meta (List Symbol))
- (case (monad#each maybe#monad symbol_name inits)
+ (when (monad#each maybe#monad symbol_name inits)
{#Some inits'} (meta#in inits')
{#None} (failure (..wrong_syntax_error (symbol ..loop)))))
init_types (monad#each meta#monad type_definition inits')
@@ -4985,7 +4985,7 @@
(def .public with_expansions
(let [with_expansions' (is (-> Text (List Code) Code (List Code))
(function (with_expansions' label tokens target)
- (case target
+ (when target
(pattern#or [_ {#Bit _}]
[_ {#Nat _}]
[_ {#Int _}]
@@ -5007,7 +5007,7 @@
[#Variant]
[#Tuple]))))]
(macro (_ tokens)
- (case (parsed (andP (tupleP (someP bindingP)) (someP anyP)) tokens)
+ (when (parsed (andP (tupleP (someP bindingP)) (someP anyP)) tokens)
{#Some [bindings bodies]}
(loop (again [bindings bindings
map (is (Property_List (List Code))
@@ -5018,10 +5018,10 @@
(list#conjoint (list#each (with_expansions' binding expansion) it)))
(list it)
map)))]
- (case bindings
+ (when bindings
{#Item [var_name expr] &rest}
(do meta#monad
- [expansion (case (normal expr)
+ [expansion (when (normal expr)
(list expr)
(single_expansion expr)
@@ -5045,7 +5045,7 @@
(def .public as_expected
(macro (_ tokens)
- (case tokens
+ (when tokens
(list expr)
(do meta#monad
[type ..expected_type]
@@ -5059,7 +5059,7 @@
(function (_ compiler)
{#Right [compiler (the #location compiler)]}))]
(macro (_ tokens)
- (case tokens
+ (when tokens
{#End}
(do meta#monad
[location location
@@ -5073,7 +5073,7 @@
(def .public type_of
(macro (_ tokens)
- (case tokens
+ (when tokens
(list [_ {#Symbol var_name}])
(do meta#monad
[var_type (type_definition var_name)]
@@ -5106,7 +5106,7 @@
(` (`' (, (with_replacements replacement_environment
template))))))]
(macro (_ tokens)
- (case (templateP tokens)
+ (when (templateP tokens)
{#Some [name args input_templates]}
(do meta#monad
[g!tokens (..generated_symbol "tokens")
@@ -5114,7 +5114,7 @@
g!_ (..generated_symbol "_")
this_module ..current_module_name]
(in (list (` (..macro ((, (local$ name)) (, g!tokens) (, g!compiler))
- (case (, g!tokens)
+ (when (, g!tokens)
(list (,* (list#each local$ args)))
{.#Right [(, g!compiler)
(list (,* (list#each (instantiated_template (simple_replacement_environment args))
@@ -5143,7 +5143,7 @@
(def .public char
(macro (_ tokens compiler)
- (case tokens
+ (when tokens
(list [_ {#Text input}])
(if (|> input "lux text size" ("lux i64 =" 1))
(|> input ("lux text char" 0)
@@ -5160,7 +5160,7 @@
{#Right [compiler (the [#info #target] compiler)]}))
platform_name (is (-> Code (Meta Text))
(function (_ choice)
- (case choice
+ (when choice
[_ {#Text platform}]
(..meta#in platform)
@@ -5169,7 +5169,7 @@
[symbol (..global_symbol symbol)
type+value (..definition_value symbol)
.let [[type value] type+value]]
- (case (anonymous_type type)
+ (when (anonymous_type type)
{#Primitive "#Text" {#End}}
(in (as ..Text value))
@@ -5184,9 +5184,9 @@
\n "Must be either a text literal or a symbol.")))))
target_pick (is (-> Text (List [Code Code]) (Maybe Code) (Meta (List Code)))
(function (target_pick target options default)
- (case options
+ (when options
{#End}
- (case default
+ (when default
{#None}
(failure (all text#composite "No code for target platform: " target))
@@ -5200,7 +5200,7 @@
(meta#in (list pick))
(target_pick target options' default))))))]
(macro (_ tokens)
- (case (..parsed (..andP (..someP (..andP ..anyP ..anyP))
+ (when (..parsed (..andP (..someP (..andP ..anyP ..anyP))
(..maybeP ..anyP))
tokens)
{.#Some [options default]}
@@ -5214,7 +5214,7 @@
... TODO: Delete "scope_type_vars" (including the #scope_type_vars Lux state) and "parameter" ASAP.
(for "{old}" (these (def (scope_type_vars state)
(Meta (List Nat))
- (case state
+ (when state
[..#info info ..#source source ..#current_module _ ..#modules modules
..#scopes scopes ..#type_context types ..#host host
..#seed seed ..#expected expected ..#location location ..#extensions extensions
@@ -5223,11 +5223,11 @@
(def .public parameter
(macro (_ tokens)
- (case tokens
+ (when tokens
(list [_ {#Nat idx}])
(do meta#monad
[stvs ..scope_type_vars]
- (case (..item idx (list#reversed stvs))
+ (when (..item idx (list#reversed stvs))
{#Some var_id}
(in (list (` {.#Ex (, (nat$ var_id))})))
@@ -5286,7 +5286,7 @@
(def .public ,,
(..immediate_unquote
(macro (_ it)
- (case it
+ (when it
(list it)
(meta#in (list it))
@@ -5305,20 +5305,20 @@
(def (embedded_expansions code)
(-> Code (Meta [(List Code) Code]))
- (case code
+ (when code
[@ {#Form (list#partial [@symbol {#Symbol original_symbol}] parameters)}]
(with_expansions [<failure> (aggregate_embedded_expansions embedded_expansions @ #Form (list#partial [@symbol {#Symbol original_symbol}] parameters))]
(do meta#monad
[resolved_symbol (..normal original_symbol)
?resolved_symbol (meta#try (..global_symbol resolved_symbol))]
- (case ?resolved_symbol
+ (when ?resolved_symbol
{#Left _}
<failure>
{#Right resolved_symbol}
(do meta#monad
[?type,value (meta#try (..definition_value resolved_symbol))]
- (case ?type,value
+ (when ?type,value
{#Left _}
<failure>
@@ -5343,7 +5343,7 @@
(def .public ``
(macro (_ tokens)
- (case tokens
+ (when tokens
(list raw)
(do meta#monad
[=raw (..embedded_expansions raw)
@@ -5363,7 +5363,7 @@
(def .public try
(macro (_ tokens)
- (case tokens
+ (when tokens
(list expression)
(do meta#monad
[g!_ (..generated_symbol "g!_")]
@@ -5376,7 +5376,7 @@
(def (methodP tokens)
(-> (List Code) (Maybe [(List Code) [Text Code]]))
- (case tokens
+ (when tokens
(list#partial [_ {#Form (list [_ {#Text "lux type check"}]
type
[_ {#Symbol ["" name]}])}]
@@ -5390,7 +5390,7 @@
(macro (_ tokens)
(do meta#monad
[methods' (monad#each meta#monad complete_expansion tokens)]
- (case (everyP methodP (list#conjoint methods'))
+ (when (everyP methodP (list#conjoint methods'))
{#Some methods}
(in (list (` (..Tuple (,* (list#each product#right methods))))
(tuple$ (list#each (|>> product#left text$) methods))))
@@ -5406,13 +5406,13 @@
(, (let$ (local$ name) (` {.#Apply (..Primitive "") (, g!self)})
body)))})))]
(macro (_ tokens)
- (case tokens
+ (when tokens
(list [_ {#Symbol "" name}] body)
(do meta#monad
[body' (complete_expansion body)
g!self (generated_symbol "g!self")
g!dummy (generated_symbol "g!dummy")]
- (case body'
+ (when body'
(list body' labels)
(in (list (recursive_type g!self g!dummy name body') labels))