aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/specification/compositor/generation/common.lux
diff options
context:
space:
mode:
authorEduardo Julian2022-10-19 19:34:33 -0400
committerEduardo Julian2022-10-19 19:34:33 -0400
commit820ffc0a87d7960e62508fc451d9df7a94a6afa7 (patch)
tree33ff1ac227942820f92b43c0a8b872d4e080f974 /stdlib/source/specification/compositor/generation/common.lux
parentd9a1d70ec04fd5796276aeb46038654ade4484f9 (diff)
Migrating default extensions to the new format [Part 2]
Diffstat (limited to 'stdlib/source/specification/compositor/generation/common.lux')
-rw-r--r--stdlib/source/specification/compositor/generation/common.lux144
1 files changed, 67 insertions, 77 deletions
diff --git a/stdlib/source/specification/compositor/generation/common.lux b/stdlib/source/specification/compositor/generation/common.lux
index b0f1c2390..099e556e1 100644
--- a/stdlib/source/specification/compositor/generation/common.lux
+++ b/stdlib/source/specification/compositor/generation/common.lux
@@ -43,8 +43,8 @@
subject r.i64]
(with_expansions [<binary> (with_template [<extension> <reference> <param_expr>]
[(_.test <extension>
- (|> {synthesis.#Extension <extension> (list (synthesis.i64 param)
- (synthesis.i64 subject))}
+ (|> {synthesis.#Extension (symbol <extension>) (list (synthesis.i64 param)
+ (synthesis.i64 subject))}
(run (..safe <extension>))
(pipe.when
{try.#Success valueT}
@@ -54,10 +54,10 @@
false)
(let [param <param_expr>])))]
- ["lux i64 and" i64.and param]
- ["lux i64 or" i64.or param]
- ["lux i64 xor" i64.xor param]
- ["lux i64 left-shift" i64.left_shifted (n.% 64 param)]
+ [.i64_and# i64.and param]
+ [.i64_or# i64.or param]
+ [.i64_xor# i64.xor param]
+ [.i64_left# i64.left_shifted (n.% 64 param)]
["lux i64 logical-right-shift" i64.logic_right_shifted (n.% 64 param)]
)]
(all _.and
@@ -69,9 +69,8 @@
(run (..safe "lux i64 arithmetic-right-shift"))
(pipe.when
{try.#Success valueT}
- ("lux i64 ="
- (i64.arithmetic_right_shifted param subject)
- (as I64 valueT))
+ (.i64_=# (i64.arithmetic_right_shifted param subject)
+ (as I64 valueT))
{try.#Failure _}
false)
@@ -81,12 +80,12 @@
(def (i64 run)
(-> Runner Test)
(do r.monad
- [param (|> r.i64 (r.only (|>> ("lux i64 =" 0) not)))
+ [param (|> r.i64 (r.only (|>> (.i64_=# 0) not)))
subject r.i64]
(`` (all _.and
(,, (with_template [<extension> <type> <prepare> <comp> <subject_expr>]
[(_.test <extension>
- (|> {synthesis.#Extension <extension> (list (synthesis.i64 subject))}
+ (|> {synthesis.#Extension (symbol <extension>) (list (synthesis.i64 subject))}
(run (..safe <extension>))
(pipe.when
{try.#Success valueT}
@@ -96,16 +95,16 @@
false)
(let [subject <subject_expr>])))]
- ["lux i64 f64" Frac i.frac f.= subject]
- ["lux i64 char" Text (|>> (as Nat) text.from_code) text#= (|> subject
- (as Nat)
- (n.% (i64.left_shifted 8 1))
- (as Int))]
+ [.int_f64# Frac i.frac f.= subject]
+ [.int_char# Text (|>> (as Nat) text.from_code) text#= (|> subject
+ (as Nat)
+ (n.% (i64.left_shifted 8 1))
+ (as Int))]
))
(,, (with_template [<extension> <reference> <outputT> <comp>]
[(_.test <extension>
- (|> {synthesis.#Extension <extension> (list (synthesis.i64 param)
- (synthesis.i64 subject))}
+ (|> {synthesis.#Extension (symbol <extension>) (list (synthesis.i64 param)
+ (synthesis.i64 subject))}
(run (..safe <extension>))
(pipe.when
{try.#Success valueT}
@@ -114,13 +113,14 @@
{try.#Failure _}
false)))]
- ["lux i64 +" i.+ Int i.=]
- ["lux i64 -" i.- Int i.=]
- ["lux i64 *" i.* Int i.=]
- ["lux i64 /" i./ Int i.=]
- ["lux i64 %" i.% Int i.=]
- ["lux i64 =" i.= Bit bit#=]
- ["lux i64 <" i.< Bit bit#=]
+ [.i64_+# i.+ Int i.=]
+ [.i64_-# i.- Int i.=]
+ [.i64_=# i.= Bit bit#=]
+
+ [.int_<# i.< Bit bit#=]
+ [.int_*# i.* Int i.=]
+ [.int_/# i./ Int i.=]
+ [.int_%# i.% Int i.=]
))
))))
@@ -136,21 +136,21 @@
(`` (all _.and
(,, (with_template [<extension> <reference> <comp>]
[(_.test <extension>
- (|> {synthesis.#Extension <extension> (list (synthesis.f64 param)
- (synthesis.f64 subject))}
+ (|> {synthesis.#Extension (symbol <extension>) (list (synthesis.f64 param)
+ (synthesis.f64 subject))}
(run (..safe <extension>))
(//when.verify (<reference> param subject))))]
- ["lux f64 +" f.+ f.=]
- ["lux f64 -" f.- f.=]
- ["lux f64 *" f.* f.=]
- ["lux f64 /" f./ f.=]
- ["lux f64 %" f.% f.=]
+ [.f64_+# f.+ f.=]
+ [.f64_-# f.- f.=]
+ [.f64_*# f.* f.=]
+ [.f64_/# f./ f.=]
+ [.f64_%# f.% f.=]
))
(,, (with_template [<extension> <text>]
[(_.test <extension>
- (|> {synthesis.#Extension <extension> (list (synthesis.f64 param)
- (synthesis.f64 subject))}
+ (|> {synthesis.#Extension (symbol <extension>) (list (synthesis.f64 param)
+ (synthesis.f64 subject))}
(run (..safe <extension>))
(pipe.when
{try.#Success valueV}
@@ -160,24 +160,14 @@
_
false)))]
- ["lux f64 =" f.=]
- ["lux f64 <" f.<]
+ [.f64_=# f.=]
+ [.f64_<# f.<]
))
- (,, (with_template [<extension> <reference>]
- [(_.test <extension>
- (|> {synthesis.#Extension <extension> (list)}
- (run (..safe <extension>))
- (//when.verify <reference>)))]
-
- ["lux f64 min" ("lux f64 min")]
- ["lux f64 max" ("lux f64 max")]
- ["lux f64 smallest" ("lux f64 smallest")]
- ))
- (_.test "'lux f64 i64 && 'lux i64 f64'"
- (|> (run (..safe "lux f64 i64")
+ (_.test ".f64_int# && .int_f64#"
+ (|> (run (..safe .f64_int#)
(|> subject synthesis.f64
- (list) {synthesis.#Extension "lux f64 i64"}
- (list) {synthesis.#Extension "lux i64 f64"}))
+ (list) {synthesis.#Extension (symbol .f64_int#)}
+ (list) {synthesis.#Extension (symbol .int_f64#)}))
(//when.verify subject)))
))))
@@ -193,23 +183,23 @@
.let [sample_lowerS (synthesis.text sample_lower)
sample_upperS (synthesis.text sample_upper)
sample_alphaS (synthesis.text sample_alpha)
- concatenatedS {synthesis.#Extension "lux text concat" (list sample_lowerS sample_upperS)}
+ concatenatedS {synthesis.#Extension (symbol .text_composite#) (list sample_lowerS sample_upperS)}
pre_rep_once (format sample_lower sample_upper)
post_rep_once (format sample_lower sample_alpha)
pre_rep_all (|> sample_lower (list.repeated sample_size) (text.interposed sample_upper))
post_rep_all (|> sample_lower (list.repeated sample_size) (text.interposed sample_alpha))]]
(all _.and
(_.test "Can compare texts for equality."
- (and (|> {synthesis.#Extension "lux text =" (list sample_lowerS sample_lowerS)}
- (run (..safe "lux text ="))
+ (and (|> {synthesis.#Extension (symbol .text_=#) (list sample_lowerS sample_lowerS)}
+ (run (..safe .text_=#))
(pipe.when
{try.#Success valueV}
(as Bit valueV)
_
false))
- (|> {synthesis.#Extension "lux text =" (list sample_upperS sample_lowerS)}
- (run (..safe "lux text ="))
+ (|> {synthesis.#Extension (symbol .text_=#) (list sample_upperS sample_lowerS)}
+ (run (..safe .text_=#))
(pipe.when
{try.#Success valueV}
(not (as Bit valueV))
@@ -217,8 +207,8 @@
_
false))))
(_.test "Can compare texts for order."
- (|> {synthesis.#Extension "lux text <" (list sample_lowerS sample_upperS)}
- (run (..safe "lux text <"))
+ (|> {synthesis.#Extension (symbol .text_<#) (list sample_lowerS sample_upperS)}
+ (run (..safe .text_<#))
(pipe.when
{try.#Success valueV}
(as Bit valueV)
@@ -226,8 +216,8 @@
{try.#Failure _}
false)))
(_.test "Can get length of text."
- (|> {synthesis.#Extension "lux text size" (list sample_lowerS)}
- (run (..safe "lux text size"))
+ (|> {synthesis.#Extension (symbol .text_size#) (list sample_lowerS)}
+ (run (..safe .text_size#))
(pipe.when
{try.#Success valueV}
(n.= sample_size (as Nat valueV))
@@ -235,8 +225,8 @@
_
false)))
(_.test "Can concatenate text."
- (|> {synthesis.#Extension "lux text size" (list concatenatedS)}
- (run (..safe "lux text size"))
+ (|> {synthesis.#Extension (symbol .text_size#) (list concatenatedS)}
+ (run (..safe .text_size#))
(pipe.when
{try.#Success valueV}
(n.= (n.* 2 sample_size) (as Nat valueV))
@@ -244,10 +234,10 @@
_
false)))
(_.test "Can find index of sub-text."
- (and (|> {synthesis.#Extension "lux text index"
+ (and (|> {synthesis.#Extension (symbol .text_index#)
(list concatenatedS sample_lowerS
(synthesis.i64 +0))}
- (run (..safe "lux text index"))
+ (run (..safe .text_index#))
(pipe.when
(^.multi {try.#Success valueV}
[(as (Maybe Nat) valueV)
@@ -256,10 +246,10 @@
_
false))
- (|> {synthesis.#Extension "lux text index"
+ (|> {synthesis.#Extension (symbol .text_index#)
(list concatenatedS sample_upperS
(synthesis.i64 +0))}
- (run (..safe "lux text index"))
+ (run (..safe .text_index#))
(pipe.when
(^.multi {try.#Success valueV}
[(as (Maybe Nat) valueV)
@@ -270,11 +260,11 @@
false))))
(let [test_clip (is (-> (I64 Any) (I64 Any) Text Bit)
(function (_ offset length expected)
- (|> {synthesis.#Extension "lux text clip"
+ (|> {synthesis.#Extension (symbol .text_clip#)
(list concatenatedS
(synthesis.i64 offset)
(synthesis.i64 length))}
- (run (..safe "lux text clip"))
+ (run (..safe .text_clip#))
(pipe.when
(^.multi {try.#Success valueV}
[(as (Maybe Text) valueV)
@@ -287,15 +277,15 @@
(and (test_clip 0 sample_size sample_lower)
(test_clip sample_size sample_size sample_upper))))
(_.test "Can extract individual characters from text."
- (|> {synthesis.#Extension "lux text char"
+ (|> {synthesis.#Extension (symbol .text_char#)
(list sample_lowerS
(synthesis.i64 char_idx))}
- (run (..safe "lux text char"))
+ (run (..safe .text_char#))
(pipe.when
(^.multi {try.#Success valueV}
[(as (Maybe Int) valueV)
{.#Some valueV}])
- (text.contains? ("lux i64 char" valueV)
+ (text.contains? (.int_char# valueV)
sample_lower)
_
@@ -308,9 +298,9 @@
[message (r.alphabetic 5)]
(all _.and
(_.test "Can log messages."
- (|> {synthesis.#Extension "lux io log"
+ (|> {synthesis.#Extension .log#
(list (synthesis.text (format "LOG: " message)))}
- (run (..safe "lux io log"))
+ (run (..safe .log#))
(pipe.when
{try.#Success valueV}
true
@@ -318,13 +308,13 @@
{try.#Failure _}
false)))
(_.test "Can throw runtime errors."
- (and (|> {synthesis.#Extension "lux try"
+ (and (|> {synthesis.#Extension .try#
(list (synthesis.function/abstraction
[synthesis.#environment (list)
synthesis.#arity 1
- synthesis.#body {synthesis.#Extension "lux io error"
+ synthesis.#body {synthesis.#Extension (symbol .error#)
(list (synthesis.text message))}]))}
- (run (..safe "lux try"))
+ (run (..safe .try#))
(pipe.when
(^.multi {try.#Success valueV}
[(as (Try Text) valueV)
@@ -333,12 +323,12 @@
_
false))
- (|> {synthesis.#Extension "lux try"
+ (|> {synthesis.#Extension .try#
(list (synthesis.function/abstraction
[synthesis.#environment (list)
synthesis.#arity 1
synthesis.#body (synthesis.text message)]))}
- (run (..safe "lux try"))
+ (run (..safe .try#))
(pipe.when
(^.multi {try.#Success valueV}
[(as (Try Text) valueV)