aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/lux/tool
diff options
context:
space:
mode:
authorEduardo Julian2020-11-07 00:29:40 -0400
committerEduardo Julian2020-11-07 00:29:40 -0400
commit2e5852abb1ac0ae5abdd8709238aca447f62520e (patch)
tree1b73a24205217c9e00f7f17d5972f67735a7cc69 /stdlib/source/lux/tool
parentef78c1f92ab29c4370193591b170535dd9e743f7 (diff)
Pure-Lux implementation for biggest and smallest Frac values.
Diffstat (limited to '')
-rw-r--r--stdlib/source/lux/tool/compiler/default/init.lux16
-rw-r--r--stdlib/source/lux/tool/compiler/default/platform.lux58
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/extension/analysis/lux.lux3
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/js/common.lux35
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/jvm/common.lux20
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/lua/common.lux18
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/python/common.lux18
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/ruby/common.lux18
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/generation/common-lisp/extension/common.lux18
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/generation/php/extension/common.lux18
-rw-r--r--stdlib/source/lux/tool/compiler/language/lux/phase/generation/scheme/extension/common.lux18
11 files changed, 37 insertions, 203 deletions
diff --git a/stdlib/source/lux/tool/compiler/default/init.lux b/stdlib/source/lux/tool/compiler/default/init.lux
index a3eaa03e3..441be4bed 100644
--- a/stdlib/source/lux/tool/compiler/default/init.lux
+++ b/stdlib/source/lux/tool/compiler/default/init.lux
@@ -9,13 +9,13 @@
[data
[binary (#+ Binary)]
["." product]
- ["." text ("#@." hash)
+ ["." text ("#//." hash)
["%" format (#+ format)]]
[collection
- ["." list ("#@." functor)]
+ ["." list ("#//." functor)]
["." dictionary]
["." set]
- ["." row ("#@." functor)]]]
+ ["." row ("#//." functor)]]]
["." meta]
[world
["." file]]]
@@ -208,7 +208,7 @@
(def: (default-dependencies prelude input)
(-> Module ///.Input (List Module))
(list& archive.runtime-module
- (if (text@= prelude (get@ #///.module input))
+ (if (text//= prelude (get@ #///.module input))
(list)
(list prelude))))
@@ -226,7 +226,7 @@
{#///.dependencies dependencies
#///.process (function (_ state archive)
(do {! try.monad}
- [#let [hash (text@hash (get@ #///.code input))]
+ [#let [hash (text//hash (get@ #///.code input))]
[state [source buffer]] (<| (///phase.run' state)
(..begin dependencies hash input))
#let [module (get@ #///.module input)]]
@@ -247,15 +247,15 @@
(wrap [state
(#.Right [[descriptor (document.write key analysis-module)]
(|> final-buffer
- (row@map (function (_ [name directive])
- [name (write-directive directive)])))])]))
+ (row//map (function (_ [name directive])
+ [name (write-directive directive)])))])]))
(#.Some [source requirements temporary-payload])
(let [[temporary-buffer temporary-registry] temporary-payload]
(wrap [state
(#.Left {#///.dependencies (|> requirements
(get@ #///directive.imports)
- (list@map product.left))
+ (list//map product.left))
#///.process (function (_ state archive)
(recur (<| (///phase.run' state)
(do {! ///phase.monad}
diff --git a/stdlib/source/lux/tool/compiler/default/platform.lux b/stdlib/source/lux/tool/compiler/default/platform.lux
index 5e3ad19f9..3e9d7a647 100644
--- a/stdlib/source/lux/tool/compiler/default/platform.lux
+++ b/stdlib/source/lux/tool/compiler/default/platform.lux
@@ -9,20 +9,20 @@
["." try (#+ Try)]
["." exception (#+ exception:)]
[concurrency
- ["." promise (#+ Promise Resolver) ("#@." monad)]
+ ["." promise (#+ Promise Resolver) ("#//." monad)]
["." stm (#+ Var STM)]]]
[data
["." binary (#+ Binary)]
["." bit]
["." product]
["." maybe]
- ["." text ("#@." equivalence)
+ ["." text ("#//." equivalence)
["%" format (#+ format)]]
[collection
["." dictionary (#+ Dictionary)]
- ["." row (#+ Row) ("#@." fold)]
+ ["." row (#+ Row) ("#//." fold)]
["." set (#+ Set)]
- ["." list ("#@." monoid functor fold)]]
+ ["." list ("#//." monoid functor fold)]]
[format
["_" binary (#+ Writer)]]]
[world
@@ -210,13 +210,13 @@
extender)]
_ (ioW.enable (get@ #&file-system platform) static)
[archive analysis-state bundles] (ioW.thaw (get@ #host platform) (get@ #&file-system platform) static import compilation-sources)
- state (promise@wrap (initialize-state extender bundles analysis-state state))]
+ state (promise//wrap (initialize-state extender bundles analysis-state state))]
(if (archive.archived? archive archive.runtime-module)
(wrap [state archive])
(do (try.with promise.monad)
[[state [archive payload]] (|> (..process-runtime archive platform)
(///phase.run' state)
- promise@wrap)
+ promise//wrap)
_ (..cache-module static platform 0 payload)]
(wrap [state archive])))))
@@ -228,9 +228,9 @@
#///directive.state
#extension.state
#///generation.log])
- (row@fold (function (_ right left)
- (format left text.new-line right))
- "")))
+ (row//fold (function (_ right left)
+ (format left text.new-line right))
+ "")))
(def: with-reset-log
(All [<type-vars>]
@@ -277,10 +277,10 @@
(|> mapping
(dictionary.upsert source ..empty (set.add target))
(dictionary.update source (set.union forward)))]
- (list@fold (function (_ previous)
- (dictionary.upsert previous ..empty (set.add target)))
- with-dependence+transitives
- (set.to-list backward))))))]
+ (list//fold (function (_ previous)
+ (dictionary.upsert previous ..empty (set.add target)))
+ with-dependence+transitives
+ (set.to-list backward))))))]
(|> dependence
(update@ #depends-on
(update-dependence
@@ -315,7 +315,7 @@
(def: (verify-dependencies importer importee dependence)
(-> Module Module Dependence (Try Any))
- (cond (text@= importer importee)
+ (cond (text//= importer importee)
(exception.throw ..module-cannot-import-itself [importer])
(..circular-dependency? importer importee dependence)
@@ -355,7 +355,7 @@
(:assume
(stm.commit
(do {! stm.monad}
- [dependence (if (text@= archive.runtime-module importer)
+ [dependence (if (text//= archive.runtime-module importer)
(stm.read dependence)
(do !
[[_ dependence] (stm.update (..depend importer module) dependence)]
@@ -369,7 +369,7 @@
(do !
[[archive state] (stm.read current)]
(if (archive.archived? archive module)
- (wrap [(promise@wrap (#try.Success [archive state]))
+ (wrap [(promise//wrap (#try.Success [archive state]))
#.None])
(do !
[@pending (stm.read pending)]
@@ -399,7 +399,7 @@
signal])]))
(#try.Failure error)
- (wrap [(promise@wrap (#try.Failure error))
+ (wrap [(promise//wrap (#try.Failure error))
#.None]))))))))))})
_ (case signal
#.None
@@ -435,7 +435,7 @@
(wrap [module lux-module])))
(archive.archived archive))
#let [additions (|> modules
- (list@map product.left)
+ (list//map product.left)
(set.from-list text.hash))]]
(wrap (update@ [#extension.state
#///directive.analysis
@@ -445,11 +445,11 @@
(|> analysis-state
(:coerce .Lux)
(update@ #.modules (function (_ current)
- (list@compose (list.filter (|>> product.left
- (set.member? additions)
- not)
- current)
- modules)))
+ (list//compose (list.filter (|>> product.left
+ (set.member? additions)
+ not)
+ current)
+ modules)))
:assume))
state))))
@@ -486,7 +486,7 @@
all-dependencies (: (List Module)
(list))]
(let [new-dependencies (get@ #///.dependencies compilation)
- all-dependencies (list@compose new-dependencies all-dependencies)
+ all-dependencies (list//compose new-dependencies all-dependencies)
continue! (:share [<type-vars>]
{<Platform>
platform}
@@ -502,11 +502,11 @@
(#.Cons _)
(do !
[archive,document+ (|> new-dependencies
- (list@map (import! module))
+ (list//map (import! module))
(monad.seq ..monad))
#let [archive (|> archive,document+
- (list@map product.left)
- (list@fold archive.merge archive))]]
+ (list//map product.left)
+ (list//fold archive.merge archive))]]
(wrap [archive (try.assume
(..updated-state archive state))])))]
(case ((get@ #///.process compilation)
@@ -533,11 +533,11 @@
(..with-reset-log state)])
(#try.Failure error)
- (promise@wrap (#try.Failure error)))))
+ (promise//wrap (#try.Failure error)))))
(#try.Failure error)
(do !
[_ (ioW.freeze (get@ #&file-system platform) static archive)]
- (promise@wrap (#try.Failure error))))))))))]
+ (promise//wrap (#try.Failure error))))))))))]
(compiler archive.runtime-module compilation-module)))
))
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/analysis/lux.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/analysis/lux.lux
index 0e6d9ba7d..1c50d6eb5 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/analysis/lux.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/analysis/lux.lux
@@ -273,9 +273,6 @@
(///bundle.install "%" (binary Frac Frac Frac))
(///bundle.install "=" (binary Frac Frac Bit))
(///bundle.install "<" (binary Frac Frac Bit))
- (///bundle.install "smallest" (nullary Frac))
- (///bundle.install "min" (nullary Frac))
- (///bundle.install "max" (nullary Frac))
(///bundle.install "i64" (unary Frac Int))
(///bundle.install "encode" (unary Frac Text))
(///bundle.install "decode" (unary Text (type (Maybe Frac)))))))
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/js/common.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/js/common.lux
index 13d67f8fa..2122a38a4 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/js/common.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/js/common.lux
@@ -1,6 +1,5 @@
(.module:
[lux #*
- [host (#+ import:)]
[abstract
["." monad (#+ do)]]
[control
@@ -57,37 +56,6 @@
)
## [[Numbers]]
-(for {@.old
- (as-is (import: java/lang/Double
- (#static MIN_VALUE double)
- (#static MAX_VALUE double))
-
- (template [<name> <const>]
- [(def: (<name> _)
- (Nullary Expression)
- (//primitive.f64 <const>))]
-
- [f64//smallest (java/lang/Double::MIN_VALUE)]
- [f64//min (f.* -1.0 (java/lang/Double::MAX_VALUE))]
- [f64//max (java/lang/Double::MAX_VALUE)]
- ))
-
- @.js
- (as-is (import: Number
- (#static MIN_VALUE Frac)
- (#static MAX_VALUE Frac))
-
- (template [<name> <const>]
- [(def: (<name> _)
- (Nullary Expression)
- (//primitive.f64 <const>))]
-
- [f64//smallest (Number::MIN_VALUE)]
- [f64//min (f.* -1.0 (Number::MAX_VALUE))]
- [f64//max (Number::MAX_VALUE)]
- )
- )})
-
(def: f64//decode
(Unary Expression)
(|>> list
@@ -212,9 +180,6 @@
(/.install "%" (binary (product.uncurry _.%)))
(/.install "=" (binary (product.uncurry _.=)))
(/.install "<" (binary (product.uncurry _.<)))
- (/.install "smallest" (nullary f64//smallest))
- (/.install "min" (nullary f64//min))
- (/.install "max" (nullary f64//max))
(/.install "i64" (unary //runtime.i64//from-number))
(/.install "encode" (unary (_.do "toString" (list))))
(/.install "decode" (unary f64//decode)))))
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/jvm/common.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/jvm/common.lux
index 68c69d153..5c98aeba1 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/jvm/common.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/jvm/common.lux
@@ -1,6 +1,5 @@
(.module:
[lux (#- Type)
- [host (#+ import:)]
[abstract
["." monad (#+ do)]]
[control
@@ -187,22 +186,6 @@
[i64::logical-right-shift _.lushr]
)
-(import: java/lang/Double
- (#static MIN_VALUE double)
- (#static MAX_VALUE double))
-
-(template [<name> <const>]
- [(def: (<name> _)
- (Nullary (Bytecode Any))
- ($_ _.compose
- (_.double <const>)
- (///value.wrap type.double)))]
-
- [f64::smallest (java/lang/Double::MIN_VALUE)]
- [f64::min (f.* -1.0 (java/lang/Double::MAX_VALUE))]
- [f64::max (java/lang/Double::MAX_VALUE)]
- )
-
(template [<name> <type> <op>]
[(def: (<name> [paramG subjectG])
(Binary (Bytecode Any))
@@ -313,9 +296,6 @@
(/////bundle.install "%" (binary ..f64::%))
(/////bundle.install "=" (binary ..f64::=))
(/////bundle.install "<" (binary ..f64::<))
- (/////bundle.install "smallest" (nullary ..f64::smallest))
- (/////bundle.install "min" (nullary ..f64::min))
- (/////bundle.install "max" (nullary ..f64::max))
(/////bundle.install "i64" (unary ..f64::i64))
(/////bundle.install "encode" (unary ..f64::encode))
(/////bundle.install "decode" (unary ..f64::decode)))))
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/lua/common.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/lua/common.lux
index eb3529f6d..b9db6e702 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/lua/common.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/lua/common.lux
@@ -1,6 +1,5 @@
(.module:
[lux #*
- [host (#+ import:)]
[abstract
["." monad (#+ do)]]
[control
@@ -57,20 +56,6 @@
(/.install "frac" (unary (_./ (_.float +1.0))))
(/.install "char" (unary (!unary "string.char"))))))
-(import: java/lang/Double
- (#static MIN_VALUE double)
- (#static MAX_VALUE double))
-
-(template [<name> <const>]
- [(def: (<name> _)
- (Nullary Literal)
- (_.float <const>))]
-
- [frac//smallest (java/lang/Double::MIN_VALUE)]
- [frac//min (f.* -1.0 (java/lang/Double::MAX_VALUE))]
- [frac//max (java/lang/Double::MAX_VALUE)]
- )
-
(def: frac//decode
(Unary (Expression Any))
(|>> list _.apply/* (|> (_.var "tonumber")) _.return (_.closure (list)) //runtime.lux//try))
@@ -86,9 +71,6 @@
(/.install "%" (binary (product.uncurry _.%)))
(/.install "=" (binary (product.uncurry _.=)))
(/.install "<" (binary (product.uncurry _.<)))
- (/.install "smallest" (nullary frac//smallest))
- (/.install "min" (nullary frac//min))
- (/.install "max" (nullary frac//max))
(/.install "int" (unary (!unary "math.floor")))
(/.install "encode" (unary (!unary "tostring")))
(/.install "decode" (unary ..frac//decode)))))
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/python/common.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/python/common.lux
index 2c43370a6..1c58fec4c 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/python/common.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/python/common.lux
@@ -1,6 +1,5 @@
(.module:
[lux #*
- [host (#+ import:)]
[abstract
["." monad (#+ do)]]
[control
@@ -54,20 +53,6 @@
(/.install "frac" (unary _.float/1))
(/.install "char" (unary _.chr/1)))))
-(import: java/lang/Double
- (#static MIN_VALUE double)
- (#static MAX_VALUE double))
-
-(template [<name> <const>]
- [(def: (<name> _)
- (Nullary (Expression Any))
- (_.float <const>))]
-
- [frac//smallest (java/lang/Double::MIN_VALUE)]
- [frac//min (f.* -1.0 (java/lang/Double::MAX_VALUE))]
- [frac//max (java/lang/Double::MAX_VALUE)]
- )
-
(def: frac-procs
Bundle
(<| (/.prefix "frac")
@@ -79,9 +64,6 @@
(/.install "%" (binary (product.uncurry _.%)))
(/.install "=" (binary (product.uncurry _.=)))
(/.install "<" (binary (product.uncurry _.<)))
- (/.install "smallest" (nullary frac//smallest))
- (/.install "min" (nullary frac//min))
- (/.install "max" (nullary frac//max))
(/.install "int" (unary _.int/1))
(/.install "encode" (unary _.repr/1))
(/.install "decode" (unary //runtime.frac//decode)))))
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/ruby/common.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/ruby/common.lux
index ec5ba8e26..0ab831668 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/ruby/common.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/extension/generation/ruby/common.lux
@@ -1,6 +1,5 @@
(.module:
[lux #*
- [host (#+ import:)]
[abstract
["." monad (#+ do)]]
[control
@@ -50,20 +49,6 @@
(/.install "-" (binary (..keep-i64 (product.uncurry _.-))))
)))
-(import: java/lang/Double
- (#static MIN_VALUE double)
- (#static MAX_VALUE double))
-
-(template [<name> <const>]
- [(def: (<name> _)
- (Nullary (Expression Any))
- (_.float <const>))]
-
- [frac//smallest (java/lang/Double::MIN_VALUE)]
- [frac//min (f.* -1.0 (java/lang/Double::MAX_VALUE))]
- [frac//max (java/lang/Double::MAX_VALUE)]
- )
-
(def: int-procs
Bundle
(<| (/.prefix "int")
@@ -86,9 +71,6 @@
(/.install "%" (binary (product.uncurry _.%)))
(/.install "=" (binary (product.uncurry _.=)))
(/.install "<" (binary (product.uncurry _.<)))
- (/.install "smallest" (nullary frac//smallest))
- (/.install "min" (nullary frac//min))
- (/.install "max" (nullary frac//max))
(/.install "int" (unary (_.do "floor" (list))))
(/.install "encode" (unary (_.do "to_s" (list))))
(/.install "decode" (unary //runtime.f64//decode)))))
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/common-lisp/extension/common.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/common-lisp/extension/common.lux
index 701738854..750688dd6 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/common-lisp/extension/common.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/common-lisp/extension/common.lux
@@ -1,6 +1,5 @@
(.module:
[lux #*
- [host (#+ import:)]
[abstract
["." monad (#+ do)]]
[control
@@ -64,20 +63,6 @@
(bundle.install "char" (unary (|>> _.code-char/1 _.string/1)))
)))
-(import: java/lang/Double
- (#static MIN_VALUE double)
- (#static MAX_VALUE double))
-
-(template [<name> <const>]
- [(def: (<name> _)
- (Nullary (Expression Any))
- (_.double <const>))]
-
- [f64//smallest (java/lang/Double::MIN_VALUE)]
- [f64//min (f.* -1.0 (java/lang/Double::MAX_VALUE))]
- [f64//max (java/lang/Double::MAX_VALUE)]
- )
-
(def: f64-procs
Bundle
(<| (bundle.prefix "f64")
@@ -89,9 +74,6 @@
(bundle.install "%" (binary (product.uncurry _.mod)))
(bundle.install "=" (binary (product.uncurry _.=)))
(bundle.install "<" (binary (product.uncurry _.<)))
- (bundle.install "smallest" (nullary f64//smallest))
- (bundle.install "min" (nullary f64//min))
- (bundle.install "max" (nullary f64//max))
(bundle.install "i64" (unary _.floor/1))
(bundle.install "encode" (unary _.write-to-string/1))
(bundle.install "decode" (unary (let [@temp (_.var "temp")]
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/php/extension/common.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/php/extension/common.lux
index 234192ede..2a4c4c50d 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/php/extension/common.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/php/extension/common.lux
@@ -1,6 +1,5 @@
(.module:
[lux #*
- [host (#+ import:)]
[abstract
["." monad (#+ do)]]
[control
@@ -56,20 +55,6 @@
(bundle.install "frac" (unary _.floatval/1))
(bundle.install "char" (unary _.chr/1)))))
-(import: java/lang/Double
- (#static MIN_VALUE double)
- (#static MAX_VALUE double))
-
-(template [<name> <const>]
- [(def: (<name> _)
- (Nullary (Expression Any))
- (_.float <const>))]
-
- [frac//smallest (java/lang/Double::MIN_VALUE)]
- [frac//min (f.* -1.0 (java/lang/Double::MAX_VALUE))]
- [frac//max (java/lang/Double::MAX_VALUE)]
- )
-
(def: frac-procs
Bundle
(<| (bundle.prefix "frac")
@@ -81,9 +66,6 @@
(bundle.install "%" (binary (product.uncurry _.%)))
(bundle.install "=" (binary (product.uncurry _.=)))
(bundle.install "<" (binary (product.uncurry _.<)))
- (bundle.install "smallest" (nullary frac//smallest))
- (bundle.install "min" (nullary frac//min))
- (bundle.install "max" (nullary frac//max))
(bundle.install "int" (unary _.intval/1))
(bundle.install "encode" (unary _.strval/1))
(bundle.install "decode" (unary (|>> _.floatval/1 ///runtime.some)))
diff --git a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/scheme/extension/common.lux b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/scheme/extension/common.lux
index b13bc5834..782838b92 100644
--- a/stdlib/source/lux/tool/compiler/language/lux/phase/generation/scheme/extension/common.lux
+++ b/stdlib/source/lux/tool/compiler/language/lux/phase/generation/scheme/extension/common.lux
@@ -1,6 +1,5 @@
(.module:
[lux #*
- [host (#+ import:)]
[abstract
["." monad (#+ do)]]
[control
@@ -100,20 +99,6 @@
Binary
(///runtime.i64//logical-right-shift (_.remainder/2 (_.int +64) paramO) subjectO))
-(import: java/lang/Double
- (#static MIN_VALUE double)
- (#static MAX_VALUE double))
-
-(template [<name> <const> <encode>]
- [(def: (<name> _)
- Nullary
- (<encode> <const>))]
-
- [f64::smallest (Double::MIN_VALUE) _.float]
- [f64::min (f.* -1.0 (Double::MAX_VALUE)) _.float]
- [f64::max (Double::MAX_VALUE) _.float]
- )
-
(template [<name> <op>]
[(def: (<name> [subjectO paramO])
Binary
@@ -185,9 +170,6 @@
(bundle.install "%" (binary f64::%))
(bundle.install "=" (binary f64::=))
(bundle.install "<" (binary f64::<))
- (bundle.install "smallest" (nullary f64::smallest))
- (bundle.install "min" (nullary f64::min))
- (bundle.install "max" (nullary f64::max))
(bundle.install "i64" (unary _.exact/1))
(bundle.install "encode" (unary _.number->string/1))
(bundle.install "decode" (unary ///runtime.frac//decode)))))