aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/library/lux/data
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib/source/library/lux/data')
-rw-r--r--stdlib/source/library/lux/data/collection/array.lux4
-rw-r--r--stdlib/source/library/lux/data/collection/queue/priority.lux4
-rw-r--r--stdlib/source/library/lux/data/collection/set/multi.lux4
-rw-r--r--stdlib/source/library/lux/data/collection/set/ordered.lux4
-rw-r--r--stdlib/source/library/lux/data/collection/stack.lux4
-rw-r--r--stdlib/source/library/lux/data/collection/tree/finger.lux4
-rw-r--r--stdlib/source/library/lux/data/color.lux192
-rw-r--r--stdlib/source/library/lux/data/color/cmyk.lux42
-rw-r--r--stdlib/source/library/lux/data/color/hsl.lux184
-rw-r--r--stdlib/source/library/lux/data/color/rgb.lux36
-rw-r--r--stdlib/source/library/lux/data/color/terminal.lux16
-rw-r--r--stdlib/source/library/lux/data/format/css.lux8
-rw-r--r--stdlib/source/library/lux/data/format/css/class.lux4
-rw-r--r--stdlib/source/library/lux/data/format/css/id.lux4
-rw-r--r--stdlib/source/library/lux/data/format/css/property.lux4
-rw-r--r--stdlib/source/library/lux/data/format/css/query.lux8
-rw-r--r--stdlib/source/library/lux/data/format/css/selector.lux16
-rw-r--r--stdlib/source/library/lux/data/format/css/style.lux4
-rw-r--r--stdlib/source/library/lux/data/format/css/value.lux18
-rw-r--r--stdlib/source/library/lux/data/format/html.lux10
-rw-r--r--stdlib/source/library/lux/data/format/markdown.lux106
-rw-r--r--stdlib/source/library/lux/data/format/tar.lux16
-rw-r--r--stdlib/source/library/lux/data/text.lux26
-rw-r--r--stdlib/source/library/lux/data/text/buffer.lux4
-rw-r--r--stdlib/source/library/lux/data/text/encoding.lux4
-rw-r--r--stdlib/source/library/lux/data/text/unicode/block.lux4
-rw-r--r--stdlib/source/library/lux/data/text/unicode/set.lux4
27 files changed, 442 insertions, 292 deletions
diff --git a/stdlib/source/library/lux/data/collection/array.lux b/stdlib/source/library/lux/data/collection/array.lux
index 3158b04d6..3e522b255 100644
--- a/stdlib/source/library/lux/data/collection/array.lux
+++ b/stdlib/source/library/lux/data/collection/array.lux
@@ -17,9 +17,9 @@
[variance (.only)]]]]]
["!" \\unsafe])
-(def .public primitive
+(def .public nominal
Text
- !.primitive)
+ !.nominal)
(type .public Array'
!.Array')
diff --git a/stdlib/source/library/lux/data/collection/queue/priority.lux b/stdlib/source/library/lux/data/collection/queue/priority.lux
index 49f6cc0a4..17cf5ee16 100644
--- a/stdlib/source/library/lux/data/collection/queue/priority.lux
+++ b/stdlib/source/library/lux/data/collection/queue/priority.lux
@@ -15,7 +15,7 @@
["n" nat (.use "[1]#[0]" interval)]]]
[meta
[type (.only by_example)
- ["[0]" primitive (.only abstraction representation)]]]]])
+ ["[0]" nominal (.only abstraction representation)]]]]])
(type .public Priority
Nat)
@@ -37,7 +37,7 @@
..builder)
@))
-(primitive.def .public (Queue a)
+(nominal.def .public (Queue a)
(Maybe (Tree :@: Priority a))
(def .public empty
diff --git a/stdlib/source/library/lux/data/collection/set/multi.lux b/stdlib/source/library/lux/data/collection/set/multi.lux
index d7087830b..46c225ab4 100644
--- a/stdlib/source/library/lux/data/collection/set/multi.lux
+++ b/stdlib/source/library/lux/data/collection/set/multi.lux
@@ -15,13 +15,13 @@
[macro
["^" pattern]]
[type
- ["[0]" primitive (.only abstraction representation)]]]]]
+ ["[0]" nominal (.only abstraction representation)]]]]]
["[0]" // (.only)
[//
["[0]" list (.use "[1]#[0]" mix monoid)]
["[0]" dictionary (.only Dictionary)]]])
-(primitive.def .public (Set a)
+(nominal.def .public (Set a)
(Dictionary a Nat)
(def .public empty
diff --git a/stdlib/source/library/lux/data/collection/set/ordered.lux b/stdlib/source/library/lux/data/collection/set/ordered.lux
index 3ff035d4b..fcaa369c7 100644
--- a/stdlib/source/library/lux/data/collection/set/ordered.lux
+++ b/stdlib/source/library/lux/data/collection/set/ordered.lux
@@ -11,9 +11,9 @@
["/" ordered]]]]
[meta
[type
- ["[0]" primitive (.except def)]]]]])
+ ["[0]" nominal (.except def)]]]]])
-(primitive.def .public (Set a)
+(nominal.def .public (Set a)
(/.Dictionary a a)
(def .public empty
diff --git a/stdlib/source/library/lux/data/collection/stack.lux b/stdlib/source/library/lux/data/collection/stack.lux
index b910f3e21..4d1d6e0cb 100644
--- a/stdlib/source/library/lux/data/collection/stack.lux
+++ b/stdlib/source/library/lux/data/collection/stack.lux
@@ -9,9 +9,9 @@
["//" list]]]
[meta
[type
- ["[0]" primitive (.except def)]]]]])
+ ["[0]" nominal (.except def)]]]]])
-(primitive.def .public (Stack a)
+(nominal.def .public (Stack a)
(List a)
(def .public empty
diff --git a/stdlib/source/library/lux/data/collection/tree/finger.lux b/stdlib/source/library/lux/data/collection/tree/finger.lux
index 4e0ed56de..b54a30582 100644
--- a/stdlib/source/library/lux/data/collection/tree/finger.lux
+++ b/stdlib/source/library/lux/data/collection/tree/finger.lux
@@ -11,10 +11,10 @@
["[0]" list (.use "[1]#[0]" monoid)]]]
[meta
[type
- ["[0]" primitive (.only abstraction representation)]]]]])
+ ["[0]" nominal (.only abstraction representation)]]]]])
... https://en.wikipedia.org/wiki/Finger_tree
-(primitive.def .public (Tree @ t v)
+(nominal.def .public (Tree @ t v)
(Record
[#monoid (Monoid t)
#tag t
diff --git a/stdlib/source/library/lux/data/color.lux b/stdlib/source/library/lux/data/color.lux
index d61e01b02..23388a61c 100644
--- a/stdlib/source/library/lux/data/color.lux
+++ b/stdlib/source/library/lux/data/color.lux
@@ -19,9 +19,10 @@
["[0]" i64]]]
[meta
[type
- ["[0]" primitive]]]]]
+ ["[0]" nominal]]]]]
[/
- ["[0]" rgb (.only RGB)]])
+ ["[0]" rgb (.only RGB)]
+ ["[0]" hsl]])
(def top
(-- rgb.limit))
@@ -37,22 +38,19 @@
(-> Frac Nat)
(|>> (f.* rgb_factor) f.int .nat))
-(type .public HSL
- [Frac Frac Frac])
-
(type .public HSB
[Frac Frac Frac])
-(primitive.def .public Color
+(nominal.def .public Color
RGB
(def .public of_rgb
(-> RGB Color)
- (|>> primitive.abstraction))
+ (|>> nominal.abstraction))
(def .public rgb
(-> Color RGB)
- (|>> primitive.representation))
+ (|>> nominal.representation))
(def .public equivalence
(Equivalence Color)
@@ -65,7 +63,7 @@
(with_template [<color> <rgb>]
[(def .public <color>
Color
- (primitive.abstraction <rgb>))]
+ (nominal.abstraction <rgb>))]
[black rgb.black]
[white rgb.white]
@@ -76,14 +74,14 @@
(Monoid Color)
(implementation
(def identity
- (primitive.abstraction
+ (nominal.abstraction
(at <rgb> identity)))
(def (composite left right)
- (primitive.abstraction
+ (nominal.abstraction
(at <rgb> composite
- (primitive.representation left)
- (primitive.representation right))))))]
+ (nominal.representation left)
+ (nominal.representation right))))))]
[addition rgb.addition]
[subtraction rgb.subtraction]
@@ -91,83 +89,11 @@
(def .public complement
(-> Color Color)
- (|>> primitive.representation
+ (|>> nominal.representation
rgb.complement
- primitive.abstraction))
+ nominal.abstraction))
)
-(def .public (hsl color)
- (-> Color HSL)
- (let [[red green blue] (rgb color)
- red (..down (rgb.number red))
- green (..down (rgb.number green))
- blue (..down (rgb.number blue))
- max (all f.max red green blue)
- min (all f.min red green blue)
- luminance (|> (f.+ max min) (f./ +2.0))]
- (if (f.= max min)
- ... Achromatic
- [+0.0
- +0.0
- luminance]
- ... Chromatic
- (let [diff (|> max (f.- min))
- saturation (|> diff
- (f./ (if (f.> +0.5 luminance)
- (|> +2.0 (f.- max) (f.- min))
- (|> max (f.+ min)))))
- hue' (cond (f.= red max)
- (|> green (f.- blue) (f./ diff)
- (f.+ (if (f.< blue green) +6.0 +0.0)))
-
- (f.= green max)
- (|> blue (f.- red) (f./ diff)
- (f.+ +2.0))
-
- ... (f.= blue max)
- (|> red (f.- green) (f./ diff)
- (f.+ +4.0)))]
- [(|> hue' (f./ +6.0))
- saturation
- luminance]))))
-
-(def (hue_rgb p q t)
- (-> Frac Frac Frac Nat)
- (let [t (cond (f.< +0.0 t) (f.+ +1.0 t)
- (f.> +1.0 t) (f.- +1.0 t)
- ... else
- t)
- f2/3 (f./ +3.0 +2.0)]
- (..up (cond (f.< (f./ +6.0 +1.0) t)
- (|> q (f.- p) (f.* +6.0) (f.* t) (f.+ p))
-
- (f.< (f./ +2.0 +1.0) t)
- q
-
- (f.< f2/3 t)
- (|> q (f.- p) (f.* (|> f2/3 (f.- t))) (f.* +6.0) (f.+ p))
-
- ... else
- p))))
-
-(def .public (of_hsl [hue saturation luminance])
- (-> HSL Color)
- (|> (if (f.= +0.0 saturation)
- ... Achromatic
- (let [intensity (..up luminance)]
- (rgb.rgb intensity intensity intensity))
- ... Chromatic
- (let [q (if (f.< +0.5 luminance)
- (|> saturation (f.+ +1.0) (f.* luminance))
- (|> luminance (f.+ saturation) (f.- (f.* saturation luminance))))
- p (|> luminance (f.* +2.0) (f.- q))
- third (|> +1.0 (f./ +3.0))]
- (rgb.rgb (|> hue (f.+ third) (hue_rgb p q))
- (|> hue (hue_rgb p q))
- (|> hue (f.- third) (hue_rgb p q)))))
- try.trusted
- of_rgb))
-
(def .public (hsb color)
(-> Color HSB)
(let [[red green blue] (rgb color)
@@ -260,12 +186,16 @@
(with_template [<op> <name>]
[(def .public (<name> ratio color)
(-> Frac Color Color)
- (let [[hue saturation luminance] (hsl color)]
- (of_hsl [hue
- (|> saturation
- (f.* (|> +1.0 (<op> (..normal ratio))))
- (f.min +1.0))
- luminance])))]
+ (let [color (hsl.of_rgb (rgb color))]
+ (|> (hsl.hsl (hsl.hue color)
+ (|> color
+ hsl.saturation
+ (f.* (|> +1.0 (<op> (..normal ratio))))
+ (f.min +1.0))
+ (hsl.luminance color))
+ try.trusted
+ hsl.rgb
+ of_rgb)))]
[f.+ saturated]
[f.- un_saturated]
@@ -273,22 +203,34 @@
(def .public (gray_scale color)
(-> Color Color)
- (let [[_ _ luminance] (hsl color)]
- (of_hsl [+0.0
- +0.0
- luminance])))
+ (let [color (hsl.of_rgb (rgb color))]
+ (|> (hsl.hsl +0.0
+ +0.0
+ (hsl.luminance color))
+ try.trusted
+ hsl.rgb
+ of_rgb)))
(with_template [<name> <1> <2>]
[(`` (def .public (<name> color)
(-> Color [Color Color Color])
- (let [[hue saturation luminance] (hsl color)]
+ (let [hsl (hsl.of_rgb (rgb color))
+ hue (hsl.hue hsl)
+ saturation (hsl.saturation hsl)
+ luminance (hsl.luminance hsl)]
[color
- (of_hsl [(|> hue (f.+ <1>) ..normal)
- saturation
- luminance])
- (of_hsl [(|> hue (f.+ <2>) ..normal)
- saturation
- luminance])])))]
+ (|> (hsl.hsl (|> hue (f.+ <1>) ..normal)
+ saturation
+ luminance)
+ try.trusted
+ hsl.rgb
+ of_rgb)
+ (|> (hsl.hsl (|> hue (f.+ <2>) ..normal)
+ saturation
+ luminance)
+ try.trusted
+ hsl.rgb
+ of_rgb)])))]
[triad (|> +1.0 (f./ +3.0)) (|> +2.0 (f./ +3.0))]
[clash (|> +1.0 (f./ +4.0)) (|> +3.0 (f./ +4.0))]
@@ -320,27 +262,27 @@
(type .public Palette
(-> Spread Nat Color (List Color)))
-(`` (def .public (analogous spread variations color)
- Palette
- (let [[hue saturation brightness] (hsb color)
- spread (..normal spread)]
- (list#each (function (_ idx)
- (of_hsb [(|> idx ++ .int int.frac (f.* spread) (f.+ hue) ..normal)
- saturation
- brightness]))
- (list.indices variations)))))
-
-(`` (def .public (monochromatic spread variations color)
- Palette
- (let [[hue saturation brightness] (hsb color)
- spread (..normal spread)]
- (|> (list.indices variations)
- (list#each (|>> ++ .int int.frac
- (f.* spread)
- (f.+ brightness)
- ..normal
- [hue saturation]
- of_hsb))))))
+(def .public (analogous spread variations color)
+ Palette
+ (let [[hue saturation brightness] (hsb color)
+ spread (..normal spread)]
+ (list#each (function (_ idx)
+ (of_hsb [(|> idx ++ .int int.frac (f.* spread) (f.+ hue) ..normal)
+ saturation
+ brightness]))
+ (list.indices variations))))
+
+(def .public (monochromatic spread variations color)
+ Palette
+ (let [[hue saturation brightness] (hsb color)
+ spread (..normal spread)]
+ (|> (list.indices variations)
+ (list#each (|>> ++ .int int.frac
+ (f.* spread)
+ (f.+ brightness)
+ ..normal
+ [hue saturation]
+ of_hsb)))))
(type .public Alpha
Rev)
diff --git a/stdlib/source/library/lux/data/color/cmyk.lux b/stdlib/source/library/lux/data/color/cmyk.lux
index 3e22ab333..d519d2cea 100644
--- a/stdlib/source/library/lux/data/color/cmyk.lux
+++ b/stdlib/source/library/lux/data/color/cmyk.lux
@@ -15,19 +15,19 @@
["[0]" int]]]
[meta
[type
- ["[0]" primitive]]]]]
+ ["[0]" nominal]]]]]
[//
["[0]" rgb (.only RGB)]])
(with_expansions [<min> +0.0
<max> +1.0]
- (primitive.def .public Value
+ (nominal.def .public Value
Frac
(with_template [<number> <name>]
[(def .public <name>
Value
- (primitive.abstraction <number>))]
+ (nominal.abstraction <number>))]
[<min> least]
[<max> most]
@@ -36,24 +36,24 @@
(exception.def .public (invalid it)
(Exception Frac)
(exception.report
- (list ["Minimum" (%.frac (primitive.representation ..least))]
- ["Maximum" (%.frac (primitive.representation ..most))]
+ (list ["Minimum" (%.frac (nominal.representation ..least))]
+ ["Maximum" (%.frac (nominal.representation ..most))]
["Value" (%.frac it)])))
(def .public (value it)
(-> Frac
(Try Value))
- (if (or (f.> (primitive.representation ..most)
+ (if (or (f.> (nominal.representation ..most)
it)
- (f.< (primitive.representation ..least)
+ (f.< (nominal.representation ..least)
it))
(exception.except ..invalid [it])
- {try.#Success (primitive.abstraction it)}))
+ {try.#Success (nominal.abstraction it)}))
(def .public number
(-> Value
Frac)
- (|>> primitive.representation))
+ (|>> nominal.representation))
(type .public CMYK
(Record
@@ -66,10 +66,10 @@
(Equivalence CMYK)
(implementation
(def (= [cR mR yR kR] [cS mS yS kS])
- (and (f.= (primitive.representation cR) (primitive.representation cS))
- (f.= (primitive.representation mR) (primitive.representation mS))
- (f.= (primitive.representation yR) (primitive.representation yS))
- (f.= (primitive.representation kR) (primitive.representation kS))))))
+ (and (f.= (nominal.representation cR) (nominal.representation cS))
+ (f.= (nominal.representation mR) (nominal.representation mS))
+ (f.= (nominal.representation yR) (nominal.representation yS))
+ (f.= (nominal.representation kR) (nominal.representation kS))))))
(def top
(-- rgb.limit))
@@ -106,26 +106,26 @@
cyan (|> <max> (f.- red) (f.- key) (f.* f))
magenta (|> <max> (f.- green) (f.- key) (f.* f))
yellow (|> <max> (f.- blue) (f.- key) (f.* f))]
- [#cyan (primitive.abstraction cyan)
- #magenta (primitive.abstraction magenta)
- #yellow (primitive.abstraction yellow)
- #key (primitive.abstraction key)]))
+ [#cyan (nominal.abstraction cyan)
+ #magenta (nominal.abstraction magenta)
+ #yellow (nominal.abstraction yellow)
+ #key (nominal.abstraction key)]))
(def .public (rgb it)
(-> CMYK
RGB)
- (when (primitive.representation (the #key it))
+ (when (nominal.representation (the #key it))
<max>
rgb.black
key
(let [~key (opposite key)
red (f.* ~key
- (opposite (primitive.representation (the #cyan it))))
+ (opposite (nominal.representation (the #cyan it))))
green (f.* ~key
- (opposite (primitive.representation (the #magenta it))))
+ (opposite (nominal.representation (the #magenta it))))
blue (f.* ~key
- (opposite (primitive.representation (the #yellow it))))]
+ (opposite (nominal.representation (the #yellow it))))]
(|> (rgb.rgb (..up red)
(..up green)
(..up blue))
diff --git a/stdlib/source/library/lux/data/color/hsl.lux b/stdlib/source/library/lux/data/color/hsl.lux
new file mode 100644
index 000000000..dd2155f2f
--- /dev/null
+++ b/stdlib/source/library/lux/data/color/hsl.lux
@@ -0,0 +1,184 @@
+(.require
+ [library
+ [lux (.except)
+ [abstract
+ [equivalence (.only Equivalence)]
+ [monad (.only do)]]
+ [control
+ ["[0]" try (.only Try)]
+ ["[0]" exception (.only Exception)]]
+ [data
+ [text
+ ["%" \\format]]]
+ [math
+ [number
+ ["i" int]
+ ["f" frac]]]
+ [meta
+ [type
+ ["[0]" nominal]]]]]
+ [//
+ ["[0]" rgb (.only RGB)]])
+
+(def top
+ (-- rgb.limit))
+
+(def rgb_factor
+ (|> top .int i.frac))
+
+(def down
+ (-> Nat
+ Frac)
+ (|>> .int i.frac (f./ rgb_factor)))
+
+(def up
+ (-> Frac
+ Nat)
+ (|>> (f.* rgb_factor) f.int .nat))
+
+(type .public Value
+ Frac)
+
+(with_template [<value> <name>]
+ [(def .public <name>
+ Value
+ <value>)]
+
+ [+0.0 least]
+ [+1.0 most]
+ )
+
+(exception.def .public (invalid value)
+ (Exception Frac)
+ (exception.report
+ (list ["Value" (%.frac value)]
+ ["Minimum" (%.frac ..least)]
+ ["Maximum" (%.frac ..most)])))
+
+(def .public (value it)
+ (-> Frac
+ (Try Value))
+ (if (or (f.< ..least it)
+ (f.> ..most it))
+ (exception.except ..invalid [it])
+ {try.#Success it}))
+
+(nominal.def .public HSL
+ (Record
+ [#hue Value
+ #saturation Value
+ #luminance Value])
+
+ (def .public equivalence
+ (Equivalence HSL)
+ (implementation
+ (def (= left right)
+ (`` (and (,, (with_template [<slot>]
+ [(f.= (the <slot> (nominal.representation left))
+ (the <slot> (nominal.representation right)))]
+
+ [#hue]
+ [#saturation]
+ [#luminance]
+ )))))))
+
+ (with_template [<name> <slot>]
+ [(def .public <name>
+ (-> HSL
+ Value)
+ (|>> nominal.representation
+ (the <slot>)))]
+
+ [hue #hue]
+ [saturation #saturation]
+ [luminance #luminance]
+ )
+
+ (def .public (hsl hue saturation luminance)
+ (-> Frac Frac Frac
+ (Try HSL))
+ (do try.monad
+ [hue (..value hue)
+ saturation (..value saturation)
+ luminance (..value luminance)]
+ (in (nominal.abstraction
+ [#hue hue
+ #saturation saturation
+ #luminance luminance]))))
+
+ (def .public (of_rgb it)
+ (-> RGB
+ HSL)
+ (let [red (..down (rgb.number (the rgb.#red it)))
+ green (..down (rgb.number (the rgb.#green it)))
+ blue (..down (rgb.number (the rgb.#blue it)))
+
+ max (all f.max red green blue)
+ min (all f.min red green blue)
+ luminance (|> (f.+ max min) (f./ +2.0))]
+ (nominal.abstraction
+ (if (f.= max min)
+ ... Achromatic
+ [#hue ..least
+ #saturation ..least
+ #luminance luminance]
+ ... Chromatic
+ (let [diff (|> max (f.- min))
+ saturation (|> diff
+ (f./ (if (f.> +0.5 luminance)
+ (|> +2.0 (f.- max) (f.- min))
+ (|> max (f.+ min)))))
+ hue' (cond (f.= red max)
+ (|> green (f.- blue) (f./ diff)
+ (f.+ (if (f.< blue green) +6.0 +0.0)))
+
+ (f.= green max)
+ (|> blue (f.- red) (f./ diff)
+ (f.+ +2.0))
+
+ ... (f.= blue max)
+ (|> red (f.- green) (f./ diff)
+ (f.+ +4.0)))]
+ [#hue (|> hue' (f./ +6.0))
+ #saturation saturation
+ #luminance luminance])))))
+
+ (def (hue_rgb p q t)
+ (-> Frac Frac Frac
+ Nat)
+ (let [t (cond (f.< +0.0 t) (f.+ +1.0 t)
+ (f.> +1.0 t) (f.- +1.0 t)
+ ... else
+ t)
+ f2/3 (f./ +3.0 +2.0)]
+ (..up (cond (f.< (f./ +6.0 +1.0) t)
+ (|> q (f.- p) (f.* +6.0) (f.* t) (f.+ p))
+
+ (f.< (f./ +2.0 +1.0) t)
+ q
+
+ (f.< f2/3 t)
+ (|> q (f.- p) (f.* (|> f2/3 (f.- t))) (f.* +6.0) (f.+ p))
+
+ ... else
+ p))))
+
+ (def .public (rgb it)
+ (-> HSL
+ RGB)
+ (let [[hue saturation luminance] (nominal.representation it)]
+ (try.trusted
+ (if (f.= ..least saturation)
+ ... Achromatic
+ (let [intensity (..up luminance)]
+ (rgb.rgb intensity intensity intensity))
+ ... Chromatic
+ (let [q (if (f.< +0.5 luminance)
+ (|> saturation (f.+ +1.0) (f.* luminance))
+ (|> luminance (f.+ saturation) (f.- (f.* saturation luminance))))
+ p (|> luminance (f.* +2.0) (f.- q))
+ third (|> +1.0 (f./ +3.0))]
+ (rgb.rgb (|> hue (f.+ third) (hue_rgb p q))
+ (|> hue (hue_rgb p q))
+ (|> hue (f.- third) (hue_rgb p q))))))))
+ )
diff --git a/stdlib/source/library/lux/data/color/rgb.lux b/stdlib/source/library/lux/data/color/rgb.lux
index 23ac52a30..8c14e7903 100644
--- a/stdlib/source/library/lux/data/color/rgb.lux
+++ b/stdlib/source/library/lux/data/color/rgb.lux
@@ -18,22 +18,22 @@
["[0]" i64]]]
[meta
[type
- ["[0]" primitive]]]]])
+ ["[0]" nominal]]]]])
(def .public limit
Nat
256)
-(primitive.def .public Value
+(nominal.def .public Value
Nat
(def .public least
Value
- (primitive.abstraction 0))
+ (nominal.abstraction 0))
(def .public most
Value
- (primitive.abstraction (-- ..limit)))
+ (nominal.abstraction (-- ..limit)))
(exception.def .public (invalid it)
(Exception Nat)
@@ -45,12 +45,12 @@
(-> Nat
(Try Value))
(if (n.< ..limit it)
- {try.#Success (primitive.abstraction it)}
+ {try.#Success (nominal.abstraction it)}
(exception.except ..invalid [it])))
(def .public number
(-> Value Nat)
- (|>> primitive.representation))
+ (|>> nominal.representation))
(type .public RGB
(Record
@@ -73,9 +73,9 @@
(Equivalence RGB)
(implementation
(def (= [rR gR bR] [rS gS bS])
- (and (n.= (primitive.representation rR) (primitive.representation rS))
- (n.= (primitive.representation gR) (primitive.representation gS))
- (n.= (primitive.representation bR) (primitive.representation bS))))))
+ (and (n.= (nominal.representation rR) (nominal.representation rS))
+ (n.= (nominal.representation gR) (nominal.representation gS))
+ (n.= (nominal.representation bR) (nominal.representation bS))))))
(def .public hash
(Hash RGB)
@@ -85,13 +85,13 @@
(def (hash [r g b])
(all i64.or
- (i64.left_shifted 16 (primitive.representation r))
- (i64.left_shifted 08 (primitive.representation g))
- (primitive.representation b)))))
+ (i64.left_shifted 16 (nominal.representation r))
+ (i64.left_shifted 08 (nominal.representation g))
+ (nominal.representation b)))))
(def (opposite_intensity value)
(-> Nat Nat)
- (|> (primitive.representation ..most)
+ (|> (nominal.representation ..most)
(n.- value)))
(def .public (complement it)
@@ -99,9 +99,9 @@
(`` [(,, (with_template [<slot>]
[<slot> (|> it
(the <slot>)
- primitive.representation
+ nominal.representation
opposite_intensity
- primitive.abstraction)]
+ nominal.abstraction)]
[#red]
[#green]
@@ -131,9 +131,9 @@
(let [left (<left> left)
right (<right> right)]
(`` [(,, (with_template [<slot>]
- [<slot> (primitive.abstraction
- (<composite> (primitive.representation (the <slot> left))
- (primitive.representation (the <slot> right))))]
+ [<slot> (nominal.abstraction
+ (<composite> (nominal.representation (the <slot> left))
+ (nominal.representation (the <slot> right))))]
[#red]
[#green]
diff --git a/stdlib/source/library/lux/data/color/terminal.lux b/stdlib/source/library/lux/data/color/terminal.lux
index 1f368de0b..d59f2986b 100644
--- a/stdlib/source/library/lux/data/color/terminal.lux
+++ b/stdlib/source/library/lux/data/color/terminal.lux
@@ -15,19 +15,19 @@
[macro
["[0]" template]]
[type
- ["[0]" primitive]]]]]
+ ["[0]" nominal]]]]]
["[0]" // (.only Color)
["[0]" rgb]])
-(primitive.def .public Command
+(nominal.def .public Command
[Text Text]
(def .public equivalence
(Equivalence Command)
(implementation
(def (= reference it)
- (let [[beforeR afterR] (primitive.representation Command reference)
- [beforeI afterI] (primitive.representation Command it)]
+ (let [[beforeR afterR] (nominal.representation Command reference)
+ [beforeI afterI] (nominal.representation Command it)]
(and (text#= beforeR beforeI)
(text#= afterR afterI))))))
@@ -38,7 +38,7 @@
(def .public (with command text)
(-> Command Text
Text)
- (let [[before after] (primitive.representation Command command)]
+ (let [[before after] (nominal.representation Command command)]
(%.format before
text
after)))
@@ -57,13 +57,13 @@
Command
(|> [(%.format ..command (%.nat <fg>) "m")
..default_foreground_color]
- (primitive.abstraction Command))))
+ (nominal.abstraction Command))))
(`` (def .public (,, (template.symbol [<color> "_background"]))
Command
(|> [(%.format ..command (%.nat <bg>) "m")
..default_background_color]
- (primitive.abstraction Command))))]
+ (nominal.abstraction Command))))]
[030 040 black]
[031 041 red]
@@ -95,7 +95,7 @@
";" (%.nat (rgb.number (the rgb.#blue it)))
"m")
<reset>]
- (primitive.abstraction Command))))]
+ (nominal.abstraction Command))))]
["38;2" foreground ..default_foreground_color]
["48;2" background ..default_background_color]
diff --git a/stdlib/source/library/lux/data/format/css.lux b/stdlib/source/library/lux/data/format/css.lux
index 53b9238ec..256e70010 100644
--- a/stdlib/source/library/lux/data/format/css.lux
+++ b/stdlib/source/library/lux/data/format/css.lux
@@ -14,7 +14,7 @@
["[0]" nat]]]
[meta
[type
- ["[0]" primitive (.except Frame def)]]]
+ ["[0]" nominal (.except Frame def)]]]
[world
[net (.only URL)]]]]
["[0]" /
@@ -25,10 +25,10 @@
["[1][0]" style]
["[1][0]" query (.only Query)]])
-(primitive.def .public Common Any)
-(primitive.def .public Special Any)
+(nominal.def .public Common Any)
+(nominal.def .public Special Any)
-(primitive.def .public (CSS brand)
+(nominal.def .public (CSS brand)
Text
(def .public css
diff --git a/stdlib/source/library/lux/data/format/css/class.lux b/stdlib/source/library/lux/data/format/css/class.lux
index a3def1196..46e980a47 100644
--- a/stdlib/source/library/lux/data/format/css/class.lux
+++ b/stdlib/source/library/lux/data/format/css/class.lux
@@ -11,9 +11,9 @@
[macro
[syntax (.only syntax)]]
[type
- ["[0]" primitive (.except def)]]]]])
+ ["[0]" nominal (.except def)]]]]])
-(primitive.def .public Class
+(nominal.def .public Class
Text
(def .public class
diff --git a/stdlib/source/library/lux/data/format/css/id.lux b/stdlib/source/library/lux/data/format/css/id.lux
index cd6c1c4cf..fc93ec1bb 100644
--- a/stdlib/source/library/lux/data/format/css/id.lux
+++ b/stdlib/source/library/lux/data/format/css/id.lux
@@ -11,9 +11,9 @@
[macro
[syntax (.only syntax)]]
[type
- ["[0]" primitive (.except def)]]]]])
+ ["[0]" nominal (.except def)]]]]])
-(primitive.def .public ID
+(nominal.def .public ID
Text
(def .public id
diff --git a/stdlib/source/library/lux/data/format/css/property.lux b/stdlib/source/library/lux/data/format/css/property.lux
index e34b27b1d..192f0395a 100644
--- a/stdlib/source/library/lux/data/format/css/property.lux
+++ b/stdlib/source/library/lux/data/format/css/property.lux
@@ -10,7 +10,7 @@
[syntax (.only syntax)]
["[0]" template]]
[type
- ["[0]" primitive (.except def)]]]]]
+ ["[0]" nominal (.except def)]]]]]
[//
[value (.only All
Number
@@ -57,7 +57,7 @@
(syntax (_ [symbol s.text])
(in (list (code.local (text.replaced "-" "_" symbol))))))
-(primitive.def .public (Property brand)
+(nominal.def .public (Property brand)
Text
(def .public name
diff --git a/stdlib/source/library/lux/data/format/css/query.lux b/stdlib/source/library/lux/data/format/css/query.lux
index 095d12b40..de3defe3b 100644
--- a/stdlib/source/library/lux/data/format/css/query.lux
+++ b/stdlib/source/library/lux/data/format/css/query.lux
@@ -11,7 +11,7 @@
[syntax (.only syntax)]
["[0]" template]]
[type
- ["[0]" primitive (.except def)]]]]]
+ ["[0]" nominal (.except def)]]]]]
["[0]" //
["[1][0]" value (.only Value Length Count Resolution Ratio
Orientation Scan Boolean Update
@@ -24,7 +24,7 @@
(syntax (_ [symbol s.text])
(in (list (code.local (text.replaced "-" "_" symbol))))))
-(primitive.def .public Media
+(nominal.def .public Media
Text
(def .public media
@@ -42,7 +42,7 @@
["speech"]
))
-(primitive.def .public Feature
+(nominal.def .public Feature
Text
(def .public feature
@@ -102,7 +102,7 @@
)
)
-(primitive.def .public Query
+(nominal.def .public Query
Text
(def .public query
diff --git a/stdlib/source/library/lux/data/format/css/selector.lux b/stdlib/source/library/lux/data/format/css/selector.lux
index a76428c86..757ca8df8 100644
--- a/stdlib/source/library/lux/data/format/css/selector.lux
+++ b/stdlib/source/library/lux/data/format/css/selector.lux
@@ -11,7 +11,7 @@
[macro
["[0]" template]]
[type
- ["[0]" primitive (.except def)]]]
+ ["[0]" nominal (.except def)]]]
[world
["[0]" locale (.only Locale)]]]]
["[0]" //
@@ -23,21 +23,21 @@
(type .public Tag Label)
(type .public Attribute Label)
-(primitive.def .public (Generic brand) Any)
+(nominal.def .public (Generic brand) Any)
(with_template [<generic> <brand>]
- [(primitive.def <brand> Any)
+ [(nominal.def <brand> Any)
(type .public <generic> (Generic <brand>))]
[Can_Chain Can_Chain']
[Cannot_Chain Cannot_Chain']
)
-(primitive.def .public Unique Any)
-(primitive.def .public Specific Any)
-(primitive.def .public Composite Any)
+(nominal.def .public Unique Any)
+(nominal.def .public Specific Any)
+(nominal.def .public Composite Any)
-(primitive.def .public (Selector kind)
+(nominal.def .public (Selector kind)
Text
(def .public selector
@@ -169,7 +169,7 @@
(format ":not")
abstraction))
- (primitive.def .public Index
+ (nominal.def .public Index
Text
(def .public index
diff --git a/stdlib/source/library/lux/data/format/css/style.lux b/stdlib/source/library/lux/data/format/css/style.lux
index ddcbbc291..d1bd1899d 100644
--- a/stdlib/source/library/lux/data/format/css/style.lux
+++ b/stdlib/source/library/lux/data/format/css/style.lux
@@ -8,12 +8,12 @@
["[0]" list (.use "[1]#[0]" mix)]]]
[meta
[type
- ["[0]" primitive (.except def)]]]]]
+ ["[0]" nominal (.except def)]]]]]
["[0]" //
["[1][0]" value (.only Value)]
["[1][0]" property (.only Property)]])
-(primitive.def .public Style
+(nominal.def .public Style
Text
(def .public empty
diff --git a/stdlib/source/library/lux/data/format/css/value.lux b/stdlib/source/library/lux/data/format/css/value.lux
index 0a46fddbe..6886dad69 100644
--- a/stdlib/source/library/lux/data/format/css/value.lux
+++ b/stdlib/source/library/lux/data/format/css/value.lux
@@ -24,7 +24,7 @@
[syntax (.only syntax)]
["[0]" template]]
[type
- ["[0]" primitive (.except def)]]]
+ ["[0]" nominal (.except def)]]]
[world
[net (.only URL)]]]]
[//
@@ -36,7 +36,7 @@
(def enumeration
(template (_ <abstraction> <representation> <out> <sample>+ <definition>+)
- [(primitive.def .public <abstraction>
+ [(nominal.def .public <abstraction>
<representation>
(def .public <out>
@@ -58,7 +58,7 @@
raw
(|> raw (text.split_at 1) maybe.trusted product.right))))
-(primitive.def .public (Value brand)
+(nominal.def .public (Value brand)
Text
(def .public value
@@ -76,11 +76,11 @@
[unset "unset"]
)
- (primitive.def .public (Numeric kind) Any)
+ (nominal.def .public (Numeric kind) Any)
(with_template [<name>]
[(with_expansions [<name>' (template.symbol [<name> "'"])]
- (primitive.def .public <name>' Any)
+ (nominal.def .public <name>' Any)
(type .public <name>
(Numeric <name>')))]
@@ -91,7 +91,7 @@
)
(with_template [<brand> <alias>+ <value>+]
- [(primitive.def .public <brand> Any)
+ [(nominal.def .public <brand> Any)
(`` (with_template [<name> <value>]
[(def .public <name>
@@ -905,7 +905,7 @@
(abstraction (format (%.nat horizontal) ..slice_separator
(%.nat vertical))))
- (primitive.def .public Stop
+ (nominal.def .public Stop
Text
(def .public stop
@@ -929,7 +929,7 @@
(representation Value start) ..stop_separator
(representation Value end))))
- (primitive.def .public Hint
+ (nominal.def .public Hint
Text
(def .public hint
@@ -950,7 +950,7 @@
(type .public (List/1 a)
[a (List a)])
- (primitive.def .public Angle
+ (nominal.def .public Angle
Text
(def .public angle
diff --git a/stdlib/source/library/lux/data/format/html.lux b/stdlib/source/library/lux/data/format/html.lux
index 0dc8a42b5..77beb4f7f 100644
--- a/stdlib/source/library/lux/data/format/html.lux
+++ b/stdlib/source/library/lux/data/format/html.lux
@@ -16,7 +16,7 @@
[target
["[0]" js]]
[type
- ["[0]" primitive (.except def)]]]
+ ["[0]" nominal (.except def)]]]
[world
[net (.only URL)]]]]
[//
@@ -86,11 +86,11 @@
(-> Tag Text)
(text.enclosed ["</" ">"]))
-(primitive.def .public (HTML brand)
+(nominal.def .public (HTML brand)
Text
(.with_template [<name> <brand>]
- [(primitive.def <brand> Any)
+ [(nominal.def <brand> Any)
(type .public <name> (HTML <brand>))]
[Meta Meta']
@@ -108,11 +108,11 @@
)
(.with_template [<super> <super_raw> <sub>+]
- [(primitive.def (<super_raw> brand) Any)
+ [(nominal.def (<super_raw> brand) Any)
(type .public <super> (HTML (<super_raw> Any)))
(`` (.with_template [<sub> <sub_raw>]
- [(primitive.def <sub_raw> Any)
+ [(nominal.def <sub_raw> Any)
(type .public <sub> (HTML (<super_raw> <sub_raw>)))]
(,, (template.spliced <sub>+))))]
diff --git a/stdlib/source/library/lux/data/format/markdown.lux b/stdlib/source/library/lux/data/format/markdown.lux
index 11c9f6e9f..e533b908b 100644
--- a/stdlib/source/library/lux/data/format/markdown.lux
+++ b/stdlib/source/library/lux/data/format/markdown.lux
@@ -8,14 +8,15 @@
["[0]" list (.use "[1]#[0]" functor)]]]
[meta
[type
- ["[0]" primitive (.except def)]]]
+ ["[0]" nominal]]]
[world
[net (.only URL)]]]])
... https://www.markdownguide.org/basic-syntax/
(def safe
- (-> Text Text)
+ (-> Text
+ Text)
(|>> (text.replaced "\" "\\")
(text.replaced "`" "\`")
(text.replaced "*" "\*")
@@ -32,27 +33,29 @@
(text.replaced "." "\.")
(text.replaced "!" "\!")))
-(primitive.def .public Span Any)
-(primitive.def .public Block Any)
+(nominal.def .public Span Any)
+(nominal.def .public Block Any)
-(primitive.def .public (Markdown brand)
+(nominal.def .public (Markdown brand)
Text
(def .public empty
Markdown
- (abstraction ""))
+ (nominal.abstraction ""))
(def .public text
- (-> Text (Markdown Span))
- (|>> ..safe abstraction))
+ (-> Text
+ (Markdown Span))
+ (|>> ..safe nominal.abstraction))
(def blank_line
(format text.new_line text.new_line))
(with_template [<name> <prefix>]
[(def .public (<name> content)
- (-> Text (Markdown Block))
- (abstraction (format <prefix> " " (..safe content) ..blank_line)))]
+ (-> (Markdown Span)
+ (Markdown Block))
+ (nominal.abstraction (format <prefix> " " (nominal.representation content) ..blank_line)))]
[heading/1 "#"]
[heading/2 "##"]
@@ -63,30 +66,35 @@
)
(def (block content)
- (-> Text (Markdown Block))
- (abstraction (format content ..blank_line)))
+ (-> Text
+ (Markdown Block))
+ (nominal.abstraction (format content ..blank_line)))
(def .public paragraph
- (-> (Markdown Span) (Markdown Block))
- (|>> representation ..block))
+ (-> (Markdown Span)
+ (Markdown Block))
+ (|>> nominal.representation ..block))
(def .public break
(Markdown Span)
- (abstraction (format " " text.new_line)))
+ (nominal.abstraction (format " " text.new_line)))
(with_template [<name> <wrapper>]
[(def .public <name>
- (-> (Markdown Span) (Markdown Span))
- (|>> representation
+ (-> (Markdown Span)
+ (Markdown Span))
+ (|>> nominal.representation
(text.enclosed [<wrapper> <wrapper>])
- abstraction))]
+ nominal.abstraction))]
[bold "**"]
[italic "_"]
)
(def (prefix with)
- (-> Text (-> Text Text))
+ (-> Text
+ (-> Text
+ Text))
(|>> (text.all_split_by text.new_line)
(list#each (function (_ line)
(if (text.empty? line)
@@ -95,25 +103,27 @@
(text.interposed text.new_line)))
(def indent
- (-> Text Text)
+ (-> Text
+ Text)
(..prefix text.tab))
(def .public quote
- (-> (Markdown Block) (Markdown Block))
- (|>> representation
+ (-> (Markdown Block)
+ (Markdown Block))
+ (|>> nominal.representation
(..prefix "> ")
- abstraction))
+ nominal.abstraction))
(def .public numbered_list
(-> (List [(Markdown Span) (Maybe (Markdown Block))])
(Markdown Block))
(|>> list.enumeration
(list#each (function (_ [idx [summary detail]])
- (format "1. " (representation summary)
+ (format "1. " (nominal.representation summary)
(when detail
{.#Some detail}
(|> detail
- representation
+ nominal.representation
..indent
(text.enclosed [text.new_line text.new_line])
(format text.new_line))
@@ -127,11 +137,11 @@
(-> (List [(Markdown Span) (Maybe (Markdown Block))])
(Markdown Block))
(|>> (list#each (function (_ [summary detail])
- (format "* " (representation summary)
+ (format "* " (nominal.representation summary)
(when detail
{.#Some detail}
(|> detail
- representation
+ nominal.representation
..indent
(text.enclosed [text.new_line text.new_line])
(format text.new_line))
@@ -143,19 +153,22 @@
... A snippet of code.
(def .public snippet
- (-> Text (Markdown Span))
- (|>> (text.enclosed ["`` " " ``"]) abstraction))
+ (-> Text
+ (Markdown Span))
+ (|>> (text.enclosed ["`` " " ``"]) nominal.abstraction))
... A (generic) block of code.
(def .public generic_code
- (-> Text (Markdown Block))
+ (-> Text
+ (Markdown Block))
(let [open (format "```" text.new_line)
close (format text.new_line "```")]
(|>> (text.enclosed [open close]) ..block)))
... A block of code of a specific language.
(def .public (code language block)
- (-> Text Text (Markdown Block))
+ (-> Text Text
+ (Markdown Block))
(let [open (format "```" language text.new_line)
close (format text.new_line "```")]
(|> block
@@ -163,24 +176,32 @@
..block)))
(def .public (image description url)
- (-> Text URL (Markdown Span))
- (abstraction (format "![" (..safe description) "](" url ")")))
+ (-> Text URL
+ (Markdown Span))
+ (nominal.abstraction (format "![" (..safe description) "](" url ")")))
(def .public horizontal_rule
(Markdown Block)
(..block "___"))
+ (def .public (anchor name)
+ (-> Text
+ (Markdown Span))
+ (nominal.abstraction (format "<a name=" name "></a>")))
+
(def .public (link description url)
- (-> (Markdown Span) URL (Markdown Span))
- (abstraction (format "[" (representation description) "](" url ")")))
+ (-> (Markdown Span) URL
+ (Markdown Span))
+ (nominal.abstraction (format "[" (nominal.representation description) "](" url ")")))
(type .public Email
Text)
(with_template [<name> <type>]
[(def .public <name>
- (-> <type> (Markdown Span))
- (|>> (text.enclosed ["<" ">"]) abstraction))]
+ (-> <type>
+ (Markdown Span))
+ (|>> (text.enclosed ["<" ">"]) nominal.abstraction))]
[url URL]
[email Email]
@@ -188,14 +209,17 @@
(with_template [<name> <brand> <infix>]
[(def .public (<name> pre post)
- (-> (Markdown <brand>) (Markdown <brand>) (Markdown <brand>))
- (abstraction (format (representation pre) <infix> (representation post))))]
+ (-> (Markdown <brand>) (Markdown <brand>)
+ (Markdown <brand>))
+ (nominal.abstraction (format (nominal.representation pre) <infix> (nominal.representation post))))]
[and Span " "]
[then Block ""]
)
(def .public markdown
- (All (_ a) (-> (Markdown a) Text))
- (|>> representation))
+ (All (_ a)
+ (-> (Markdown a)
+ Text))
+ (|>> nominal.representation))
)
diff --git a/stdlib/source/library/lux/data/format/tar.lux b/stdlib/source/library/lux/data/format/tar.lux
index 8daa5be57..c98ef6ee5 100644
--- a/stdlib/source/library/lux/data/format/tar.lux
+++ b/stdlib/source/library/lux/data/format/tar.lux
@@ -34,7 +34,7 @@
[macro
["^" pattern]]
[type
- ["[0]" primitive (.except def #name)]]]
+ ["[0]" nominal (.except def #name)]]]
[world
["[0]" file]
[time
@@ -79,7 +79,7 @@
(list ["Value" (%.nat value)]
["Maximum" (%.nat (-- <limit>))])))
- (primitive.def .public <type>
+ (nominal.def .public <type>
Nat
(def .public (<in> value)
@@ -164,7 +164,7 @@
[value (at n.octal decoded digits)]
(..big value)))))
-(primitive.def Checksum
+(nominal.def Checksum
Text
(def from_checksum
@@ -257,7 +257,7 @@
(binary!.slice 0 (++ end) string))))))))
(with_template [<type> <representation> <size> <exception> <in> <out> <format> <parser> <none>]
- [(primitive.def .public <type>
+ [(nominal.def .public <type>
<representation>
(exception.def .public (<exception> value)
@@ -315,7 +315,7 @@
(def magic_size Size 7)
-(primitive.def Magic
+(nominal.def Magic
Text
(def ustar
@@ -402,7 +402,7 @@
... devminor
(..small_number ..device_size)))
-(primitive.def Link_Flag
+(nominal.def Link_Flag
Char
(def link_flag
@@ -451,7 +451,7 @@
(exception.except ..invalid_link_flag [(.nat it)]))))))
)
-(primitive.def .public Mode
+(nominal.def .public Mode
Nat
(def .public mode
@@ -540,7 +540,7 @@
(list.repeated ..content_size)
(list#mix n.* 1)))
-(primitive.def .public Content
+(nominal.def .public Content
[Big Binary]
(def .public (content it)
diff --git a/stdlib/source/library/lux/data/text.lux b/stdlib/source/library/lux/data/text.lux
index cc8bf71b8..6222ada19 100644
--- a/stdlib/source/library/lux/data/text.lux
+++ b/stdlib/source/library/lux/data/text.lux
@@ -224,15 +224,15 @@
(for @.old
(as Text
("jvm invokevirtual:java.lang.String:replace:java.lang.CharSequence,java.lang.CharSequence"
- (as (Primitive "java.lang.String") template)
- (as (Primitive "java.lang.CharSequence") pattern)
- (as (Primitive "java.lang.CharSequence") replacement)))
+ (as (Nominal "java.lang.String") template)
+ (as (Nominal "java.lang.CharSequence") pattern)
+ (as (Nominal "java.lang.CharSequence") replacement)))
@.jvm
(as Text
(.jvm_member_invoke_virtual# [] "java.lang.String" "replace" []
- (as (Primitive "java.lang.String") template)
- ["Ljava/lang/CharSequence;" (as (Primitive "java.lang.CharSequence") pattern)]
- ["Ljava/lang/CharSequence;" (as (Primitive "java.lang.CharSequence") replacement)]))
+ (as (Nominal "java.lang.String") template)
+ ["Ljava/lang/CharSequence;" (as (Nominal "java.lang.CharSequence") pattern)]
+ ["Ljava/lang/CharSequence;" (as (Nominal "java.lang.CharSequence") replacement)]))
@.js
... TODO: Remove this when Nashorn is no longer being used.
(..if_nashorn
@@ -287,18 +287,18 @@
(def (hash input)
(for @.old
(|> input
- (is (Primitive "java.lang.Object"))
+ (is (Nominal "java.lang.Object"))
"jvm invokevirtual:java.lang.Object:hashCode:"
"jvm convert int-to-long"
(as Nat))
@.jvm
(|> input
- (as (Primitive "java.lang.Object"))
+ (as (Nominal "java.lang.Object"))
(.jvm_member_invoke_virtual# [] "java.lang.Object" "hashCode" [])
.jvm_conversion_int_to_long#
.jvm_object_cast#
- (is (Primitive "java.lang.Long"))
+ (is (Nominal "java.lang.Long"))
(as Nat))
... Platform-independent default.
(let [length (.text_size# input)]
@@ -358,11 +358,11 @@
(for @.old
(as Text
("jvm invokevirtual:java.lang.String:toLowerCase:"
- (as (Primitive "java.lang.String") value)))
+ (as (Nominal "java.lang.String") value)))
@.jvm
(as Text
(.jvm_member_invoke_virtual# [] "java.lang.String" "toLowerCase" []
- (as (Primitive "java.lang.String") value)))
+ (as (Nominal "java.lang.String") value)))
@.js
(as Text
("js object do" "toLowerCase" value []))
@@ -381,11 +381,11 @@
(for @.old
(as Text
("jvm invokevirtual:java.lang.String:toUpperCase:"
- (as (Primitive "java.lang.String") value)))
+ (as (Nominal "java.lang.String") value)))
@.jvm
(as Text
(.jvm_member_invoke_virtual# [] "java.lang.String" "toUpperCase" []
- (as (Primitive "java.lang.String") value)))
+ (as (Nominal "java.lang.String") value)))
@.js
(as Text
("js object do" "toUpperCase" value []))
diff --git a/stdlib/source/library/lux/data/text/buffer.lux b/stdlib/source/library/lux/data/text/buffer.lux
index 17b603e3b..5b1bf4a6f 100644
--- a/stdlib/source/library/lux/data/text/buffer.lux
+++ b/stdlib/source/library/lux/data/text/buffer.lux
@@ -17,7 +17,7 @@
[meta
["@" target]
[type
- ["[0]" primitive (.except def)]]]]]
+ ["[0]" nominal (.except def)]]]]]
["[0]" //])
(with_expansions [<jvm> (these (import java/lang/CharSequence
@@ -49,7 +49,7 @@
)
(these))))
-(`` (primitive.def .public Buffer
+(`` (nominal.def .public Buffer
(for @.old [Nat (-> java/lang/StringBuilder java/lang/StringBuilder)]
@.jvm [Nat (-> java/lang/StringBuilder java/lang/StringBuilder)]
@.js [Nat (-> (JS_Array Text) (JS_Array Text))]
diff --git a/stdlib/source/library/lux/data/text/encoding.lux b/stdlib/source/library/lux/data/text/encoding.lux
index c4247a851..6ff9aeec0 100644
--- a/stdlib/source/library/lux/data/text/encoding.lux
+++ b/stdlib/source/library/lux/data/text/encoding.lux
@@ -5,10 +5,10 @@
[macro
["[0]" template]]
[type
- ["[0]" primitive (.except def)]]]]])
+ ["[0]" nominal (.except def)]]]]])
... https://en.wikipedia.org/wiki/Character_encoding#Common_character_encodings
-(primitive.def .public Encoding
+(nominal.def .public Encoding
Text
(with_template [<name> <encoding>]
diff --git a/stdlib/source/library/lux/data/text/unicode/block.lux b/stdlib/source/library/lux/data/text/unicode/block.lux
index ea4fe8889..2ad6484b8 100644
--- a/stdlib/source/library/lux/data/text/unicode/block.lux
+++ b/stdlib/source/library/lux/data/text/unicode/block.lux
@@ -12,11 +12,11 @@
["[0]" i64]]]
[meta
[type
- ["[0]" primitive (.except def)]]]]]
+ ["[0]" nominal (.except def)]]]]]
[///
[char (.only Char)]])
-(primitive.def .public Block
+(nominal.def .public Block
(Interval Char)
(def .public monoid
diff --git a/stdlib/source/library/lux/data/text/unicode/set.lux b/stdlib/source/library/lux/data/text/unicode/set.lux
index 19ab0a416..67704b82e 100644
--- a/stdlib/source/library/lux/data/text/unicode/set.lux
+++ b/stdlib/source/library/lux/data/text/unicode/set.lux
@@ -11,7 +11,7 @@
["[1]" finger (.only Tree)]]]]
[meta
[type (.only by_example)
- ["[0]" primitive (.except def)]]]]]
+ ["[0]" nominal (.except def)]]]]]
[//
["[0]" block (.only Block)]
[//
@@ -27,7 +27,7 @@
@))
-(primitive.def .public Set
+(nominal.def .public Set
(Tree :@: Block [])
(def .public (composite left right)