From 14e96f5e5dad439383d63e60a52169cc2e7aaa5c Mon Sep 17 00:00:00 2001 From: Eduardo Julian Date: Sun, 20 May 2018 21:04:03 -0400 Subject: - Re-named "Top" to "Any", and "Bottom" to "Nothing". - Removed some modules that should have been deleted before. --- stdlib/source/lux.lux | 92 +++++++++++++++++++++++++-------------------------- 1 file changed, 46 insertions(+), 46 deletions(-) (limited to 'stdlib/source/lux.lux') diff --git a/stdlib/source/lux.lux b/stdlib/source/lux.lux index 795133b33..5fbbf44b5 100644 --- a/stdlib/source/lux.lux +++ b/stdlib/source/lux.lux @@ -9,10 +9,10 @@ [["" +0 +0] (+0 true)]] (+0)))]) -## (type: Top +## (type: Any ## (Ex [a] a)) -("lux def" Top - (+10 ["lux" "Top"] +("lux def" Any + (+10 ["lux" "Any"] (+8 (+0) (+4 +1))) [dummy-cursor (+10 (+1 [[dummy-cursor (+7 ["lux" "type?"])] @@ -25,10 +25,10 @@ It can be used to write functions or data-structures that can take, or return, anything.")]] (+0)))))]) -## (type: Bottom +## (type: Nothing ## (All [a] a)) -("lux def" Bottom - (+10 ["lux" "Bottom"] +("lux def" Nothing + (+10 ["lux" "Nothing"] (+7 (+0) (+4 +1))) [dummy-cursor (+10 (+1 [[dummy-cursor (+7 ["lux" "type?"])] @@ -48,7 +48,7 @@ (+10 ["lux" "List"] (+7 (+0) (+1 ## "lux.Nil" - Top + Any ## "lux.Cons" (+2 (+4 +1) (+9 (+4 +1) (+4 +0)))))) @@ -175,7 +175,7 @@ (+10 ["lux" "Maybe"] (+7 #Nil (+1 ## "lux.None" - Top + Any ## "lux.Some" (+4 +1)))) [dummy-cursor @@ -212,7 +212,7 @@ {Type-List ("lux case" ("lux check type" (+2 Type Type)) {Type-Pair - (+9 Bottom + (+9 Nothing (+7 #Nil (+1 ## "lux.Primitive" (+2 Text Type-List) @@ -468,10 +468,10 @@ (record$ #Nil)) ## (type: Definition -## [Type Code Top]) +## [Type Code Any]) ("lux def" Definition (#Named ["lux" "Definition"] - (#Product Type (#Product Code Top))) + (#Product Type (#Product Code Any))) (record$ (#Cons [(tag$ ["lux" "doc"]) (text$ "Represents all the data associated with a definition: its type, its annotations, and its value.")] default-def-meta-exported))) @@ -565,12 +565,12 @@ (#Named ["lux" "Module-State"] (#Sum ## #Active - Top + Any (#Sum ## #Compiled - Top + Any ## #Cached - Top))) + Any))) (record$ (#Cons [(tag$ ["lux" "tags"]) (tuple$ (#Cons (text$ "Active") (#Cons (text$ "Compiled") (#Cons (text$ "Cached") #Nil))))] default-def-meta-exported))) @@ -652,11 +652,11 @@ ("lux def" Mode (#Named ["lux" "Mode"] (#Sum ## Build - Top + Any (#Sum ## Eval - Top + Any ## REPL - Top))) + Any))) (record$ (#Cons [(tag$ ["lux" "tags"]) (tuple$ (#Cons (text$ "Build") (#Cons (text$ "Eval") @@ -700,8 +700,8 @@ ## #expected (Maybe Type) ## #seed Nat ## #scope-type-vars (List Nat) -## #extensions Bottom -## #host Bottom}) +## #extensions Nothing +## #host Nothing}) ("lux def" Lux (#Named ["lux" "Lux"] (#Product ## "lux.info" @@ -725,9 +725,9 @@ (#Product ## scope-type-vars (#Apply Nat List) (#Product ## extensions - Bottom + Nothing ## "lux.host" - Bottom)))))))))))) + Nothing)))))))))))) (record$ (#Cons [(tag$ ["lux" "tags"]) (tuple$ (#Cons (text$ "info") (#Cons (text$ "source") @@ -1227,7 +1227,7 @@ ## A name can be provided, to specify a recursive type. (All List [a] - (| Top + (| Any [a (List a)]))")] #Nil) (let'' [self-name tokens] ("lux case" tokens @@ -1374,12 +1374,12 @@ (text$ "## Tuple types: (& Text Int Bool) - ## Top. + ## Any. (&)")] #Nil) ("lux case" (list/reverse tokens) {#Nil - (return (list (symbol$ ["lux" "Top"]))) + (return (list (symbol$ ["lux" "Any"]))) (#Cons last prevs) (return (list (list/fold (function'' [left right] (form$ (list (tag$ ["lux" "Product"]) left right))) @@ -1392,12 +1392,12 @@ (text$ "## Variant types: (| Text Int Bool) - ## Bottom. + ## Nothing. (|)")] #Nil) ("lux case" (list/reverse tokens) {#Nil - (return (list (symbol$ ["lux" "Bottom"]))) + (return (list (symbol$ ["lux" "Nothing"]))) (#Cons last prevs) (return (list (list/fold (function'' [left right] (form$ (list (tag$ ["lux" "Sum"]) left right))) @@ -1774,7 +1774,7 @@ (text$ "Logs message to standard output. Useful for debugging.")]) - (-> Text Top) + (-> Text Any) ("lux io log" message)) (def:''' (text/compose x y) @@ -2212,7 +2212,7 @@ (def:''' (high-bits value) (list) - (-> ($' I64 Top) I64) + (-> ($' I64 Any) I64) ("lux i64 logical-right-shift" +32 value)) (def:''' low-mask @@ -2224,7 +2224,7 @@ (def:''' (low-bits value) (list) - (-> ($' I64 Top) I64) + (-> ($' I64 Any) I64) ("lux i64 and" low-mask value)) (def:''' #export (n/< test subject) @@ -2898,7 +2898,7 @@ (#Cons type #Nil) ("lux case" type {[_ (#Tag "" member-name)] - (return [(` .Top) (#Some (list member-name))]) + (return [(` .Any) (#Some (list member-name))]) [_ (#Form (#Cons [_ (#Tag "" member-name)] member-types))] (return [(` (& (~+ member-types))) (#Some (list member-name))]) @@ -2913,7 +2913,7 @@ (function' [case] ("lux case" case {[_ (#Tag "" member-name)] - (return [member-name (` .Top)]) + (return [member-name (` .Any)]) [_ (#Form (#Cons [_ (#Tag "" member-name)] (#Cons member-type #Nil)))] (return [member-name member-type]) @@ -2956,7 +2956,7 @@ {(#Cons [_ (#Symbol "" name)] (#Cons body #Nil)) (let' [body' (replace-syntax (list [name (` (#.Apply (~ (make-bound +1)) (~ (make-bound +0))))]) (update-bounds body))] - (return (list (` (#.Apply .Bottom (#.UnivQ #.Nil (~ body'))))))) + (return (list (` (#.Apply .Nothing (#.UnivQ #.Nil (~ body'))))))) _ (fail "Wrong syntax for Rec")})) @@ -3608,7 +3608,7 @@ (def: #export (error! message) {#.doc "## Causes an error, with the given error message. (error! \"OH NO!\")"} - (-> Text Bottom) + (-> Text Nothing) ("lux io error" message)) (macro: (default tokens state) @@ -4027,9 +4027,9 @@ (if (empty? args) (let [g!param (symbol$ ["" ""]) prime-name (symbol$ ["" name]) - type+ (replace-syntax (list [name (` ((~ prime-name) .Bottom))]) type)] + type+ (replace-syntax (list [name (` ((~ prime-name) .Nothing))]) type)] (#Some (` ((All (~ prime-name) [(~ g!param)] (~ type+)) - .Bottom)))) + .Nothing)))) #None) (case args #Nil @@ -4432,13 +4432,13 @@ #inner _ #locals {#counter _ #mappings locals} #captured {#counter _ #mappings closure}} - (try-both (find (: (-> [Text [Type Top]] (Maybe Type)) + (try-both (find (: (-> [Text [Type Any]] (Maybe Type)) (function (_ [bname [type _]]) (if (text/= name bname) (#Some type) #None)))) - (: (List [Text [Type Top]]) locals) - (: (List [Text [Type Top]]) closure))))) + (: (List [Text [Type Any]]) locals) + (: (List [Text [Type Any]]) closure))))) scopes))) (def: (find-def-type name state) @@ -4461,7 +4461,7 @@ (#Some def-type))))) (def: (find-def-value name state) - (-> Ident (Meta [Type Top])) + (-> Ident (Meta [Type Any])) (let [[v-prefix v-name] name {#info info #source source #current-module _ #modules modules #scopes scopes #type-context types #host host @@ -4824,10 +4824,10 @@ openings+options (parse-openings options) #let [[openings options] openings+options] current-module current-module-name - #let [test-referrals (: (-> Text (List Text) (List Text) (Meta (List Top))) + #let [test-referrals (: (-> Text (List Text) (List Text) (Meta (List Any))) (function (_ module-name all-defs referred-defs) (monad/map Monad - (: (-> Text (Meta Top)) + (: (-> Text (Meta Any)) (function (_ _def) (if (is-member? all-defs _def) (return []) @@ -4849,10 +4849,10 @@ (-> Text Refer (Meta (List Code))) (do Monad [current-module current-module-name - #let [test-referrals (: (-> Text (List Text) (List Text) (Meta (List Top))) + #let [test-referrals (: (-> Text (List Text) (List Text) (Meta (List Any))) (function (_ module-name all-defs referred-defs) (monad/map Monad - (: (-> Text (Meta Top)) + (: (-> Text (Meta Any)) (function (_ _def) (if (is-member? all-defs _def) (return []) @@ -5299,7 +5299,7 @@ (do-template [ ] [(def: #export - (-> (I64 Top) ) + (-> (I64 Any) ) (|>> (:! )))] [i64 I64] @@ -6016,7 +6016,7 @@ )) (def: (parse-end tokens) - (-> (List Code) (Meta Top)) + (-> (List Code) (Meta Any)) (case tokens (^ (list)) (return []) @@ -6297,7 +6297,7 @@ ) (def: to-significand - (-> (I64 Top) Frac) + (-> (I64 Any) Frac) (|>> ("lux i64 logical-right-shift" +11) int-to-frac)) -- cgit v1.2.3