diff options
Diffstat (limited to 'stdlib/source/test/lux/data')
-rw-r--r-- | stdlib/source/test/lux/data/format/tar.lux | 8 | ||||
-rw-r--r-- | stdlib/source/test/lux/data/text/unicode/block.lux | 211 | ||||
-rw-r--r-- | stdlib/source/test/lux/data/text/unicode/segment.lux | 211 | ||||
-rw-r--r-- | stdlib/source/test/lux/data/text/unicode/set.lux | 42 |
4 files changed, 237 insertions, 235 deletions
diff --git a/stdlib/source/test/lux/data/format/tar.lux b/stdlib/source/test/lux/data/format/tar.lux index 92f5915c7..7f271de05 100644 --- a/stdlib/source/test/lux/data/format/tar.lux +++ b/stdlib/source/test/lux/data/format/tar.lux @@ -17,7 +17,7 @@ ["." encoding] ["." unicode #_ ["#" set] - ["#/." segment]]] + ["#/." block]]] [number ["n" nat] ["i" int]] @@ -40,7 +40,7 @@ (do {! random.monad} [expected (random.ascii/lower-alpha /.path-size) invalid (random.ascii/lower-alpha (inc /.path-size)) - not-ascii (random.text (random.char (unicode.set [unicode/segment.katakana (list)])) + not-ascii (random.text (random.char (unicode.set [unicode/block.katakana (list)])) /.path-size)] (`` ($_ _.and (_.cover [/.path /.from-path] @@ -73,7 +73,7 @@ (do {! random.monad} [expected (random.ascii/lower-alpha /.name-size) invalid (random.ascii/lower-alpha (inc /.name-size)) - not-ascii (random.text (random.char (unicode.set [unicode/segment.katakana (list)])) + not-ascii (random.text (random.char (unicode.set [unicode/block.katakana (list)])) /.name-size)] (`` ($_ _.and (_.cover [/.name /.from-name] @@ -314,7 +314,7 @@ [path (random.ascii/lower-alpha /.path-size) expected (random.ascii/lower-alpha /.name-size) invalid (random.ascii/lower-alpha (inc /.name-size)) - not-ascii (random.text (random.char (unicode.set [unicode/segment.katakana (list)])) + not-ascii (random.text (random.char (unicode.set [unicode/block.katakana (list)])) /.name-size)] (_.for [/.Ownership /.Owner /.ID] ($_ _.and diff --git a/stdlib/source/test/lux/data/text/unicode/block.lux b/stdlib/source/test/lux/data/text/unicode/block.lux new file mode 100644 index 000000000..eb55617ca --- /dev/null +++ b/stdlib/source/test/lux/data/text/unicode/block.lux @@ -0,0 +1,211 @@ +(.module: + [lux #* + ["_" test (#+ Test)] + [abstract + [monad (#+ do)] + {[0 #spec] + [/ + ["$." equivalence] + ["$." hash] + ["$." monoid]]}] + [data + ["." text] + [number (#+ hex) + ["n" nat]] + [collection + ["." set] + ["." list]]] + [macro + ["." template]] + [math + ["." random (#+ Random)]]] + {1 + ["." /]}) + +(def: #export random + (Random /.Block) + (do random.monad + [start random.nat + end random.nat] + (wrap (/.block start end)))) + +(with-expansions [<blocks> (as-is [blocks/0 + [/.basic-latin + /.latin-1-supplement + /.latin-extended-a + /.latin-extended-b + /.ipa-extensions + /.spacing-modifier-letters + /.combining-diacritical-marks + /.greek-and-coptic + /.cyrillic + /.cyrillic-supplementary + /.armenian + /.hebrew + /.arabic + /.syriac + /.thaana + /.devanagari + /.bengali + /.gurmukhi + /.gujarati + /.oriya + /.tamil + /.telugu + /.kannada + /.malayalam + /.sinhala + /.thai + /.lao + /.tibetan + /.myanmar + /.georgian + /.hangul-jamo + /.ethiopic + /.cherokee + /.unified-canadian-aboriginal-syllabics + /.ogham + /.runic + /.tagalog + /.hanunoo + /.buhid + /.tagbanwa + /.khmer + /.mongolian]] + [blocks/1 + [/.limbu + /.tai-le + /.khmer-symbols + /.phonetic-extensions + /.latin-extended-additional + /.greek-extended + /.general-punctuation + /.superscripts-and-subscripts + /.currency-symbols + /.combining-diacritical-marks-for-symbols + /.letterlike-symbols + /.number-forms + /.arrows + /.mathematical-operators + /.miscellaneous-technical + /.control-pictures + /.optical-character-recognition + /.enclosed-alphanumerics + /.box-drawing + /.block-elements + /.geometric-shapes + /.miscellaneous-symbols + /.dingbats + /.miscellaneous-mathematical-symbols-a + /.supplemental-arrows-a + /.braille-patterns + /.supplemental-arrows-b + /.miscellaneous-mathematical-symbols-b + /.supplemental-mathematical-operators + /.miscellaneous-symbols-and-arrows + /.cjk-radicals-supplement + /.kangxi-radicals + /.ideographic-description-characters + /.cjk-symbols-and-punctuation + /.hiragana + /.katakana + /.bopomofo + /.hangul-compatibility-jamo + /.kanbun + /.bopomofo-extended + /.katakana-phonetic-extensions + /.enclosed-cjk-letters-and-months + /.cjk-compatibility + /.cjk-unified-ideographs-extension-a + /.yijing-hexagram-symbols + /.cjk-unified-ideographs + /.yi-syllables + /.yi-radicals + /.hangul-syllables + /.high-surrogates + /.high-private-use-surrogates + /.low-surrogates + /.private-use-area + /.cjk-compatibility-ideographs + /.alphabetic-presentation-forms]] + [blocks/2 + [/.arabic-presentation-forms-a + /.variation-selectors + /.combining-half-marks + /.cjk-compatibility-forms + /.small-form-variants + /.arabic-presentation-forms-b + /.halfwidth-and-fullwidth-forms + /.specials + + ## Specialized blocks + /.basic-latin/decimal + /.basic-latin/upper-alpha + /.basic-latin/lower-alpha]] + ) + <named> (template [<definition> <part>] + [((: (-> Any (List /.Block)) + (function (_ _) + (`` (list (~~ (template.splice <part>)))))) + [])] + + <blocks>)] + (template [<definition> <part>] + [(def: <definition> + Test + (`` (_.cover [(~~ (template.splice <part>))] + (let [all (list.concat (list <named>)) + unique (set.from-list /.hash all)] + (n.= (list.size all) + (set.size unique))))))] + + <blocks> + ) + + (def: #export test + Test + (<| (_.covering /._) + (_.for [/.Block]) + (do {! random.monad} + [#let [top-start (hex "AC00") + top-end (hex "D7AF")] + start (\ ! map (|>> (n.% top-start) inc) random.nat) + end (\ ! map (|>> (n.% top-end) inc) random.nat) + #let [sample (/.block start end) + size (/.size sample)] + inside (\ ! map + (|>> (n.% size) + (n.+ (/.start sample))) + random.nat)] + (`` ($_ _.and + (_.for [/.equivalence] + ($equivalence.spec /.equivalence ..random)) + (_.for [/.hash] + ($hash.spec /.hash ..random)) + (_.for [/.monoid] + ($monoid.spec /.equivalence /.monoid ..random)) + + (_.cover [/.block] + (\ /.equivalence = + (/.block start end) + (/.block end start))) + (_.cover [/.start] + (n.= (n.min start end) + (/.start (/.block start end)))) + (_.cover [/.end] + (n.= (n.max start end) + (/.end (/.block start end)))) + (_.cover [/.size] + (n.= (inc (n.- (n.min start end) + (n.max start end))) + (/.size (/.block start end)))) + (_.cover [/.within?] + (and (/.within? sample inside) + (not (/.within? sample (dec (/.start sample)))) + (not (/.within? sample (inc (/.end sample)))))) + (~~ (template [<definition> <part>] + [<definition>] + + <blocks>)) + ))))) + ) diff --git a/stdlib/source/test/lux/data/text/unicode/segment.lux b/stdlib/source/test/lux/data/text/unicode/segment.lux deleted file mode 100644 index 62a399cd1..000000000 --- a/stdlib/source/test/lux/data/text/unicode/segment.lux +++ /dev/null @@ -1,211 +0,0 @@ -(.module: - [lux #* - ["_" test (#+ Test)] - [abstract - [monad (#+ do)] - {[0 #spec] - [/ - ["$." equivalence] - ["$." hash] - ["$." monoid]]}] - [data - ["." text] - [number (#+ hex) - ["n" nat]] - [collection - ["." set] - ["." list]]] - [macro - ["." template]] - [math - ["." random (#+ Random)]]] - {1 - ["." /]}) - -(def: #export random - (Random /.Segment) - (do random.monad - [start random.nat - end random.nat] - (wrap (/.segment start end)))) - -(with-expansions [<segments> (as-is [segments/0 - [/.basic-latin - /.latin-1-supplement - /.latin-extended-a - /.latin-extended-b - /.ipa-extensions - /.spacing-modifier-letters - /.combining-diacritical-marks - /.greek-and-coptic - /.cyrillic - /.cyrillic-supplementary - /.armenian - /.hebrew - /.arabic - /.syriac - /.thaana - /.devanagari - /.bengali - /.gurmukhi - /.gujarati - /.oriya - /.tamil - /.telugu - /.kannada - /.malayalam - /.sinhala - /.thai - /.lao - /.tibetan - /.myanmar - /.georgian - /.hangul-jamo - /.ethiopic - /.cherokee - /.unified-canadian-aboriginal-syllabics - /.ogham - /.runic - /.tagalog - /.hanunoo - /.buhid - /.tagbanwa - /.khmer - /.mongolian]] - [segments/1 - [/.limbu - /.tai-le - /.khmer-symbols - /.phonetic-extensions - /.latin-extended-additional - /.greek-extended - /.general-punctuation - /.superscripts-and-subscripts - /.currency-symbols - /.combining-diacritical-marks-for-symbols - /.letterlike-symbols - /.number-forms - /.arrows - /.mathematical-operators - /.miscellaneous-technical - /.control-pictures - /.optical-character-recognition - /.enclosed-alphanumerics - /.box-drawing - /.block-elements - /.geometric-shapes - /.miscellaneous-symbols - /.dingbats - /.miscellaneous-mathematical-symbols-a - /.supplemental-arrows-a - /.braille-patterns - /.supplemental-arrows-b - /.miscellaneous-mathematical-symbols-b - /.supplemental-mathematical-operators - /.miscellaneous-symbols-and-arrows - /.cjk-radicals-supplement - /.kangxi-radicals - /.ideographic-description-characters - /.cjk-symbols-and-punctuation - /.hiragana - /.katakana - /.bopomofo - /.hangul-compatibility-jamo - /.kanbun - /.bopomofo-extended - /.katakana-phonetic-extensions - /.enclosed-cjk-letters-and-months - /.cjk-compatibility - /.cjk-unified-ideographs-extension-a - /.yijing-hexagram-symbols - /.cjk-unified-ideographs - /.yi-syllables - /.yi-radicals - /.hangul-syllables - /.high-surrogates - /.high-private-use-surrogates - /.low-surrogates - /.private-use-area - /.cjk-compatibility-ideographs - /.alphabetic-presentation-forms]] - [segments/2 - [/.arabic-presentation-forms-a - /.variation-selectors - /.combining-half-marks - /.cjk-compatibility-forms - /.small-form-variants - /.arabic-presentation-forms-b - /.halfwidth-and-fullwidth-forms - /.specials - - ## Specialized segments - /.basic-latin/decimal - /.basic-latin/upper-alpha - /.basic-latin/lower-alpha]] - ) - <named> (template [<definition> <part>] - [((: (-> Any (List /.Segment)) - (function (_ _) - (`` (list (~~ (template.splice <part>)))))) - [])] - - <segments>)] - (template [<definition> <part>] - [(def: <definition> - Test - (`` (_.cover [(~~ (template.splice <part>))] - (let [all (list.concat (list <named>)) - unique (set.from-list /.hash all)] - (n.= (list.size all) - (set.size unique))))))] - - <segments> - ) - - (def: #export test - Test - (<| (_.covering /._) - (_.for [/.Segment]) - (do {! random.monad} - [#let [top-start (hex "AC00") - top-end (hex "D7AF")] - start (\ ! map (|>> (n.% top-start) inc) random.nat) - end (\ ! map (|>> (n.% top-end) inc) random.nat) - #let [sample (/.segment start end) - size (/.size sample)] - inside (\ ! map - (|>> (n.% size) - (n.+ (/.start sample))) - random.nat)] - (`` ($_ _.and - (_.for [/.equivalence] - ($equivalence.spec /.equivalence ..random)) - (_.for [/.hash] - ($hash.spec /.hash ..random)) - (_.for [/.monoid] - ($monoid.spec /.equivalence /.monoid ..random)) - - (_.cover [/.segment] - (\ /.equivalence = - (/.segment start end) - (/.segment end start))) - (_.cover [/.start] - (n.= (n.min start end) - (/.start (/.segment start end)))) - (_.cover [/.end] - (n.= (n.max start end) - (/.end (/.segment start end)))) - (_.cover [/.size] - (n.= (inc (n.- (n.min start end) - (n.max start end))) - (/.size (/.segment start end)))) - (_.cover [/.within?] - (and (/.within? sample inside) - (not (/.within? sample (dec (/.start sample)))) - (not (/.within? sample (inc (/.end sample)))))) - (~~ (template [<definition> <part>] - [<definition>] - - <segments>)) - ))))) - ) diff --git a/stdlib/source/test/lux/data/text/unicode/set.lux b/stdlib/source/test/lux/data/text/unicode/set.lux index 21c5a90f1..16e29d368 100644 --- a/stdlib/source/test/lux/data/text/unicode/set.lux +++ b/stdlib/source/test/lux/data/text/unicode/set.lux @@ -17,17 +17,17 @@ ["." random (#+ Random)]]] ["." / #_ ["/#" // #_ - ["#." segment]]] + ["#." block]]] {1 ["." / [// - ["." segment]]]}) + ["." block]]]}) (def: #export random (Random /.Set) (do {! random.monad} - [left //segment.random - right //segment.random] + [left //block.random + right //block.random] (wrap (/.set [left (list right)])))) (def: #export test @@ -35,13 +35,13 @@ (<| (_.covering /._) (_.for [/.Set]) (do {! random.monad} - [segment //segment.random + [block //block.random inside (\ ! map - (|>> (n.% (segment.size segment)) - (n.+ (segment.start segment))) + (|>> (n.% (block.size block)) + (n.+ (block.start block))) random.nat) - left //segment.random - right //segment.random + left //block.random + right //block.random #let [equivalence (product.equivalence n.equivalence n.equivalence)]] (`` ($_ _.and @@ -50,21 +50,21 @@ (_.cover [/.range] (let [[start end] (/.range (/.set [left (list right)]))] - (and (n.= (n.min (segment.start left) - (segment.start right)) + (and (n.= (n.min (block.start left) + (block.start right)) start) - (n.= (n.max (segment.end left) - (segment.end right)) + (n.= (n.max (block.end left) + (block.end right)) end)))) (_.cover [/.member?] - (bit\= (segment.within? segment inside) - (/.member? (/.set [segment (list)]) inside))) + (bit\= (block.within? block inside) + (/.member? (/.set [block (list)]) inside))) (_.cover [/.compose] (\ equivalence = - [(n.min (segment.start left) - (segment.start right)) - (n.max (segment.end left) - (segment.end right))] + [(n.min (block.start left) + (block.start right)) + (n.max (block.end left) + (block.end right))] (/.range (/.compose (/.set [left (list)]) (/.set [right (list)]))))) (_.cover [/.set] @@ -86,8 +86,10 @@ [/.ascii/alpha-num] [/.ascii/lower-alpha] [/.ascii/upper-alpha] + [/.character] + [/.non-character] [/.full] )) - //segment.test + //block.test ))))) |