aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/lux
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib/source/lux')
-rw-r--r--stdlib/source/lux/concurrency/atom.lux2
-rw-r--r--stdlib/source/lux/host.js.lux2
-rw-r--r--stdlib/source/lux/host.jvm.lux30
-rw-r--r--stdlib/source/lux/meta/poly.lux20
-rw-r--r--stdlib/source/lux/meta/poly/eq.lux2
-rw-r--r--stdlib/source/lux/meta/type.lux20
-rw-r--r--stdlib/source/lux/meta/type/check.lux6
-rw-r--r--stdlib/source/lux/meta/type/object.lux6
-rw-r--r--stdlib/source/lux/meta/type/opaque.lux2
-rw-r--r--stdlib/source/lux/meta/type/unit.lux4
-rw-r--r--stdlib/source/lux/world/blob.jvm.lux2
11 files changed, 48 insertions, 48 deletions
diff --git a/stdlib/source/lux/concurrency/atom.lux b/stdlib/source/lux/concurrency/atom.lux
index c9402ed80..aad81a791 100644
--- a/stdlib/source/lux/concurrency/atom.lux
+++ b/stdlib/source/lux/concurrency/atom.lux
@@ -5,7 +5,7 @@
(type: #export (Atom a)
{#;doc "Atomic references that are safe to mutate concurrently."}
- (#;Host "#Atom" (#;Cons a #;Nil)))
+ (#;Primitive "#Atom" (#;Cons a #;Nil)))
(def: #export (atom value)
(All [a] (-> a (Atom a)))
diff --git a/stdlib/source/lux/host.js.lux b/stdlib/source/lux/host.js.lux
index 4abafbdf3..85a1cca1e 100644
--- a/stdlib/source/lux/host.js.lux
+++ b/stdlib/source/lux/host.js.lux
@@ -9,7 +9,7 @@
))
(do-template [<name> <type>]
- [(type: #export <name> (#;Host <type> #;Nil))]
+ [(type: #export <name> (#;Primitive <type> #;Nil))]
[Object "object"]
[Function "function"]
diff --git a/stdlib/source/lux/host.jvm.lux b/stdlib/source/lux/host.jvm.lux
index 319615411..25876bad4 100644
--- a/stdlib/source/lux/host.jvm.lux
+++ b/stdlib/source/lux/host.jvm.lux
@@ -24,7 +24,7 @@
<from>
"To:"
<to>)}
- (-> (host <from>) (host <to>))
+ (-> (primitive <from>) (primitive <to>))
(_lux_proc ["jvm" <op>] [value]))]
[b2l "b2l" java.lang.Byte java.lang.Long]
@@ -107,7 +107,7 @@
{#class-name Text
#class-params (List TypeParam)})
-(type: StackFrame (host java.lang.StackTraceElement))
+(type: StackFrame (primitive java.lang.StackTraceElement))
(type: StackTrace (Array StackFrame))
(type: SuperClassDecl
@@ -284,7 +284,7 @@
[[name params] _ _]
(let [=params (list/map (class->type' mode type-params in-array?) params)]
- (` (host (~ (code;symbol ["" name])) [(~@ =params)])))))
+ (` (primitive (~ (code;symbol ["" name])) [(~@ =params)])))))
(def: (class->type' mode type-params in-array? class)
(-> Primitive-Mode (List TypeParam) Bool GenericType Code)
@@ -334,7 +334,7 @@
(#;Cons bound1 _)
(class->type #ManualPrM class-params bound1))))
class-params)]
- (` (host (~ (code;symbol ["" class-name])) [(~@ =params)]))))
+ (` (primitive (~ (code;symbol ["" class-name])) [(~@ =params)]))))
(def: empty-imports
ClassImports
@@ -1381,7 +1381,7 @@
(null? "YOLO")
"=>"
false)}
- (-> (host java.lang.Object) Bool)
+ (-> (primitive java.lang.Object) Bool)
(;_lux_proc ["jvm" "null?"] [obj]))
(syntax: #export (??? expr)
@@ -1436,7 +1436,7 @@
#;None
(do @
[g!obj (meta;gensym "obj")]
- (wrap (list (` (: (-> (host (~' java.lang.Object)) Bool)
+ (wrap (list (` (: (-> (primitive (~' java.lang.Object)) Bool)
(function [(~ g!obj)]
(;_lux_proc ["jvm" (~ (code;text (format "instanceof" ":" (simple-class$ (list) class))))] [(~ g!obj)])))))))
))
@@ -1470,7 +1470,7 @@
{#;type? true
#;;jvm-class (~ (code;text full-name))}
Type
- (host (~ (code;symbol ["" full-name])))))
+ (primitive (~ (code;symbol ["" full-name])))))
(#;Cons _)
(let [params' (list/map (function [[p _]] (code;symbol ["" p])) params)]
@@ -1479,8 +1479,8 @@
#;;jvm-class (~ (code;text full-name))}
Type
(All [(~@ params')]
- (host (~ (code;symbol ["" full-name]))
- [(~@ params')]))))))))
+ (primitive (~ (code;symbol ["" full-name]))
+ [(~@ params')]))))))))
(def: (member-type-vars class-tvars member)
(-> (List TypeParam) ImportMemberDecl (List TypeParam))
@@ -1552,7 +1552,7 @@
[return-type
(let [g!temp (code;symbol ["" "Ω"])]
(` (let [(~ g!temp) (~ return-term)]
- (if (not (null? (:! (host (~' java.lang.Object))
+ (if (not (null? (:! (primitive (~' java.lang.Object))
(~ g!temp))))
(~ g!temp)
(error! "Cannot produce null references from method calls.")))))])
@@ -1679,13 +1679,13 @@
[#let [enum-type (: Code
(case class-tvars
#;Nil
- (` (host (~ (code;symbol ["" full-name]))))
+ (` (primitive (~ (code;symbol ["" full-name]))))
_
(let [=class-tvars (|> class-tvars
(list;filter free-type-param?)
(list/map type-param->type-arg))]
- (` (All [(~@ =class-tvars)] (host (~ (code;symbol ["" full-name])) [(~@ =class-tvars)]))))))
+ (` (All [(~@ =class-tvars)] (primitive (~ (code;symbol ["" full-name])) [(~@ =class-tvars)]))))))
getter-interop (: (-> Text Code)
(function [name]
(let [getter-name (code;symbol ["" (format method-prefix member-separator name)])]
@@ -1827,11 +1827,11 @@
(member-def-interop type-params kind class =args member method-prefix))))
(def: (interface? class)
- (All [a] (-> (host java.lang.Class [a]) Bool))
+ (All [a] (-> (primitive java.lang.Class [a]) Bool))
(_lux_proc ["jvm" "invokevirtual:java.lang.Class:isInterface:"] [class]))
(def: (load-class class-name)
- (-> Text (Either Text (host java.lang.Class [(Ex [a] a)])))
+ (-> Text (Either Text (primitive java.lang.Class [(Ex [a] a)])))
(try (_lux_proc ["jvm" "invokestatic:java.lang.Class:forName:java.lang.String"] [class-name])))
(def: (class-kind [class-name _])
@@ -1932,7 +1932,7 @@
(def: (type->class-name type)
(-> Type (Meta Text))
(case type
- (#;Host name params)
+ (#;Primitive name params)
(:: Monad<Meta> wrap name)
(#;Apply A F)
diff --git a/stdlib/source/lux/meta/poly.lux b/stdlib/source/lux/meta/poly.lux
index 04ac1fd82..c374e585c 100644
--- a/stdlib/source/lux/meta/poly.lux
+++ b/stdlib/source/lux/meta/poly.lux
@@ -128,15 +128,15 @@
[void "Void" #;Void]
[unit "Unit" #;Unit]
- [bool "Bool" (#;Host "#Bool" #;Nil)]
- [nat "Nat" (#;Host "#Nat" #;Nil)]
- [int "Int" (#;Host "#Int" #;Nil)]
- [deg "Deg" (#;Host "#Deg" #;Nil)]
- [frac "Frac" (#;Host "#Frac" #;Nil)]
- [text "Text" (#;Host "#Text" #;Nil)]
+ [bool "Bool" (#;Primitive "#Bool" #;Nil)]
+ [nat "Nat" (#;Primitive "#Nat" #;Nil)]
+ [int "Int" (#;Primitive "#Int" #;Nil)]
+ [deg "Deg" (#;Primitive "#Deg" #;Nil)]
+ [frac "Frac" (#;Primitive "#Frac" #;Nil)]
+ [text "Text" (#;Primitive "#Text" #;Nil)]
)
-(def: #export primitive
+(def: #export basic
(Poly Type)
(do p;Monad<Parser>
[headT any]
@@ -399,9 +399,9 @@
(def: #export (to-ast env type)
(-> Env Type Code)
(case type
- (#;Host name params)
- (` (#;Host (~ (code;text name))
- (list (~@ (list/map (to-ast env) params)))))
+ (#;Primitive name params)
+ (` (#;Primitive (~ (code;text name))
+ (list (~@ (list/map (to-ast env) params)))))
(^template [<tag>]
<tag>
diff --git a/stdlib/source/lux/meta/poly/eq.lux b/stdlib/source/lux/meta/poly/eq.lux
index c2ecd5988..38386a6c8 100644
--- a/stdlib/source/lux/meta/poly/eq.lux
+++ b/stdlib/source/lux/meta/poly/eq.lux
@@ -38,7 +38,7 @@
(function [type]
(` (eq;Eq (~ (poly;to-ast *env* type))))))]]
($_ p;either
- ## Primitive types
+ ## Basic types
(~~ (do-template [<matcher> <eq>]
[(do @
[_ <matcher>]
diff --git a/stdlib/source/lux/meta/type.lux b/stdlib/source/lux/meta/type.lux
index ad51b0c58..e7c630966 100644
--- a/stdlib/source/lux/meta/type.lux
+++ b/stdlib/source/lux/meta/type.lux
@@ -14,8 +14,8 @@
(def: (beta-reduce env type)
(-> (List Type) Type Type)
(case type
- (#;Host name params)
- (#;Host name (List/map (beta-reduce env) params))
+ (#;Primitive name params)
+ (#;Primitive name (List/map (beta-reduce env) params))
(^template [<tag>]
(<tag> left right)
@@ -46,7 +46,7 @@
(struct: #export _ (Eq Type)
(def: (= x y)
(case [x y]
- [(#;Host xname xparams) (#;Host yname yparams)]
+ [(#;Primitive xname xparams) (#;Primitive yname yparams)]
(and (Text/= xname yname)
(n.= (list;size yparams) (list;size xparams))
(List/fold (;function [[x y] prev] (and prev (= x y)))
@@ -167,9 +167,9 @@
(def: #export (to-ast type)
(-> Type Code)
(case type
- (#;Host name params)
- (` (#;Host (~ (code;text name))
- (list (~@ (List/map to-ast params)))))
+ (#;Primitive name params)
+ (` (#;Primitive (~ (code;text name))
+ (list (~@ (List/map to-ast params)))))
(^template [<tag>]
<tag>
@@ -206,13 +206,13 @@
(def: #export (to-text type)
(-> Type Text)
(case type
- (#;Host name params)
+ (#;Primitive name params)
(case params
#;Nil
- ($_ Text/compose "(host " name ")")
+ ($_ Text/compose "(primitive " name ")")
_
- ($_ Text/compose "(host " name " " (|> params (List/map to-text) list;reverse (list;interpose " ") (List/fold Text/compose "")) ")"))
+ ($_ Text/compose "(primitive " name " " (|> params (List/map to-text) list;reverse (list;interpose " ") (List/fold Text/compose "")) ")"))
#;Void
"Void"
@@ -351,4 +351,4 @@
(-> Nat Type Type)
(case level
+0 elem-type
- _ (#;Host "#Array" (list (array (n.dec level) elem-type)))))
+ _ (#;Primitive "#Array" (list (array (n.dec level) elem-type)))))
diff --git a/stdlib/source/lux/meta/type/check.lux b/stdlib/source/lux/meta/type/check.lux
index 3b7c95cc4..296aee11a 100644
--- a/stdlib/source/lux/meta/type/check.lux
+++ b/stdlib/source/lux/meta/type/check.lux
@@ -241,10 +241,10 @@
(wrap type))))
(wrap type))))
- (#;Host name params)
+ (#;Primitive name params)
(do Monad<Check>
[=params (monad;map @ (clean t-id) params)]
- (wrap (#;Host name =params)))
+ (wrap (#;Primitive name =params)))
(^template [<tag>]
(<tag> left right)
@@ -476,7 +476,7 @@
actual' (apply-type! actual ex)]
(check' expected actual' assumptions))
- [(#;Host e-name e-params) (#;Host a-name a-params)]
+ [(#;Primitive e-name e-params) (#;Primitive a-name a-params)]
(if (and (text/= e-name a-name)
(n.= (list;size e-params)
(list;size a-params)))
diff --git a/stdlib/source/lux/meta/type/object.lux b/stdlib/source/lux/meta/type/object.lux
index dd2552eab..43b563122 100644
--- a/stdlib/source/lux/meta/type/object.lux
+++ b/stdlib/source/lux/meta/type/object.lux
@@ -312,11 +312,11 @@
(def: (type-to-code type)
(-> Type (Meta Code))
(case type
- (#;Host name params)
+ (#;Primitive name params)
(do Monad<Meta>
[paramsC+ (M;map @ type-to-code params)]
- (wrap (` (;host (~ (code;symbol ["" name]))
- (~@ paramsC+)))))
+ (wrap (` (;primitive (~ (code;symbol ["" name]))
+ (~@ paramsC+)))))
#;Void
(Meta/wrap (` (;|)))
diff --git a/stdlib/source/lux/meta/type/opaque.lux b/stdlib/source/lux/meta/type/opaque.lux
index 460ae22c4..acd73d6a4 100644
--- a/stdlib/source/lux/meta/type/opaque.lux
+++ b/stdlib/source/lux/meta/type/opaque.lux
@@ -156,7 +156,7 @@
representation-declaration (` ((~ hidden-name) (~@ type-varsC)))]
(wrap (list& (` (type: (~@ (csw;export export)) (~ opaque-declaration)
(~ (csw;annotations annotations))
- (host (~ hidden-name) [(~@ type-varsC)])))
+ (primitive (~ hidden-name) [(~@ type-varsC)])))
(` (type: (~@ (csw;export export)) (~ representation-declaration)
(~ representation-type)))
(` (install-casts (~ (code;local-symbol name)) [(~@ type-varsC)]))
diff --git a/stdlib/source/lux/meta/type/unit.lux b/stdlib/source/lux/meta/type/unit.lux
index 9382a0506..de00fb82d 100644
--- a/stdlib/source/lux/meta/type/unit.lux
+++ b/stdlib/source/lux/meta/type/unit.lux
@@ -70,7 +70,7 @@
[annotations (p;default cs;empty-annotations csr;annotations)])
(wrap (list (` (type: (~@ (csw;export export)) (~ (code;local-symbol name))
(~ (csw;annotations annotations))
- (host (~ (code;local-symbol (unit-name name))))))
+ (primitive (~ (code;local-symbol (unit-name name))))))
(` (def: (~@ (csw;export export)) (~ (code;local-symbol (format "@" name)))
(~ (code;local-symbol name))
(:!! [])))
@@ -94,7 +94,7 @@
(let [g!scale (code;local-symbol name)]
(wrap (list (` (type: (~@ (csw;export export)) ((~ g!scale) (~' u))
(~ (csw;annotations annotations))
- (host (~ (code;local-symbol (scale-name name))) [(~' u)])))
+ (primitive (~ (code;local-symbol (scale-name name))) [(~' u)])))
(` (struct: (~@ (csw;export export)) (~ (code;local-symbol (format "@" name)))
(;;Scale (~ g!scale))
(def: (~' scale)
diff --git a/stdlib/source/lux/world/blob.jvm.lux b/stdlib/source/lux/world/blob.jvm.lux
index 88efc1859..c31feb8e5 100644
--- a/stdlib/source/lux/world/blob.jvm.lux
+++ b/stdlib/source/lux/world/blob.jvm.lux
@@ -23,7 +23,7 @@
(|> +1 (bit;shift-left +8) n.dec))
(def: byte-to-nat
- (-> (host java.lang.Byte) Nat)
+ (-> (primitive java.lang.Byte) Nat)
(|>. host;b2l (:! Nat) (bit;and byte-mask)))
(def: #export (create size)