From e2500061ed74ffccb299c2923894dd549238112b Mon Sep 17 00:00:00 2001 From: Eduardo Julian Date: Fri, 20 Oct 2017 20:36:58 -0400 Subject: - Re-named "Host" to "Primitive". --- stdlib/source/lux.lux | 56 +++++++++++++++++----------------- stdlib/source/lux/concurrency/atom.lux | 2 +- stdlib/source/lux/host.js.lux | 2 +- stdlib/source/lux/host.jvm.lux | 30 +++++++++--------- stdlib/source/lux/meta/poly.lux | 20 ++++++------ stdlib/source/lux/meta/poly/eq.lux | 2 +- stdlib/source/lux/meta/type.lux | 20 ++++++------ stdlib/source/lux/meta/type/check.lux | 6 ++-- stdlib/source/lux/meta/type/object.lux | 6 ++-- stdlib/source/lux/meta/type/opaque.lux | 2 +- stdlib/source/lux/meta/type/unit.lux | 4 +-- stdlib/source/lux/world/blob.jvm.lux | 2 +- 12 files changed, 76 insertions(+), 76 deletions(-) (limited to 'stdlib/source') diff --git a/stdlib/source/lux.lux b/stdlib/source/lux.lux index fd8948164..31e7fe01c 100644 --- a/stdlib/source/lux.lux +++ b/stdlib/source/lux.lux @@ -169,7 +169,7 @@ #Nil))))))]) ## (type: #rec Type -## (#Host Text (List Type)) +## (#Primitive Text (List Type)) ## #Void ## #Unit ## (#Sum Type Type) @@ -193,7 +193,7 @@ Type-Pair (+11 Void (+9 #Nil - (+3 ## "lux;Host" + (+3 ## "lux;Primitive" (+4 Text Type-List) (+3 ## "lux;Void" (+2) @@ -225,7 +225,7 @@ (#Cons [[dummy-cursor (+7 ["lux" "export?"])] [dummy-cursor (+0 true)]] (#Cons [[dummy-cursor (+7 ["lux" "tags"])] - [dummy-cursor (+9 (#Cons [dummy-cursor (+5 "Host")] + [dummy-cursor (+9 (#Cons [dummy-cursor (+5 "Primitive")] (#Cons [dummy-cursor (+5 "Void")] (#Cons [dummy-cursor (+5 "Unit")] (#Cons [dummy-cursor (+5 "Sum")] @@ -1944,21 +1944,21 @@ (wrap (wrap-meta (form$ (list (tag$ ["lux" "Record"]) (untemplate-list =fields)))))) )) -(macro:' #export (host tokens) +(macro:' #export (primitive tokens) (list [(tag$ ["lux" "doc"]) - (text$ "## Macro to treat host-types as Lux-types. - (host java.lang.Object) + (text$ "## Macro to treat define new primitive types. + (primitive java.lang.Object) - (host java.util.List [java.lang.Long])")]) + (primitive java.util.List [java.lang.Long])")]) (_lux_case tokens (#Cons [_ (#Symbol "" class-name)] #Nil) - (return (list (form$ (list (tag$ ["lux" "Host"]) (text$ class-name) (tag$ ["lux" "Nil"]))))) + (return (list (form$ (list (tag$ ["lux" "Primitive"]) (text$ class-name) (tag$ ["lux" "Nil"]))))) (#Cons [_ (#Symbol "" class-name)] (#Cons [_ (#Tuple params)] #Nil)) - (return (list (form$ (list (tag$ ["lux" "Host"]) (text$ class-name) (untemplate-list params))))) + (return (list (form$ (list (tag$ ["lux" "Primitive"]) (text$ class-name) (untemplate-list params))))) _ - (fail "Wrong syntax for host"))) + (fail "Wrong syntax for primitive"))) (def:'' (current-module-name state) #Nil @@ -2435,7 +2435,7 @@ (function' [state] (_lux_case state {#info info #source source #modules modules - #scopes scopes #type-context types #host host + #scopes scopes #type-context types #host host #seed seed #expected expected #cursor cursor #scope-type-vars scope-type-vars} @@ -4292,16 +4292,16 @@ _ (list))) -(def: (Type/show type) +(def: (type/show type) (-> Type Text) (case type - (#Host name params) + (#Primitive name params) (case params #;Nil name _ - ($_ text/compose "(" name " " (|> params (map Type/show) (interpose " ") reverse (fold text/compose "")) ")")) + ($_ text/compose "(" name " " (|> params (map type/show) (interpose " ") reverse (fold text/compose "")) ")")) #Void "Void" @@ -4310,13 +4310,13 @@ "Unit" (#Sum _) - ($_ text/compose "(| " (|> (flatten-variant type) (map Type/show) (interpose " ") reverse (fold text/compose "")) ")") + ($_ text/compose "(| " (|> (flatten-variant type) (map type/show) (interpose " ") reverse (fold text/compose "")) ")") (#Product _) - ($_ text/compose "[" (|> (flatten-tuple type) (map Type/show) (interpose " ") reverse (fold text/compose "")) "]") + ($_ text/compose "[" (|> (flatten-tuple type) (map type/show) (interpose " ") reverse (fold text/compose "")) "]") (#Function _) - ($_ text/compose "(-> " (|> (flatten-lambda type) (map Type/show) (interpose " ") reverse (fold text/compose "")) ")") + ($_ text/compose "(-> " (|> (flatten-lambda type) (map type/show) (interpose " ") reverse (fold text/compose "")) ")") (#Bound id) (nat/encode id) @@ -4328,16 +4328,16 @@ ($_ text/compose "⟨e:" (nat/encode id) "⟩") (#UnivQ env body) - ($_ text/compose "(All " (Type/show body) ")") + ($_ text/compose "(All " (type/show body) ")") (#ExQ env body) - ($_ text/compose "(Ex " (Type/show body) ")") + ($_ text/compose "(Ex " (type/show body) ")") (#Apply _) (let [[func args] (flatten-app type)] ($_ text/compose - "(" (Type/show func) " " - (|> args (map Type/show) (interpose " ") reverse (fold text/compose "")) + "(" (type/show func) " " + (|> args (map type/show) (interpose " ") reverse (fold text/compose "")) ")")) (#Named [prefix name] _) @@ -4366,7 +4366,7 @@ struct-evidence (resolve-type-tags init-type)] (case struct-evidence #;None - (fail (text/compose "Can only \"open\" structs: " (Type/show init-type))) + (fail (text/compose "Can only \"open\" structs: " (type/show init-type))) (#;Some tags&members) (do Monad @@ -4545,7 +4545,7 @@ (return (list/join decls'))) _ - (fail (text/compose "Can only \"open\" structs: " (Type/show struct-type))))) + (fail (text/compose "Can only \"open\" structs: " (type/show struct-type))))) _ (fail "Wrong syntax for open"))) @@ -4921,8 +4921,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 [] ( left right) @@ -5191,8 +5191,8 @@ (def: (type-to-code type) (-> Type Code) (case type - (#Host name params) - (` (#Host (~ (text$ name)) (~ (untemplate-list (map type-to-code params))))) + (#Primitive name params) + (` (#Primitive (~ (text$ name)) (~ (untemplate-list (map type-to-code params))))) #Void (` #Void) @@ -5866,7 +5866,7 @@ (type: #export (Array a) {#;doc "Mutable arrays."} - (#;Host "#Array" (#;Cons a #;Nil))) + (#;Primitive "#Array" (#;Cons a #;Nil))) (def: target (Meta Text) 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 [ ] - [(type: #export (#;Host #;Nil))] + [(type: #export (#;Primitive #;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 @@ "To:" )} - (-> (host ) (host )) + (-> (primitive ) (primitive )) (_lux_proc ["jvm" ] [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 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 [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 [] 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 [ ] [(do @ [_ ] 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 [] ( 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 [] @@ -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 [=params (monad;map @ (clean t-id) params)] - (wrap (#;Host name =params))) + (wrap (#;Primitive name =params))) (^template [] ( 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 [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) -- cgit v1.2.3