aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/lux/data
diff options
context:
space:
mode:
Diffstat (limited to '')
-rw-r--r--stdlib/source/lux/data/collection/set/multi.lux2
-rw-r--r--stdlib/source/lux/data/collection/set/ordered.lux2
-rw-r--r--stdlib/source/lux/data/collection/tree/finger.lux15
-rw-r--r--stdlib/source/lux/data/color.lux2
-rw-r--r--stdlib/source/lux/data/format/css.lux6
-rw-r--r--stdlib/source/lux/data/format/css/property.lux2
-rw-r--r--stdlib/source/lux/data/format/css/query.lux6
-rw-r--r--stdlib/source/lux/data/format/css/selector.lux14
-rw-r--r--stdlib/source/lux/data/format/css/style.lux4
-rw-r--r--stdlib/source/lux/data/format/css/value.lux14
-rw-r--r--stdlib/source/lux/data/format/html.lux8
-rw-r--r--stdlib/source/lux/data/format/markdown.lux6
-rw-r--r--stdlib/source/lux/data/format/tar.lux14
-rw-r--r--stdlib/source/lux/data/text/buffer.lux4
-rw-r--r--stdlib/source/lux/data/text/encoding.lux2
-rw-r--r--stdlib/source/lux/data/text/unicode.lux345
16 files changed, 203 insertions, 243 deletions
diff --git a/stdlib/source/lux/data/collection/set/multi.lux b/stdlib/source/lux/data/collection/set/multi.lux
index 4f3f02276..9cfd9e4b1 100644
--- a/stdlib/source/lux/data/collection/set/multi.lux
+++ b/stdlib/source/lux/data/collection/set/multi.lux
@@ -17,8 +17,6 @@
["n" nat]]]]])
(abstract: #export (Set a)
- {}
-
(Dictionary a Nat)
(def: #export new
diff --git a/stdlib/source/lux/data/collection/set/ordered.lux b/stdlib/source/lux/data/collection/set/ordered.lux
index 4f814c1ea..8cafd922e 100644
--- a/stdlib/source/lux/data/collection/set/ordered.lux
+++ b/stdlib/source/lux/data/collection/set/ordered.lux
@@ -12,8 +12,6 @@
abstract]])
(abstract: #export (Set a)
- {}
-
(/.Dictionary a a)
(def: #export new
diff --git a/stdlib/source/lux/data/collection/tree/finger.lux b/stdlib/source/lux/data/collection/tree/finger.lux
index 03c23702c..3a6e52948 100644
--- a/stdlib/source/lux/data/collection/tree/finger.lux
+++ b/stdlib/source/lux/data/collection/tree/finger.lux
@@ -1,21 +1,22 @@
(.module:
[lux #*
[abstract
- ["m" monoid]
- [predicate (#+ Predicate)]]])
+ [predicate (#+ Predicate)]
+ ["." monoid (#+ Monoid)]]])
(type: #export (Node m a)
(#Leaf m a)
(#Branch m (Node m a) (Node m a)))
(type: #export (Tree m a)
- {#monoid (m.Monoid m)
+ {#monoid (Monoid m)
#node (Node m a)})
(def: #export (tag tree)
(All [m a] (-> (Tree m a) m))
(case (get@ #node tree)
- (^or (#Leaf tag _) (#Branch tag _ _))
+ (^or (#Leaf tag _)
+ (#Branch tag _ _))
tag))
(def: #export (value tree)
@@ -37,16 +38,16 @@
(def: #export (search pred tree)
(All [m a] (-> (-> m Bit) (Tree m a) (Maybe a)))
- (let [tag;compose (get@ [#monoid #m.compose] tree)]
+ (let [tag@compose (get@ [#monoid #monoid.compose] tree)]
(if (pred (tag tree))
- (loop [_tag (get@ [#monoid #m.identity] tree)
+ (loop [_tag (get@ [#monoid #monoid.identity] tree)
_node (get@ #node tree)]
(case _node
(#Leaf _ value)
(#.Some value)
(#Branch _ left right)
- (let [shifted-tag (tag;compose _tag (tag (set@ #node left tree)))]
+ (let [shifted-tag (tag@compose _tag (tag (set@ #node left tree)))]
(if (pred shifted-tag)
(recur _tag left)
(recur shifted-tag right)))))
diff --git a/stdlib/source/lux/data/color.lux b/stdlib/source/lux/data/color.lux
index 11da105cf..36b9fdf6d 100644
--- a/stdlib/source/lux/data/color.lux
+++ b/stdlib/source/lux/data/color.lux
@@ -45,8 +45,6 @@
[Frac Frac Frac])
(abstract: #export Color
- {}
-
RGB
(def: #export (from-rgb [red green blue])
diff --git a/stdlib/source/lux/data/format/css.lux b/stdlib/source/lux/data/format/css.lux
index 2b09140f6..aef22816a 100644
--- a/stdlib/source/lux/data/format/css.lux
+++ b/stdlib/source/lux/data/format/css.lux
@@ -20,12 +20,10 @@
["#." style (#+ Style)]
["#." query (#+ Query)]])
-(abstract: #export Common {} Any)
-(abstract: #export Special {} Any)
+(abstract: #export Common Any)
+(abstract: #export Special Any)
(abstract: #export (CSS brand)
- {}
-
Text
(def: #export css (-> (CSS Any) Text) (|>> :representation))
diff --git a/stdlib/source/lux/data/format/css/property.lux b/stdlib/source/lux/data/format/css/property.lux
index 29e919501..bbfdd1930 100644
--- a/stdlib/source/lux/data/format/css/property.lux
+++ b/stdlib/source/lux/data/format/css/property.lux
@@ -55,8 +55,6 @@
(wrap (list (code.local-identifier identifier))))
(abstract: #export (Property brand)
- {}
-
Text
(def: #export name
diff --git a/stdlib/source/lux/data/format/css/query.lux b/stdlib/source/lux/data/format/css/query.lux
index 31f5bee21..6b1e57554 100644
--- a/stdlib/source/lux/data/format/css/query.lux
+++ b/stdlib/source/lux/data/format/css/query.lux
@@ -24,8 +24,6 @@
(wrap (list (code.local-identifier identifier))))
(abstract: #export Media
- {}
-
Text
(def: #export media
@@ -44,8 +42,6 @@
))
(abstract: #export Feature
- {}
-
Text
(def: #export feature
@@ -106,8 +102,6 @@
)
(abstract: #export Query
- {}
-
Text
(def: #export query
diff --git a/stdlib/source/lux/data/format/css/selector.lux b/stdlib/source/lux/data/format/css/selector.lux
index dd99a98c4..1c0f4b566 100644
--- a/stdlib/source/lux/data/format/css/selector.lux
+++ b/stdlib/source/lux/data/format/css/selector.lux
@@ -18,23 +18,21 @@
(type: #export Class Label)
(type: #export Attribute Label)
-(abstract: #export (Generic brand) {} Any)
+(abstract: #export (Generic brand) Any)
(template [<generic> <brand>]
- [(abstract: <brand> {} Any)
+ [(abstract: <brand> Any)
(type: #export <generic> (Generic <brand>))]
[Can-Chain Can-Chain']
[Cannot-Chain Cannot-Chain']
)
-(abstract: #export Unique {} Any)
-(abstract: #export Specific {} Any)
-(abstract: #export Composite {} Any)
+(abstract: #export Unique Any)
+(abstract: #export Specific Any)
+(abstract: #export Composite Any)
(abstract: #export (Selector kind)
- {}
-
Text
(def: #export selector
@@ -164,8 +162,6 @@
:abstraction))
(abstract: #export Index
- {}
-
Text
(def: #export index
diff --git a/stdlib/source/lux/data/format/css/style.lux b/stdlib/source/lux/data/format/css/style.lux
index 5264fb0f9..fbcab6700 100644
--- a/stdlib/source/lux/data/format/css/style.lux
+++ b/stdlib/source/lux/data/format/css/style.lux
@@ -10,10 +10,10 @@
["#." property (#+ Property)]])
(abstract: #export Style
- {#.doc "The style associated with a CSS selector."}
-
Text
+ {#.doc "The style associated with a CSS selector."}
+
(def: #export empty Style (:abstraction ""))
(def: #export separator " ")
diff --git a/stdlib/source/lux/data/format/css/value.lux b/stdlib/source/lux/data/format/css/value.lux
index 4b3f3b1ba..d6aee7813 100644
--- a/stdlib/source/lux/data/format/css/value.lux
+++ b/stdlib/source/lux/data/format/css/value.lux
@@ -32,8 +32,6 @@
(template: (enumeration: <abstraction> <representation> <out> <sample>+ <definition>+)
(abstract: #export <abstraction>
- {}
-
<representation>
(def: #export <out>
@@ -63,8 +61,6 @@
(|> raw (text.split 1) maybe.assume product.right))))
(abstract: #export (Value brand)
- {}
-
Text
(def: #export value
@@ -80,7 +76,7 @@
)
(template [<brand> <alias>+ <value>+]
- [(abstract: #export <brand> {} Any)
+ [(abstract: #export <brand> Any)
(`` (template [<name> <value>]
[(def: #export <name>
@@ -893,8 +889,6 @@
(%.nat vertical))))
(abstract: #export Stop
- {}
-
Text
(def: #export stop
@@ -915,8 +909,6 @@
(:representation Value end))))
(abstract: #export Hint
- {}
-
Text
(def: #export hint
@@ -936,8 +928,6 @@
[a (List a)])
(abstract: #export Angle
- {}
-
Text
(def: #export angle
@@ -977,8 +967,6 @@
)
(abstract: #export Percentage
- {}
-
Text
(def: #export percentage
diff --git a/stdlib/source/lux/data/format/html.lux b/stdlib/source/lux/data/format/html.lux
index 92d1b22e4..a5fbce4d7 100644
--- a/stdlib/source/lux/data/format/html.lux
+++ b/stdlib/source/lux/data/format/html.lux
@@ -76,12 +76,10 @@
(text.enclose ["</" ">"]))
(abstract: #export (HTML brand)
- {}
-
Text
(template [<name> <brand>]
- [(abstract: #export <brand> {} Any)
+ [(abstract: #export <brand> Any)
(type: #export <name> (HTML <brand>))]
[Meta Meta']
@@ -99,11 +97,11 @@
)
(template [<super> <super-raw> <sub>+]
- [(abstract: #export (<super-raw> brand) {} Any)
+ [(abstract: #export (<super-raw> brand) Any)
(type: #export <super> (HTML (<super-raw> Any)))
(`` (template [<sub> <sub-raw>]
- [(abstract: #export <sub-raw> {} Any)
+ [(abstract: #export <sub-raw> Any)
(type: #export <sub> (HTML (<super-raw> <sub-raw>)))]
(~~ (template.splice <sub>+))))]
diff --git a/stdlib/source/lux/data/format/markdown.lux b/stdlib/source/lux/data/format/markdown.lux
index fe20f30b2..bb9a86b46 100644
--- a/stdlib/source/lux/data/format/markdown.lux
+++ b/stdlib/source/lux/data/format/markdown.lux
@@ -30,12 +30,10 @@
(text.replace-all "." "\.")
(text.replace-all "!" "\!")))
-(abstract: #export Span {} Any)
-(abstract: #export Block {} Any)
+(abstract: #export Span Any)
+(abstract: #export Block Any)
(abstract: #export (Markdown brand)
- {}
-
Text
(def: #export empty
diff --git a/stdlib/source/lux/data/format/tar.lux b/stdlib/source/lux/data/format/tar.lux
index 544540418..ca5037a65 100644
--- a/stdlib/source/lux/data/format/tar.lux
+++ b/stdlib/source/lux/data/format/tar.lux
@@ -65,8 +65,6 @@
["Maximum" (%.nat (dec <limit>))]))
(abstract: #export <type>
- {}
-
Nat
(def: #export (<in> value)
@@ -152,8 +150,6 @@
(..big value)))))
(abstract: Checksum
- {}
-
Text
(def: from-checksum
@@ -245,8 +241,6 @@
(template [<type> <representation> <size> <exception> <in> <out> <writer> <parser> <none>]
[(abstract: #export <type>
- {}
-
<representation>
(exception: #export (<exception> {value Text})
@@ -302,8 +296,6 @@
(def: magic-size Size 7)
(abstract: Magic
- {}
-
Text
(def: ustar (:abstraction "ustar "))
@@ -390,8 +382,6 @@
(..small-number ..device-size)))
(abstract: Link-Flag
- {}
-
Char
(def: link-flag
@@ -440,8 +430,6 @@
)
(abstract: #export Mode
- {}
-
Nat
(def: #export mode
@@ -530,8 +518,6 @@
(list@fold n.* 1)))
(abstract: #export Content
- {}
-
[Big Binary]
(def: #export (content content)
diff --git a/stdlib/source/lux/data/text/buffer.lux b/stdlib/source/lux/data/text/buffer.lux
index e14013a29..c3f35f7f5 100644
--- a/stdlib/source/lux/data/text/buffer.lux
+++ b/stdlib/source/lux/data/text/buffer.lux
@@ -26,13 +26,13 @@
(toString [] String)))}))
(`` (abstract: #export Buffer
- {#.doc "Immutable text buffer for efficient text concatenation."}
-
(for {(~~ (static _.old))
[Nat (-> StringBuilder StringBuilder)]}
## default
(Row Text))
+ {#.doc "Immutable text buffer for efficient text concatenation."}
+
(def: #export empty
Buffer
(:abstraction (for {(~~ (static _.old))
diff --git a/stdlib/source/lux/data/text/encoding.lux b/stdlib/source/lux/data/text/encoding.lux
index ae1e11021..88b04c00c 100644
--- a/stdlib/source/lux/data/text/encoding.lux
+++ b/stdlib/source/lux/data/text/encoding.lux
@@ -14,8 +14,6 @@
## https://docs.oracle.com/javase/8/docs/technotes/guides/intl/encoding.doc.html
(abstract: #export Encoding
- {}
-
Text
(template [<name> <encoding>]
diff --git a/stdlib/source/lux/data/text/unicode.lux b/stdlib/source/lux/data/text/unicode.lux
index 6a4192b4c..8faf56789 100644
--- a/stdlib/source/lux/data/text/unicode.lux
+++ b/stdlib/source/lux/data/text/unicode.lux
@@ -1,13 +1,13 @@
(.module:
[lux #*
[abstract
- ["." interval (#+ Interval)]
- [monoid (#+ Monoid)]]
+ [monoid (#+ Monoid)]
+ ["." interval (#+ Interval)]]
[data
[number (#+ hex)
["n" nat ("#@." interval)]]
[collection
- ["." list]
+ ["." list ("#@." fold functor)]
[tree
["." finger (#+ Tree)]]]]
[type
@@ -15,13 +15,13 @@
[// (#+ Char)])
(abstract: #export Segment
- {}
(Interval Char)
- (def: empty (:abstraction (interval.between n.enum n@top n@bottom)))
-
- (structure: monoid (Monoid Segment)
- (def: identity ..empty)
+ (structure: monoid
+ (Monoid Segment)
+
+ (def: identity
+ (:abstraction (interval.between n.enum n@top n@bottom)))
(def: (compose left right)
(let [left (:representation left)
right (:representation right)]
@@ -189,171 +189,182 @@
[basic-latin/lower-alpha "0061" "007A"]
)
-(type: #export Set (Tree Segment []))
+(abstract: #export Set
+ (Tree Segment [])
-(def: (singleton segment)
- (-> Segment Set)
- {#finger.monoid ..monoid
- #finger.node (#finger.Leaf segment [])})
+ (def: #export (compose left right)
+ (-> Set Set Set)
+ (:abstraction
+ (finger.branch (:representation left)
+ (:representation right))))
-(def: #export (set segments)
- (-> (List Segment) Set)
- (case segments
- (^ (list))
- (..singleton (:: ..monoid identity))
-
- (^ (list singleton))
- (..singleton singleton)
-
- (^ (list left right))
- (..singleton (:: ..monoid compose left right))
-
- _
- (let [[sides extra] (n./% 2 (list.size segments))
- [left+ right+] (list.split (n.+ sides extra) segments)]
- (finger.branch (set left+)
- (set right+)))))
+ (def: (singleton segment)
+ (-> Segment Set)
+ (:abstraction
+ {#finger.monoid ..monoid
+ #finger.node (#finger.Leaf segment [])}))
-(def: half/0
- (List Segment)
- (list 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
- 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
- ))
+ (def: #export (set [head tail])
+ (-> [Segment (List Segment)] Set)
+ (list@fold ..compose (..singleton head) (list@map ..singleton tail)))
-(def: half/1
- (List Segment)
- (list 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
- arabic-presentation-forms-a
- variation-selectors
- combining-half-marks
- cjk-compatibility-forms
- small-form-variants
- arabic-presentation-forms-b
- halfwidth-and-fullwidth-forms
- specials
- linear-b-syllabary
- linear-b-ideograms
- aegean-numbers
- old-italic
- gothic
- ugaritic
- deseret
- shavian
- osmanya
- cypriot-syllabary
- byzantine-musical-symbols
- musical-symbols
- tai-xuan-jing-symbols
- mathematical-alphanumeric-symbols
- cjk-unified-ideographs-extension-b
- cjk-compatibility-ideographs-supplement
- tags
- ))
+ (def: half/0
+ (..set [basic-latin
+ (list 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
+ 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
+ )]))
-(def: #export full
- Set
- (finger.branch (set half/0) (set half/1)))
+ (def: half/1
+ (..set [block-elements
+ (list 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
+ arabic-presentation-forms-a
+ variation-selectors
+ combining-half-marks
+ cjk-compatibility-forms
+ small-form-variants
+ arabic-presentation-forms-b
+ halfwidth-and-fullwidth-forms
+ specials
+ linear-b-syllabary
+ linear-b-ideograms
+ aegean-numbers
+ old-italic
+ gothic
+ ugaritic
+ deseret
+ shavian
+ osmanya
+ cypriot-syllabary
+ byzantine-musical-symbols
+ musical-symbols
+ tai-xuan-jing-symbols
+ mathematical-alphanumeric-symbols
+ cjk-unified-ideographs-extension-b
+ cjk-compatibility-ideographs-supplement
+ tags
+ )]))
+
+ (def: #export full
+ (..compose ..half/0 ..half/1))
+
+ (def: #export (range set)
+ (-> Set [Char Char])
+ (let [tag (finger.tag (:representation set))]
+ [(..start tag)
+ (..end tag)]))
+
+ (def: #export (member? set character)
+ (-> Set Char Bit)
+ (let [[_monoid node] (:representation set)]
+ (loop [node node]
+ (case node
+ (#finger.Leaf segment _)
+ (..within? segment character)
+
+ (#finger.Branch _ left right)
+ (or (recur left)
+ (recur right))))))
+ )
(template [<name> <segments>]
- [(def: #export <name> Set (set <segments>))]
+ [(def: #export <name>
+ (..set <segments>))]
- [ascii (list basic-latin)]
- [ascii/alpha (list basic-latin/upper-alpha basic-latin/lower-alpha)]
- [ascii/alpha-num (list basic-latin/upper-alpha basic-latin/lower-alpha basic-latin/decimal)]
- [ascii/upper-alpha (list basic-latin/upper-alpha)]
- [ascii/lower-alpha (list basic-latin/lower-alpha)]
+ [ascii [basic-latin (list)]]
+ [ascii/alpha [basic-latin/upper-alpha (list basic-latin/lower-alpha)]]
+ [ascii/alpha-num [basic-latin/upper-alpha (list basic-latin/lower-alpha basic-latin/decimal)]]
+ [ascii/upper-alpha [basic-latin/upper-alpha (list)]]
+ [ascii/lower-alpha [basic-latin/lower-alpha (list)]]
)