aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/library/lux/tool/compiler/language
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib/source/library/lux/tool/compiler/language')
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case/coverage.lux13
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/function.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/inference.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/structure.lux8
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux40
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/common.lux93
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/common.lux15
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux6
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua.lux51
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/function.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/structure.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/runtime.lux42
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/case.lux5
14 files changed, 155 insertions, 130 deletions
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux
index d5b6529f0..5532c5977 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux
@@ -84,7 +84,7 @@
(#.Var id)
(do ///.monad
[?caseT' (//type.with_env
- (check.read' id))]
+ (check.peek id))]
(.case ?caseT'
(#.Some caseT')
(recur envs caseT')
@@ -110,7 +110,7 @@
(do ///.monad
[funcT' (//type.with_env
(do check.monad
- [?funct' (check.read' funcT_id)]
+ [?funct' (check.peek funcT_id)]
(.case ?funct'
(#.Some funct')
(in funct')
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case/coverage.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case/coverage.lux
index 31ed0f394..36c5f193f 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case/coverage.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case/coverage.lux
@@ -48,12 +48,13 @@
... way, while the other tags cover more specific cases for bits
... and variants.
(type: .public #rec Coverage
- #Partial
- (#Bit Bit)
- (#Variant (Maybe Nat) (Dictionary Nat Coverage))
- (#Seq Coverage Coverage)
- (#Alt Coverage Coverage)
- #Exhaustive)
+ (.Variant
+ #Partial
+ (#Bit Bit)
+ (#Variant (Maybe Nat) (Dictionary Nat Coverage))
+ (#Seq Coverage Coverage)
+ (#Alt Coverage Coverage)
+ #Exhaustive))
(def: .public (exhaustive? coverage)
(-> Coverage Bit)
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/function.lux
index 931e27eeb..a499b5df4 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/function.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/function.lux
@@ -71,7 +71,7 @@
(#.Var id)
(do !
[?expectedT' (//type.with_env
- (check.read' id))]
+ (check.peek id))]
(case ?expectedT'
(#.Some expectedT')
(recur expectedT')
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/inference.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/inference.lux
index 36ddce2e2..366a92cad 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/inference.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/inference.lux
@@ -167,7 +167,7 @@
(#.Var infer_id)
(do ///.monad
[?inferT' (//type.with_env
- (check.read' infer_id))]
+ (check.peek infer_id))]
(case ?inferT'
(#.Some inferT')
(general archive analyse inferT' args)
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/structure.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/structure.lux
index 76781c92a..f44670a38 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/structure.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/structure.lux
@@ -119,7 +119,7 @@
(#.Var id)
(do !
[?expectedT' (//type.with_env
- (check.read' id))]
+ (check.peek id))]
(case ?expectedT'
(#.Some expectedT')
(//type.with_type expectedT'
@@ -145,7 +145,7 @@
(#.Var funT_id)
(do !
[?funT' (//type.with_env
- (check.read' funT_id))]
+ (check.peek funT_id))]
(case ?funT'
(#.Some funT')
(//type.with_type (#.Apply inputT funT')
@@ -209,7 +209,7 @@
(#.Var id)
(do !
[?expectedT' (//type.with_env
- (check.read' id))]
+ (check.peek id))]
(case ?expectedT'
(#.Some expectedT')
(//type.with_type expectedT'
@@ -239,7 +239,7 @@
(#.Var funT_id)
(do !
[?funT' (//type.with_env
- (check.read' funT_id))]
+ (check.peek funT_id))]
(case ?funT'
(#.Some funT')
(//type.with_type (#.Apply inputT funT')
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux
index b1b57e1ff..ef87ca48a 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux
@@ -189,17 +189,19 @@
)
(type: Member
- {#class External
- #member Text})
+ (Record
+ {#class External
+ #member Text}))
(def: member
(Parser Member)
($_ <>.and <code>.text <code>.text))
(type: Method_Signature
- {#method .Type
- #deprecated? Bit
- #exceptions (List .Type)})
+ (Record
+ {#method .Type
+ #deprecated? Bit
+ #exceptions (List .Type)}))
(template [<name>]
[(exception: .public (<name> {type .Type})
@@ -1079,11 +1081,12 @@
objectA)))))]))
(type: Method_Style
- #Static
- #Abstract
- #Virtual
- #Special
- #Interface)
+ (Variant
+ #Static
+ #Abstract
+ #Virtual
+ #Special
+ #Interface))
(def: (check_method aliasing class method_name method_style inputsJT method)
(-> Aliasing (java/lang/Class java/lang/Object) Text Method_Style (List (Type Value)) java/lang/reflect/Method (Operation Bit))
@@ -1246,8 +1249,9 @@
exceptionsT]))))
(type: Evaluation
- (#Pass Method_Signature)
- (#Hint Method_Signature))
+ (Variant
+ (#Pass Method_Signature)
+ (#Hint Method_Signature)))
(template [<name> <tag>]
[(def: <name>
@@ -1597,10 +1601,11 @@
)
(type: .public Visibility
- #Public
- #Private
- #Protected
- #Default)
+ (Variant
+ #Public
+ #Private
+ #Protected
+ #Default))
(type: .public Finality Bit)
(type: .public Strictness Bit)
@@ -2022,7 +2027,8 @@
))))))
(type: .public (Method_Definition a)
- (#Overriden_Method (Overriden_Method a)))
+ (Variant
+ (#Overriden_Method (Overriden_Method a))))
(def: .public parameter_types
(-> (List (Type Var)) (Check (List [(Type Var) .Type])))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/common.lux
index 11605c1d5..0c812936b 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/common.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/common.lux
@@ -19,7 +19,7 @@
[number
["f" frac]]]
["@" target
- ["_" lua (#+ Expression)]]]]
+ ["_" lua (#+ Expression Statement)]]]]
["." //// #_
["/" bundle]
["/#" // #_
@@ -28,12 +28,18 @@
[extension (#+ Nullary Unary Binary Trinary
nullary unary binary trinary)]
["//" lua #_
- ["#." runtime (#+ Operation Phase Handler Bundle Generator)]]]
+ ["#." runtime (#+ Operation Phase Phase! Handler Bundle Generator)]
+ ["#." primitive]
+ ["#." structure]
+ ["#." reference]
+ ["#." case]
+ ["#." loop]
+ ["#." function]]]
[//
- [synthesis (#+ %synthesis)]
+ ["." synthesis (#+ %synthesis)]
["." generation]
[///
- ["#" phase]]]]])
+ ["#" phase ("#\." monad)]]]]])
(def: .public (custom [parser handler])
(All [s]
@@ -49,7 +55,51 @@
(/////.except extension.invalid_syntax [extension_name %synthesis input]))))
(template: (!unary function)
- (|>> list _.apply/* (|> (_.var function))))
+ [(|>> list _.apply/* (|> (_.var function)))])
+
+(def: .public (statement expression archive synthesis)
+ Phase!
+ (case synthesis
+ ... TODO: Get rid of this ASAP
+ (#synthesis.Extension "lux syntax char case!" parameters)
+ (do /////.monad
+ [body (expression archive synthesis)]
+ (in (:as Statement body)))
+
+ (^template [<tag>]
+ [(^ (<tag> value))
+ (/////\each _.return (expression archive synthesis))])
+ ([synthesis.bit]
+ [synthesis.i64]
+ [synthesis.f64]
+ [synthesis.text]
+ [synthesis.variant]
+ [synthesis.tuple]
+ [#synthesis.Reference]
+ [synthesis.branch/get]
+ [synthesis.function/apply]
+ [#synthesis.Extension])
+
+ (^ (synthesis.branch/case case))
+ (//case.case! statement expression archive case)
+
+ (^ (synthesis.branch/let let))
+ (//case.let! statement expression archive let)
+
+ (^ (synthesis.branch/if if))
+ (//case.if! statement expression archive if)
+
+ (^ (synthesis.loop/scope scope))
+ (do /////.monad
+ [[inits scope!] (//loop.scope! statement expression archive false scope)]
+ (in scope!))
+
+ (^ (synthesis.loop/recur updates))
+ (//loop.recur! statement expression archive updates)
+
+ (^ (synthesis.function/abstraction abstraction))
+ (/////\each _.return (//function.function statement expression archive abstraction))
+ ))
... TODO: Get rid of this ASAP
(def: lux::syntax_char_case!
@@ -62,12 +112,12 @@
(function (_ extension_name phase archive [input else conditionals])
(do {! /////.monad}
[inputG (phase archive input)
- elseG (phase archive else)
+ else! (..statement phase archive else)
@input (\ ! each _.var (generation.identifier "input"))
- conditionalsG (: (Operation (List [Expression Expression]))
+ conditionals! (: (Operation (List [Expression Statement]))
(monad.each ! (function (_ [chars branch])
(do !
- [branchG (phase archive branch)]
+ [branch! (..statement phase archive branch)]
(in [(|> chars
(list\each (|>> .int _.int (_.= @input)))
(list\mix (function (_ clause total)
@@ -75,14 +125,23 @@
clause
(_.or clause total)))
_.nil))
- branchG])))
+ branch!])))
conditionals))
- .let [closure (_.closure (list @input)
- (list\mix (function (_ [test then] else)
- (_.if test (_.return then) else))
- (_.return elseG)
- conditionalsG))]]
- (in (_.apply/1 closure inputG))))]))
+ ... .let [closure (_.closure (list @input)
+ ... (list\mix (function (_ [test then] else)
+ ... (_.if test (_.return then) else))
+ ... (_.return elseG)
+ ... conditionalsG))]
+ ]
+ ... (in (_.apply/1 closure inputG))
+ (in (<| (:as Expression)
+ (: Statement)
+ ($_ _.then
+ (_.set (list @input) inputG)
+ (list\mix (function (_ [test then!] else!)
+ (_.if test then! else!))
+ else!
+ conditionals!))))))]))
(def: lux_procs
Bundle
@@ -98,8 +157,8 @@
(/.install "and" (binary (product.uncurried _.bit_and)))
(/.install "or" (binary (product.uncurried _.bit_or)))
(/.install "xor" (binary (product.uncurried _.bit_xor)))
- (/.install "left-shift" (binary (product.uncurried //runtime.i64//left_shift)))
- (/.install "right-shift" (binary (product.uncurried //runtime.i64//right_shift)))
+ (/.install "left-shift" (binary (product.uncurried //runtime.i64//left_shifted)))
+ (/.install "right-shift" (binary (product.uncurried //runtime.i64//right_shifted)))
(/.install "=" (binary (product.uncurried _.=)))
(/.install "+" (binary (product.uncurried _.+)))
(/.install "-" (binary (product.uncurried _.-)))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/common.lux
index 78e4d7a4a..16ac4b882 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/common.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/common.lux
@@ -140,13 +140,14 @@
... _ (generation.save! (product.right artifact_id) #.None closure)
]
... (in (_.apply/* @closure dependencies))
- (in (:as (Expression Any)
- ($_ _.then
- (_.set (list @input) inputG)
- (list\mix (function (_ [test then!] else!)
- (_.if test then! else!))
- else!
- conditionals!))))))]))
+ (in (<| (:as (Expression Any))
+ (: (Statement Any))
+ ($_ _.then
+ (_.set (list @input) inputG)
+ (list\mix (function (_ [test then!] else!)
+ (_.if test then! else!))
+ else!
+ conditionals!))))))]))
(def: lux_procs
Bundle
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux
index 6579de615..b76af26be 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux
@@ -601,12 +601,12 @@
(_.apply/1 (_.var "Math.log"))
(_./ (_.var "Math.LN2"))
(_.apply/1 (_.var "Math.ceil"))))
- (_.define delta (_.? (_.<= (_.i32 +48) log2)
- (_.i32 +1)
+ (_.define delta (_.? (_.> (_.i32 +48) log2)
(_.apply/2 (_.var "Math.pow")
(_.i32 +2)
(_.- (_.i32 +48)
- log2))))
+ log2))
+ (_.i32 +1)))
(_.define approximate_result approximate_result')
(_.define approximate_remainder approx_remainder)
(_.while (_.or (negative? approximate_remainder)
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua.lux
index 59dc82f3c..05fa66ca8 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua.lux
@@ -8,7 +8,7 @@
[target
["_" lua]]]]
["." / #_
- [runtime (#+ Phase Phase!)]
+ [runtime (#+ Phase)]
["#." primitive]
["#." structure]
["#." reference]
@@ -18,7 +18,10 @@
["/#" // #_
["#." reference]
["/#" // #_
- ["#." extension]
+ ["#." extension
+ [generation
+ [lua
+ ["#/." common]]]]
["/#" // #_
[analysis (#+)]
["." synthesis]
@@ -27,44 +30,6 @@
[reference (#+)
[variable (#+)]]]]]]])
-(def: (statement expression archive synthesis)
- Phase!
- (case synthesis
- (^template [<tag>]
- [(^ (<tag> value))
- (//////phase\each _.return (expression archive synthesis))])
- ([synthesis.bit]
- [synthesis.i64]
- [synthesis.f64]
- [synthesis.text]
- [synthesis.variant]
- [synthesis.tuple]
- [#synthesis.Reference]
- [synthesis.branch/get]
- [synthesis.function/apply]
- [#synthesis.Extension])
-
- (^ (synthesis.branch/case case))
- (/case.case! statement expression archive case)
-
- (^ (synthesis.branch/let let))
- (/case.let! statement expression archive let)
-
- (^ (synthesis.branch/if if))
- (/case.if! statement expression archive if)
-
- (^ (synthesis.loop/scope scope))
- (do //////phase.monad
- [[inits scope!] (/loop.scope! statement expression archive false scope)]
- (in scope!))
-
- (^ (synthesis.loop/recur updates))
- (/loop.recur! statement expression archive updates)
-
- (^ (synthesis.function/abstraction abstraction))
- (//////phase\each _.return (/function.function statement expression archive abstraction))
- ))
-
(exception: .public cannot_recur_as_an_expression)
(def: (expression archive synthesis)
@@ -88,7 +53,7 @@
(//reference.reference /reference.system archive value)
(^ (synthesis.branch/case case))
- (/case.case ..statement expression archive case)
+ (/case.case ///extension/common.statement expression archive case)
(^ (synthesis.branch/let let))
(/case.let expression archive let)
@@ -100,13 +65,13 @@
(/case.get expression archive get)
(^ (synthesis.loop/scope scope))
- (/loop.scope ..statement expression archive scope)
+ (/loop.scope ///extension/common.statement expression archive scope)
(^ (synthesis.loop/recur updates))
(//////phase.except ..cannot_recur_as_an_expression [])
(^ (synthesis.function/abstraction abstraction))
- (/function.function ..statement expression archive abstraction)
+ (/function.function ///extension/common.statement expression archive abstraction)
(^ (synthesis.function/apply application))
(/function.apply expression archive application)
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/function.lux
index 0d96c3150..f88bc1d3a 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/function.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/function.lux
@@ -1,6 +1,6 @@
(.module:
[library
- [lux (#- function)
+ [lux (#- Tuple Variant function)
[abstract
["." monad (#+ do)]]
[control
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/structure.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/structure.lux
index 59d70ae69..ebb503f26 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/structure.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/structure.lux
@@ -1,6 +1,6 @@
(.module:
[library
- [lux #*
+ [lux (#- Tuple Variant)
[abstract
["." monad (#+ do)]]
[target
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/runtime.lux
index 5d91dbde7..26c962945 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/runtime.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/runtime.lux
@@ -180,10 +180,10 @@
(runtime: (i64::unsigned_low input)
(with_vars [low]
($_ _.then
- (_.set! low (|> input (_.item (_.string ..i64_low_field))))
- (_.if (|> low (_.>= (_.int +0)))
- low
- (|> low (_.+ f2^32))))))
+ (_.set! low (_.item (_.string ..i64_low_field) input))
+ (_.if (_.< (_.int +0) low)
+ (_.+ f2^32 low)
+ low))))
(runtime: (i64::float input)
(let [high (|> input
@@ -423,9 +423,10 @@
(i64::new high low))])
(let [low (|> (i64_high input)
(i64::arithmetic_right_shifted_32 (|> shift (_.- (_.int +32)))))
- high (_.if (|> (i64_high input) (_.>= (_.int +0)))
- (_.int +0)
- (_.int -1))]
+ high (_.if (_.< (_.int +0)
+ (i64_high input))
+ (_.int -1)
+ (_.int +0))]
(i64::new high low)))))
(runtime: (i64::/ param subject)
@@ -485,10 +486,10 @@
(_.var "floor"))
calc_approximate_result (i64::of_float approximate)
calc_approximate_remainder (|> approximate_result (i64::* param))
- delta (_.if (|> (_.float +48.0) (_.<= log2))
- (_.float +1.0)
+ delta (_.if (_.> log2 (_.float +48.0))
(_.** (|> log2 (_.- (_.float +48.0)))
- (_.float +2.0)))]
+ (_.float +2.0))
+ (_.float +1.0))]
($_ _.then
(_.set! approximate (_.apply (list (_.float +1.0) calc_rough_estimate)
(_.var "max")))
@@ -722,15 +723,6 @@
(-> Expression Expression)
(|>> (_.+ (_.int +1))))
-(template [<name> <top_cmp>]
- [(def: (<name> top value)
- (-> Expression Expression Expression)
- (|> (|> value (_.>= (_.int +0)))
- (_.and (|> value (<top_cmp> top)))))]
-
- [within? _.<]
- )
-
(def: (text_clip start end text)
(-> Expression Expression Expression Expression)
(_.apply (list text start end)
@@ -745,7 +737,7 @@
($_ _.then
(_.set! startF (i64::float start))
(_.set! subjectL (text_length subject))
- (_.if (|> startF (within? subjectL))
+ (_.if (_.< subjectL startF)
($_ _.then
(_.set! idx (|> (_.apply_kw (list param (_.if (|> startF (_.= (_.int +0)))
subject
@@ -765,7 +757,7 @@
($_ _.then
(_.set! length (_.length text))
(_.set! to (_.+ additional minimum))
- (_.if (within? length to)
+ (_.if (_.< length to)
(..some (text_clip (++ minimum) (++ to) text))
..none))))
@@ -775,7 +767,7 @@
(_.var "utf8ToInt")))
(runtime: (text::char text idx)
- (_.if (|> idx (within? (_.length text)))
+ (_.if (_.< (_.length text) idx)
($_ _.then
(_.set! idx (++ idx))
(..some (i64::of_float (char_at idx text))))
@@ -791,9 +783,9 @@
(def: (check_index_out_of_bounds array idx body)
(-> Expression Expression Expression Expression)
- (_.if (|> idx (_.<= (_.length array)))
- body
- (_.stop (_.string "Array index out of bounds!"))))
+ (_.if (_.> (_.length array) idx)
+ (_.stop (_.string "Array index out of bounds!"))
+ body))
(runtime: (array::new size)
(with_vars [output]
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/case.lux
index 75e27d5bf..b6544e285 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/case.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/case.lux
@@ -317,8 +317,9 @@
"Invalid expression for pattern-matching.")
(type: .public Storage
- {#bindings (Set Register)
- #dependencies (Set Variable)})
+ (Record
+ {#bindings (Set Register)
+ #dependencies (Set Variable)}))
(def: empty
Storage