aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/library
diff options
context:
space:
mode:
Diffstat (limited to '')
-rw-r--r--stdlib/source/library/lux.lux2
-rw-r--r--stdlib/source/library/lux/abstract/comonad.lux16
-rw-r--r--stdlib/source/library/lux/abstract/monad.lux16
-rw-r--r--stdlib/source/library/lux/control/parser/type.lux2
-rw-r--r--stdlib/source/library/lux/data/collection/dictionary/ordered.lux56
-rw-r--r--stdlib/source/library/lux/data/text/regex.lux4
-rw-r--r--stdlib/source/library/lux/debug.lux14
-rw-r--r--stdlib/source/library/lux/ffi.jvm.lux6
-rw-r--r--stdlib/source/library/lux/ffi.old.lux12
-rw-r--r--stdlib/source/library/lux/macro/syntax.lux20
-rw-r--r--stdlib/source/library/lux/math/number.lux9
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/common.lux2
-rw-r--r--stdlib/source/library/lux/tool/interpreter.lux36
13 files changed, 101 insertions, 94 deletions
diff --git a/stdlib/source/library/lux.lux b/stdlib/source/library/lux.lux
index 93e5c00cc..d10f8d2f5 100644
--- a/stdlib/source/library/lux.lux
+++ b/stdlib/source/library/lux.lux
@@ -4575,7 +4575,7 @@
(def: (case_level^ level)
(-> Code (Meta [Code Code]))
(case level
- (^ [_ (#Record (list [expr binding]))])
+ (^ [_ (#Tuple (list expr binding))])
(in_meta [expr binding])
_
diff --git a/stdlib/source/library/lux/abstract/comonad.lux b/stdlib/source/library/lux/abstract/comonad.lux
index 2e37a943e..b4dd60a68 100644
--- a/stdlib/source/library/lux/abstract/comonad.lux
+++ b/stdlib/source/library/lux/abstract/comonad.lux
@@ -60,16 +60,16 @@
(#.Right [state (list (case ?name
(#.Some name)
(let [name [location.dummy (#.Identifier ["" name])]]
- (` ({(~ name)
- ({[(~ g!each) (~' out) (~ g!disjoint)]
- (~ body')}
- (~ name))}
- (~ comonad))))
+ (` (.case (~ comonad)
+ (~ name)
+ (.case (~ name)
+ [(~ g!each) (~' out) (~ g!disjoint)]
+ (~ body')))))
#.None
- (` ({[(~ g!each) (~' out) (~ g!disjoint)]
- (~ body')}
- (~ comonad)))))]))
+ (` (.case (~ comonad)
+ [(~ g!each) (~' out) (~ g!disjoint)]
+ (~ body')))))]))
(#.Left "'be' bindings must have an even number of parts."))
#.None
diff --git a/stdlib/source/library/lux/abstract/monad.lux b/stdlib/source/library/lux/abstract/monad.lux
index b90a93580..98baec35e 100644
--- a/stdlib/source/library/lux/abstract/monad.lux
+++ b/stdlib/source/library/lux/abstract/monad.lux
@@ -91,16 +91,16 @@
(#.Right [state (list (case ?name
(#.Some name)
(let [name [location.dummy (#.Identifier ["" name])]]
- (` ({(~ name)
- ({[(~ g!each) (~' in) (~ g!conjoint)]
- (~ body')}
- (~ name))}
- (~ monad))))
+ (` (.case (~ monad)
+ (~ name)
+ (.case (~ name)
+ [(~ g!each) (~' in) (~ g!conjoint)]
+ (~ body')))))
#.None
- (` ({[(~ g!each) (~' in) (~ g!conjoint)]
- (~ body')}
- (~ monad)))))]))
+ (` (.case (~ monad)
+ [(~ g!each) (~' in) (~ g!conjoint)]
+ (~ body')))))]))
(#.Left "'do' bindings must have an even number of parts."))
#.None
diff --git a/stdlib/source/library/lux/control/parser/type.lux b/stdlib/source/library/lux/control/parser/type.lux
index 735b594d8..c75df1031 100644
--- a/stdlib/source/library/lux/control/parser/type.lux
+++ b/stdlib/source/library/lux/control/parser/type.lux
@@ -329,7 +329,7 @@
(case (type.anonymous headT)
(^multi (^ (#.Apply (|recursion_dummy|) (#.Parameter funcT_idx)))
(n.= 0 (adjusted_idx env funcT_idx))
- {(dictionary.value 0 env) (#.Some [self_type self_call])})
+ [(dictionary.value 0 env) (#.Some [self_type self_call])])
(in self_call)
_
diff --git a/stdlib/source/library/lux/data/collection/dictionary/ordered.lux b/stdlib/source/library/lux/data/collection/dictionary/ordered.lux
index 8407703a0..857683d40 100644
--- a/stdlib/source/library/lux/data/collection/dictionary/ordered.lux
+++ b/stdlib/source/library/lux/data/collection/dictionary/ordered.lux
@@ -168,7 +168,7 @@
#Red
(case (value@ #left addition)
(^multi (#.Some left)
- {(value@ #color left) #Red})
+ [(value@ #color left) #Red])
(red (value@ #key addition)
(value@ #value addition)
(#.Some (blackened left))
@@ -180,7 +180,7 @@
_
(case (value@ #right addition)
(^multi (#.Some right)
- {(value@ #color right) #Red})
+ [(value@ #color right) #Red])
(red (value@ #key right)
(value@ #value right)
(#.Some (black (value@ #key addition)
@@ -217,7 +217,7 @@
#Red
(case (value@ #right addition)
(^multi (#.Some right)
- {(value@ #color right) #Red})
+ [(value@ #color right) #Red])
(red (value@ #key addition)
(value@ #value addition)
(#.Some (black (value@ #key center)
@@ -229,7 +229,7 @@
_
(case (value@ #left addition)
(^multi (#.Some left)
- {(value@ #color left) #Red})
+ [(value@ #color left) #Red])
(red (value@ #key left)
(value@ #value left)
(#.Some (black (value@ #key center)
@@ -280,18 +280,18 @@
(All (_ k v) (-> k v (Maybe (Node k v)) (Maybe (Node k v)) (Node k v)))
(case ?left
(^multi (#.Some left)
- {(value@ #color left) #Red}
- {(value@ #left left) (#.Some left>>left)}
- {(value@ #color left>>left) #Red})
+ [(value@ #color left) #Red]
+ [(value@ #left left) (#.Some left>>left)]
+ [(value@ #color left>>left) #Red])
(red (value@ #key left)
(value@ #value left)
(#.Some (blackened left>>left))
(#.Some (black key value (value@ #right left) ?right)))
(^multi (#.Some left)
- {(value@ #color left) #Red}
- {(value@ #right left) (#.Some left>>right)}
- {(value@ #color left>>right) #Red})
+ [(value@ #color left) #Red]
+ [(value@ #right left) (#.Some left>>right)]
+ [(value@ #color left>>right) #Red])
(red (value@ #key left>>right)
(value@ #value left>>right)
(#.Some (black (value@ #key left)
@@ -309,18 +309,18 @@
(All (_ k v) (-> k v (Maybe (Node k v)) (Maybe (Node k v)) (Node k v)))
(case ?right
(^multi (#.Some right)
- {(value@ #color right) #Red}
- {(value@ #right right) (#.Some right>>right)}
- {(value@ #color right>>right) #Red})
+ [(value@ #color right) #Red]
+ [(value@ #right right) (#.Some right>>right)]
+ [(value@ #color right>>right) #Red])
(red (value@ #key right)
(value@ #value right)
(#.Some (black key value ?left (value@ #left right)))
(#.Some (blackened right>>right)))
(^multi (#.Some right)
- {(value@ #color right) #Red}
- {(value@ #left right) (#.Some right>>left)}
- {(value@ #color right>>left) #Red})
+ [(value@ #color right) #Red]
+ [(value@ #left right) (#.Some right>>left)]
+ [(value@ #color right>>left) #Red])
(red (value@ #key right>>left)
(value@ #value right>>left)
(#.Some (black key value ?left (value@ #left right>>left)))
@@ -336,19 +336,19 @@
(All (_ k v) (-> k v (Maybe (Node k v)) (Maybe (Node k v)) (Node k v)))
(case ?left
(^multi (#.Some left)
- {(value@ #color left) #Red})
+ [(value@ #color left) #Red])
(red key value (#.Some (blackened left)) ?right)
_
(case ?right
(^multi (#.Some right)
- {(value@ #color right) #Black})
+ [(value@ #color right) #Black])
(right_balanced key value ?left (#.Some (reddened right)))
(^multi (#.Some right)
- {(value@ #color right) #Red}
- {(value@ #left right) (#.Some right>>left)}
- {(value@ #color right>>left) #Black})
+ [(value@ #color right) #Red]
+ [(value@ #left right) (#.Some right>>left)]
+ [(value@ #color right>>left) #Black])
(red (value@ #key right>>left)
(value@ #value right>>left)
(#.Some (black key value ?left (value@ #left right>>left)))
@@ -365,19 +365,19 @@
(All (_ k v) (-> k v (Maybe (Node k v)) (Maybe (Node k v)) (Node k v)))
(case ?right
(^multi (#.Some right)
- {(value@ #color right) #Red})
+ [(value@ #color right) #Red])
(red key value ?left (#.Some (blackened right)))
_
(case ?left
(^multi (#.Some left)
- {(value@ #color left) #Black})
+ [(value@ #color left) #Black])
(left_balanced key value (#.Some (reddened left)) ?right)
(^multi (#.Some left)
- {(value@ #color left) #Red}
- {(value@ #right left) (#.Some left>>right)}
- {(value@ #color left>>right) #Black})
+ [(value@ #color left) #Red]
+ [(value@ #right left) (#.Some left>>right)]
+ [(value@ #color left>>right) #Black])
(red (value@ #key left>>right)
(value@ #value left>>right)
(#.Some (left_balanced (value@ #key left)
@@ -496,7 +496,7 @@
(if go_left?
(case (value@ #left root)
(^multi (#.Some left)
- {(value@ #color left) #Black})
+ [(value@ #color left) #Black])
[(#.Some (without_left root_key root_val side_outcome (value@ #right root)))
#0]
@@ -505,7 +505,7 @@
#0])
(case (value@ #right root)
(^multi (#.Some right)
- {(value@ #color right) #Black})
+ [(value@ #color right) #Black])
[(#.Some (without_right root_key root_val (value@ #left root) side_outcome))
#0]
diff --git a/stdlib/source/library/lux/data/text/regex.lux b/stdlib/source/library/lux/data/text/regex.lux
index 0be5f7ebd..94fd16694 100644
--- a/stdlib/source/library/lux/data/text/regex.lux
+++ b/stdlib/source/library/lux/data/text/regex.lux
@@ -429,7 +429,7 @@
branches (<>.many <code>.any)])
(with_identifiers [g!temp]
(in (list& (` (^multi (~ g!temp)
- {((~! <text>.result) (..regex (~ (code.text pattern))) (~ g!temp))
- (#try.Success (~ (maybe.else g!temp bindings)))}))
+ [((~! <text>.result) (..regex (~ (code.text pattern))) (~ g!temp))
+ (#try.Success (~ (maybe.else g!temp bindings)))]))
body
branches))))
diff --git a/stdlib/source/library/lux/debug.lux b/stdlib/source/library/lux/debug.lux
index e8fcb8348..8ce5e58e7 100644
--- a/stdlib/source/library/lux/debug.lux
+++ b/stdlib/source/library/lux/debug.lux
@@ -159,12 +159,10 @@
(let [value (:as (array.Array java/lang/Object) value)]
(case (array.read! 0 value)
(^multi (#.Some tag)
- {(ffi.check java/lang/Integer tag)
- (#.Some tag)}
- {[(array.read! 1 value)
- (array.read! 2 value)]
- [last?
- (#.Some choice)]})
+ [(ffi.check java/lang/Integer tag)
+ (#.Some tag)]
+ [[(array.read! 1 value) (array.read! 2 value)]
+ [last? (#.Some choice)]])
(let [last? (case last?
(#.Some _) #1
#.None #0)]
@@ -549,8 +547,8 @@
(<code>.Parser Target)
(<>.either (<>.and <code>.local_identifier
(\ <>.monad in #.None))
- (<code>.record (<>.and <code>.local_identifier
- (\ <>.monad each (|>> #.Some) <code>.any)))))
+ (<code>.tuple (<>.and <code>.local_identifier
+ (\ <>.monad each (|>> #.Some) <code>.any)))))
(exception: .public (unknown_local_binding [name Text])
(exception.report
diff --git a/stdlib/source/library/lux/ffi.jvm.lux b/stdlib/source/library/lux/ffi.jvm.lux
index 8b7ba8911..be7fbe0d3 100644
--- a/stdlib/source/library/lux/ffi.jvm.lux
+++ b/stdlib/source/library/lux/ffi.jvm.lux
@@ -1265,12 +1265,12 @@
(syntax: .public (!!! [expr <code>.any])
(with_identifiers [g!value]
- (in (list (` ({(#.Some (~ g!value))
+ (in (list (` (.case (~ expr)
+ (#.Some (~ g!value))
(~ g!value)
#.None
- ("jvm object null")}
- (~ expr)))))))
+ ("jvm object null")))))))
(syntax: .public (check [class (..type^ (list))
unchecked (<>.maybe <code>.any)])
diff --git a/stdlib/source/library/lux/ffi.old.lux b/stdlib/source/library/lux/ffi.old.lux
index f62581e68..f84cc2d4a 100644
--- a/stdlib/source/library/lux/ffi.old.lux
+++ b/stdlib/source/library/lux/ffi.old.lux
@@ -300,11 +300,13 @@
Code)
(case [name+params mode in_array?]
(^multi [[prim #.End] #ManualPrM #0]
- {(manual_primitive_type prim) (#.Some output)})
+ [(manual_primitive_type prim)
+ (#.Some output)])
output
(^multi [[prim #.End] #AutoPrM #0]
- {(auto_primitive_type prim) (#.Some output)})
+ [(auto_primitive_type prim)
+ (#.Some output)])
output
[[name params] _ _]
@@ -1250,12 +1252,12 @@
(syntax: .public (!!! [expr <code>.any])
(with_identifiers [g!value]
- (in (list (` ({(#.Some (~ g!value))
+ (in (list (` (.case (~ expr)
+ (#.Some (~ g!value))
(~ g!value)
#.None
- ("jvm object null")}
- (~ expr)))))))
+ ("jvm object null")))))))
(syntax: .public (check [class (..generic_type^ (list))
unchecked (<>.maybe <code>.any)])
diff --git a/stdlib/source/library/lux/macro/syntax.lux b/stdlib/source/library/lux/macro/syntax.lux
index a3562d51c..efdb15f1f 100644
--- a/stdlib/source/library/lux/macro/syntax.lux
+++ b/stdlib/source/library/lux/macro/syntax.lux
@@ -79,18 +79,18 @@
this_module meta.current_module_name
.let [g!state (code.identifier ["" "*lux*"])
error_msg (code.text (macro.wrong_syntax_error [this_module name]))]]
- (in (list (` (macro: (~ export_policy) ((~ (code.identifier ["" name])) (~ g!tokens) (~ g!state))
- ({(#.Right (~ g!body))
+ (in (list (` (.macro: (~ export_policy) ((~ (code.identifier ["" name])) (~ g!tokens) (~ g!state))
+ (.case ((~! </>.result)
+ (: ((~! </>.Parser) (Meta (List Code)))
+ ((~! do) (~! <>.monad)
+ [(~+ (..un_paired vars+parsers))]
+ ((~' in) (~ body))))
+ (~ g!tokens))
+ (#try.Success (~ g!body))
((~ g!body) (~ g!state))
- (#.Left (~ g!error))
- (#.Left ((~! text.interposed) (~! text.new_line) (list (~ error_msg) (~ g!error))))}
- ((~! </>.result)
- (: ((~! </>.Parser) (Meta (List Code)))
- ((~! do) (~! <>.monad)
- [(~+ (..un_paired vars+parsers))]
- ((~' in) (~ body))))
- (~ g!tokens)))))))))
+ (#try.Failure (~ g!error))
+ (#try.Failure ((~! text.interposed) (~! text.new_line) (list (~ error_msg) (~ g!error)))))))))))
(#try.Failure error)
(meta.failure (macro.wrong_syntax_error (name_of ..syntax:)))))
diff --git a/stdlib/source/library/lux/math/number.lux b/stdlib/source/library/lux/math/number.lux
index da7aa73fd..2f0338817 100644
--- a/stdlib/source/library/lux/math/number.lux
+++ b/stdlib/source/library/lux/math/number.lux
@@ -41,15 +41,18 @@
(#try.Success [state (list [meta (#.Nat value)])])
(^multi (#try.Failure _)
- {(\ <int> decoded repr) (#try.Success value)})
+ [(\ <int> decoded repr)
+ (#try.Success value)])
(#try.Success [state (list [meta (#.Int value)])])
(^multi (#try.Failure _)
- {(\ <rev> decoded repr) (#try.Success value)})
+ [(\ <rev> decoded repr)
+ (#try.Success value)])
(#try.Success [state (list [meta (#.Rev value)])])
(^multi (#try.Failure _)
- {(\ <frac> decoded repr) (#try.Success value)})
+ [(\ <frac> decoded repr)
+ (#try.Success value)])
(#try.Success [state (list [meta (#.Frac value)])])
_
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/common.lux
index 4b9ef22e4..d240e786b 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/common.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/common.lux
@@ -34,7 +34,7 @@
(type: .public Bundle
(Dict Text Proc))
-(syntax: (Vector [{size s.nat}
+(syntax: (Vector [size <code>.nat
elemT <code>.any])
(in (list (` [(~+ (list.repeated size elemT))]))))
diff --git a/stdlib/source/library/lux/tool/interpreter.lux b/stdlib/source/library/lux/tool/interpreter.lux
index 8a12cd2db..79c8073f3 100644
--- a/stdlib/source/library/lux/tool/interpreter.lux
+++ b/stdlib/source/library/lux/tool/interpreter.lux
@@ -130,10 +130,11 @@
(function (_ state)
(case (<| (phase.result' state)
(:sharing [anchor expression directive]
- {(State+ anchor expression directive)
- state}
- {<Interpretation>
- (interpret_directive code)}))
+ (State+ anchor expression directive)
+ state
+
+ <Interpretation>
+ (interpret_directive code)))
(#try.Success [state' output])
(#try.Success [state' output])
@@ -141,10 +142,11 @@
(if (ex.match? total.not_a_directive error)
(<| (phase.result' state)
(:sharing [anchor expression directive]
- {(State+ anchor expression directive)
- state}
- {<Interpretation>
- (interpret_expression code)}))
+ (State+ anchor expression directive)
+ state
+
+ <Interpretation>
+ (interpret_expression code)))
(#try.Failure error)))))
)
@@ -176,17 +178,19 @@
[source' input] (syntax.parse ..module syntax.no_aliases (text.size _code) (value@ #source context))
[state' representation] (let [... TODO: Simplify ASAP
state (:sharing [anchor expression directive]
- {<Context>
- context}
- {(State+ anchor expression directive)
- (value@ #state context)})]
+ <Context>
+ context
+
+ (State+ anchor expression directive)
+ (value@ #state context))]
(<| (phase.result' state)
... TODO: Simplify ASAP
(:sharing [anchor expression directive]
- {<Context>
- context}
- {(Operation anchor expression directive Text)
- (execute (value@ #configuration context) input)})))]
+ <Context>
+ context
+
+ (Operation anchor expression directive Text)
+ (execute (value@ #configuration context) input))))]
(in [(|> context
(with@ #state state')
(with@ #source source'))