aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/library
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib/source/library')
-rw-r--r--stdlib/source/library/lux/data/color/cmyk.lux2
-rw-r--r--stdlib/source/library/lux/data/color/hsb.lux52
-rw-r--r--stdlib/source/library/lux/data/color/hsl.lux2
-rw-r--r--stdlib/source/library/lux/ffi.lux484
-rw-r--r--stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/c++/runtime.lux63
-rw-r--r--stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/c++/type.lux26
-rw-r--r--stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/js/runtime.lux4
-rw-r--r--stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/jvm/debug.lux31
-rw-r--r--stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/jvm/runtime.lux4
-rw-r--r--stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/jvm/type.lux5
-rw-r--r--stdlib/source/library/lux/meta/target/c++.lux284
-rw-r--r--stdlib/source/library/lux/meta/target/jvm/type.lux47
-rw-r--r--stdlib/source/library/lux/meta/target/python.lux18
13 files changed, 734 insertions, 288 deletions
diff --git a/stdlib/source/library/lux/data/color/cmyk.lux b/stdlib/source/library/lux/data/color/cmyk.lux
index dc85a4a97..4f2b46238 100644
--- a/stdlib/source/library/lux/data/color/cmyk.lux
+++ b/stdlib/source/library/lux/data/color/cmyk.lux
@@ -68,7 +68,7 @@
(def up
(-> Frac
Nat)
- (|>> (f.* rgb_factor) f.int .nat))
+ (|>> (f.* rgb_factor) f.round f.int .nat))
(def (opposite it)
(-> Frac
diff --git a/stdlib/source/library/lux/data/color/hsb.lux b/stdlib/source/library/lux/data/color/hsb.lux
index ede1ffd08..5e7216de0 100644
--- a/stdlib/source/library/lux/data/color/hsb.lux
+++ b/stdlib/source/library/lux/data/color/hsb.lux
@@ -92,7 +92,7 @@
(def up
(-> Frac
Nat)
- (|>> (f.* rgb_factor) f.int .nat))
+ (|>> (f.* rgb_factor) f.round f.int .nat))
(def .public (of_rgb it)
(-> RGB
@@ -101,30 +101,36 @@
green (..down (the rgb.#green it))
blue (..down (the rgb.#blue it))
- max (all f.max red green blue)
- min (all f.min red green blue)
+ brightness (all f.max red green blue)
+ range (all f.min red green blue)
- brightness max
- diff (|> max (f.- min))
- saturation (if (f.= +0.0 max)
+ chroma (|> brightness (f.- range))
+ saturation (if (f.= +0.0 brightness)
+0.0
- (|> diff (f./ max)))]
+ (|> chroma (f./ brightness)))]
(nominal.abstraction
- [#hue (if (f.= max min)
- ... Achromatic
- +0.0
- ... Chromatic
- (cond (f.= max red)
- (|> green (f.- blue) (f./ diff)
- (f.+ (if (f.< blue green) +6.0 +0.0)))
-
- (f.= max green)
- (|> blue (f.- red) (f./ diff)
- (f.+ +2.0))
-
- ... (f.= max blue)
- (|> red (f.- green) (f./ diff)
- (f.+ +4.0))))
+ [#hue (cond (f.= +0.0 chroma)
+ ... Achromatic
+ +0.0
+ ... Chromatic
+ (and (f.= brightness red)
+ (not (f.= red blue)))
+ (|> green (f.- blue)
+ (f./ chroma)
+ (f.+ +0.0)
+ (f./ +6.0))
+
+ (f.= brightness green)
+ (|> blue (f.- red)
+ (f./ chroma)
+ (f.+ +2.0)
+ (f./ +6.0))
+
+ ... (f.= brightness blue)
+ (|> red (f.- green)
+ (f./ chroma)
+ (f.+ +4.0)
+ (f./ +6.0)))
#saturation saturation
#brightness brightness])))
@@ -140,7 +146,7 @@
t (|> +1.0 (f.- (|> +1.0 (f.- f) (f.* saturation))) (f.* brightness))
v brightness
mod (|> i (f.% +6.0) f.int .nat)
-
+
red (when mod 0 v 1 q 2 p 3 p 4 t 5 v _ (undefined))
green (when mod 0 t 1 v 2 v 3 q 4 p 5 p _ (undefined))
blue (when mod 0 p 1 p 2 t 3 v 4 v 5 q _ (undefined))]
diff --git a/stdlib/source/library/lux/data/color/hsl.lux b/stdlib/source/library/lux/data/color/hsl.lux
index df8fb8a82..ac0b637c8 100644
--- a/stdlib/source/library/lux/data/color/hsl.lux
+++ b/stdlib/source/library/lux/data/color/hsl.lux
@@ -28,7 +28,7 @@
(def up
(-> Frac
Nat)
- (|>> (f.* rgb_factor) f.int .nat))
+ (|>> (f.* rgb_factor) f.round f.int .nat))
(type .public Value
Frac)
diff --git a/stdlib/source/library/lux/ffi.lux b/stdlib/source/library/lux/ffi.lux
index 6d0f9d390..8afc76f04 100644
--- a/stdlib/source/library/lux/ffi.lux
+++ b/stdlib/source/library/lux/ffi.lux
@@ -1,13 +1,13 @@
(.require
[library
- [lux (.except Symbol Alias Global Declaration global function type_of undefined alias)
+ [lux (.except Symbol Alias Global Declaration Pattern global function type_of undefined alias)
[abstract
["[0]" monad (.only do)]]
[control
["<>" parser (.use "[1]#[0]" monad)]
["[0]" io]
["[0]" maybe (.use "[1]#[0]" functor)]
- ["[0]" try]]
+ ["[0]" try (.only Try)]]
[data
["[0]" product]
["[0]" text (.use "[1]#[0]" equivalence)
@@ -15,174 +15,324 @@
[collection
["[0]" list (.use "[1]#[0]" monoid monad mix)]]]
["[0]" meta (.only)
+ ["[0]" location]
["[0]" code (.only)
["<[1]>" \\parser (.only Parser)]]
["[0]" macro (.only with_symbols)
[syntax (.only syntax)]
["[0]" template]]
- [type
+ [type (.only sharing)
["[0]" nominal (.except #name def)]]
["@" target (.only)
- ["[0]" js]]]]])
-
-... These extensions must be defined this way because importing any of the modules
-... normally used when writing extensions would introduce a circular dependency
-... because the Archive type depends on Binary, and that module depends on this ffi module.
-(def extension_name
- (syntax (_ [])
- (do meta.monad
- [module meta.current_module_name
- unique_id meta.seed]
- (in (list (code.text (%.format module " " (%.nat unique_id))))))))
-
-(def extension_analysis
- (template (_ <name> <parameter>)
- [{5 #1 [<name> <parameter>]}]))
-
-(def text_analysis
- (template (_ <it>)
- [{0 #0 {5 #1 <it>}}]))
-
-(def analysis
- (template (_ <name> <bindings> <parser> <inputs> <body>)
- [("lux def analysis" <name>
- (.function (_ name phase archive inputs)
- (.function (_ state)
- (let [<bindings> [name phase archive state]]
- (when (<code>.result <parser> inputs)
- {try.#Failure error}
- {try.#Failure (%.format "Invalid inputs for extension: " (%.text name)
- text.\n error)}
-
- {try.#Success <inputs>}
- <body>)))))]))
-
-(def translation
- (template (_ <name> <bindings> <inputs> <body>)
- [("lux def translation" <name>
- (.function (_ name phase archive inputs)
- (.function (_ state)
- (let [<bindings> [name phase archive state]]
- (when inputs
- <inputs>
- <body>
-
- _
- {try.#Failure (%.format "Invalid inputs for extension: " (%.text name))})))))]))
-
-(for @.js (with_expansions [<undefined> (..extension_name)
- <undefined?> (..extension_name)
- <object> (..extension_name)
- <set> (..extension_name)]
- (these (analysis <undefined>
- [name phase archive state]
- <code>.end
- _
- {try.#Success [state (extension_analysis name (list))]})
-
- (translation <undefined>
- [name phase archive state]
+ ["[0]" js]
+ ["[0]" python]]
+ [compiler
+ [arity (.only Arity)]
+ [reference (.only Reference)
+ [variable (.only Register)]]
+ [language
+ [lux
+ ["[0]" analysis
+ ["[1]/[0]" simple]
+ [complex (.only Complex)]
+ [pattern (.only Pattern)]]
+ ["[0]" synthesis
+ ["[1]/[0]" simple]
+ [access (.only Access)
+ [side (.only Side)]
+ ["[1]/[0]" member]]]]]]]]])
+
+(for @.js (these (type (Analysis_Branch of)
+ [Pattern of])
+
+ (type (Analysis_Match of)
+ [(Analysis_Branch of) (List (Analysis_Branch of))])
+
+ (type (Environment of)
+ (List of))
+
+ (type (Extension of)
+ [.Symbol (List of)])
+
+ (with_expansions [@ ($ (Analysis~' $))]
+ (type (Analysis~' $)
+ (Or analysis/simple.Simple
+ (Complex @)
+ Reference
+ [@ (Analysis_Match @)]
+ [(Environment @) @]
+ [@ @]
+ (Extension @))))
+
+ (type Analysis~
+ (Ann Location
+ (Analysis~' (Ann Location))))
+
+ (def extension_analysis
+ (template (_ <name> <parameter>)
+ [(is Analysis~
+ [location.dummy {5 #1 [<name> <parameter>]}])]))
+
+ (def text_analysis
+ (template (_ <it>)
+ [(is Analysis~
+ [location.dummy {0 #0 {5 #1 <it>}}])]))
+
+ (def analysis
+ (template (_ <name> <bindings> <parser> <inputs> <body>)
+ [(def .public <name>
+ (<| (as .Analysis)
+ (.function (_ phase archive inputs))
+ (.function (_ state))
+ (let [<bindings> [phase archive state]]
+ (when (<code>.result <parser> inputs)
+ {try.#Success <inputs>}
+ <body>
+
+ {try.#Failure error}
+ {try.#Failure (%.format "Invalid inputs for extension..."
+ text.\n error)}))))]))
+
+ (type (Synthesis_Road value next)
+ [value next])
+
+ (type (Synthesis_Fork value next)
+ [(Synthesis_Road value next)
+ (List (Synthesis_Road value next))])
+
+ (type (Synthesis_Path s)
+ (Or Any
+ Register
+ Access
+ [Bit (Synthesis_Path s) (Maybe (Synthesis_Path s))]
+ (Synthesis_Fork I64 (Synthesis_Path s))
+ (Synthesis_Fork Frac (Synthesis_Path s))
+ (Synthesis_Fork Text (Synthesis_Path s))
+ [(Synthesis_Path s) (Synthesis_Path s)]
+ [(Synthesis_Path s) (Synthesis_Path s)]
+ s))
+
+ (type (Synthesis_Abstraction s)
+ [(Environment s) Arity s])
+
+ (type (Synthesis_Apply s)
+ [s (List s)])
+
+ (type (Synthesis_Function s)
+ (Or (Synthesis_Abstraction s)
+ (Synthesis_Apply s)))
+
+ (type (Synthesis_Branch s)
+ (Or [s s]
+ [s Register s]
+ [s s s]
+ [(List synthesis/member.Member) s]
+ [s (Synthesis_Path s)]))
+
+ (type (Synthesis_Scope s)
+ [Register (List s) s])
+
+ (type (Synthesis_Loop s)
+ (Or (Synthesis_Scope s)
+ (List s)))
+
+ (type (Synthesis_Control s)
+ (Or (Synthesis_Branch s)
+ (Synthesis_Loop s)
+ (Synthesis_Function s)))
+
+ (with_expansions [@ ($ (Synthesis~' $))]
+ (type (Synthesis~' $)
+ (Or synthesis/simple.Simple
+ (Complex @)
+ Reference
+ (Synthesis_Control @)
+ (Extension @))))
+
+ (type Synthesis~
+ (Ann Location
+ (Synthesis~' (Ann Location))))
+
+ (def text_synthesis
+ (template (_ <@> <it>)
+ [[<@> {0 #0 {2 #1 <it>}}]]))
+
+ (def translation
+ (syntax (_ [<name> <code>.any
+ <bindings> <code>.any
+ <inputs> (<>.or <code>.local
+ <code>.any)
+ <body> <code>.any])
+ (with_symbols ['_ 'phase 'archive 'inputs 'state]
+ (in (list (` (def .public (, <name>)
+ (<| (as .Translation)
+ (.function ((, '_) (, 'phase) (, 'archive) (, 'inputs)))
+ (.function ((, '_) (, 'state)))
+ (let [(, <bindings>) [(, 'phase) (, 'archive) (, 'state)]]
+ (, (when <inputs>
+ {.#Left <inputs>}
+ (` (when (is (List Synthesis~) (, 'inputs))
+ (, (code.local <inputs>))
+ (, <body>)))
+
+ {.#Right <inputs>}
+ (` (when (is (List Synthesis~) (, 'inputs))
+ (, <inputs>)
+ (, <body>)
+
+ (, '_)
+ {try.#Failure "Invalid inputs for extension."})))))))))))))
+
+ (translation undefined?|translation
+ [phase archive state]
+ (list it)
+ (do try.monad
+ [.let [phase (sharing [archive it state]
+ (is [archive it state]
+ [archive it state])
+ (is (-> archive it state
+ (Try [state js.Expression]))
+ (as_expected phase)))]
+ [state it] (phase archive it state)]
+ (in [state (js.= js.undefined it)])))
+
+ (analysis undefined?|analysis
+ [phase archive state]
+ <code>.any
+ it
+ (do try.monad
+ [.let [phase (sharing [archive state]
+ (is [archive state]
+ [archive state])
+ (is (-> archive Code state
+ (Try [state Analysis~]))
+ (as_expected phase)))]
+ [state it] (phase archive (` (.is .Any (, it))) state)]
+ (in [state (extension_analysis (symbol ..undefined?|translation)
+ (list it))])))
+
+ (def .public undefined?
+ (template (undefined? <it>)
+ [(.as .Bit (.is .Any (undefined?|analysis <it>)))]))
+
+ (translation undefined|translation
+ [phase archive state]
+ (list)
+ {try.#Success [state js.undefined]})
+
+ (analysis undefined|analysis
+ [phase archive state]
+ <code>.end
+ _
+ {try.#Success [state (extension_analysis (symbol ..undefined|translation)
+ (list))]})
+
+ (def .public undefined
+ (template (_)
+ [(.is ..Undefined (undefined|analysis))]))
+
+ (def (pairs it)
+ (All (_ a) (-> (List a) (List [a a])))
+ (when it
+ (list.partial left right tail)
+ (list.partial [left right] (pairs tail))
+
(list)
- {try.#Success [state js.undefined]})
-
- (def .public undefined
- (template (undefined)
- [(.is ..Undefined (<undefined>))]))
-
- (analysis <undefined?>
- [name phase archive state]
- <code>.any
- it
- (do try.monad
- [[state it] (phase archive (` (.is .Any (, it))) state)]
- (in [state (extension_analysis name (list it))])))
-
- (translation <undefined?>
- [name phase archive state]
- (list it)
- (do try.monad
- [[state it] (phase archive it state)]
- (in [state (js.= js.undefined it)])))
-
- (def .public undefined?
- (template (undefined? <it>)
- [(.as .Bit (.is .Any (<undefined?> <it>)))]))
-
- (analysis <object>
- [name phase archive state]
- (<>.some (<>.and <code>.text <code>.any))
- it
- (do [! try.monad]
- [[state output] (monad.mix ! (.function (_ [key value] [state output])
- (do !
- [[state value] (phase archive (` (.is .Any (, value))) state)]
- (in [state (list.partial value (text_analysis key) output)])))
- [state (list)]
- it)]
- (in [state (extension_analysis name (list.reversed output))])))
-
- (def text_synthesis
- (template (_ <it>)
- [{0 #0 {2 #1 <it>}}]))
-
- (def (pairs it)
- (All (_ a) (-> (List a) (List [a a])))
- (when it
- (list.partial left right tail)
- (list.partial [left right] (pairs tail))
-
- (list)
- (list)
-
- _
- (.undefined)))
-
- (translation <object>
- [name phase archive state]
- (list.partial head_key head_value tail)
- (do [! try.monad]
- [[state output] (monad.mix !
- (.function (_ [key value] [state output])
- (when key
- (text_synthesis key)
- (do try.monad
- [[state value] (phase archive value state)]
- (in [state (list.partial [key value] output)]))
-
- _
- (.undefined)))
- [state (list)]
- (pairs (list.partial head_key head_value tail)))]
- (in [state (js.object (list.reversed output))])))
-
- (def .public object
- (syntax (_ [it (<>.some <code>.any)])
- (in (list (` (.as (..Object .Any)
- (<object> (,* it))))))))
-
- (analysis <set>
- [name phase archive state]
- (all <>.and <code>.text <code>.any <code>.any)
- [field value object]
- (do try.monad
- [[state value] (phase archive (` (.is .Any (, value))) state)
- [state object] (phase archive (` (.is (..Object .Any) (, object))) state)]
- (in [state (extension_analysis name (list (text_analysis field) value object))])))
-
- (translation <set>
- [name phase archive state]
- (list (text_synthesis field) value object)
- (do try.monad
- [[state value] (phase archive value state)
- [state object] (phase archive object state)]
- (in [state (js.set (js.the field object) value)])))
-
- (def .public set
- (syntax (_ [field <code>.any
- value <code>.any
- object <code>.any])
- (in (list (` (.as .Any (<set> (, field) (, value) (, object))))))))
- ))
+ (list)
+
+ _
+ (.undefined)))
+
+ (translation object|translation
+ [phase archive state]
+ it
+ (do [! try.monad]
+ [.let [phase (sharing [archive state]
+ (is [archive state]
+ [archive state])
+ (is (-> archive Synthesis~ state
+ (Try [state js.Expression]))
+ (as_expected phase)))]
+ [state output] (monad.mix !
+ (sharing [state]
+ (is state
+ state)
+ (is (-> [Synthesis~ Synthesis~] [state (List [Text js.Expression])]
+ (Try [state (List [Text js.Expression])]))
+ (.function (_ [key value] [state output])
+ (when key
+ (text_synthesis @ key)
+ (do try.monad
+ [[state value] (phase archive value state)]
+ (in [state (list.partial [key value] output)]))
+
+ _
+ (.undefined)))))
+ [state (list)]
+ (pairs it))]
+ (in [state (js.object (list.reversed output))])))
+
+ (analysis object|analysis
+ [phase archive state]
+ (<>.some (<>.and <code>.text <code>.any))
+ it
+ (do [! try.monad]
+ [.let [phase (sharing [archive state]
+ (is [archive state]
+ [archive state])
+ (is (-> archive Code state
+ (Try [state Analysis~]))
+ (as_expected phase)))]
+ [state output] (monad.mix ! (.function (_ [key value] [state output])
+ (do !
+ [[state value] (phase archive (` (.is .Any (, value))) state)]
+ (in [state (list.partial value (text_analysis key) output)])))
+ [state (list)]
+ it)]
+ (in [state (extension_analysis (symbol ..object|translation)
+ (list.reversed output))])))
+
+ (def .public object
+ (syntax (_ [it (<>.some <code>.any)])
+ (in (list (` (.as (..Object .Any)
+ (object|analysis (,* it))))))))
+
+ (translation set|translation
+ [phase archive state]
+ (list (text_synthesis @ field) value object)
+ (do try.monad
+ [.let [phase (sharing [archive state]
+ (is [archive state]
+ [archive state])
+ (is (-> archive Synthesis~ state
+ (Try [state js.Expression]))
+ (as_expected phase)))]
+ [state value] (phase archive value state)
+ [state object] (phase archive object state)]
+ (in [state (js.set (js.the field object) value)])))
+
+ (analysis set|analysis
+ [phase archive state]
+ (all <>.and <code>.text <code>.any <code>.any)
+ [field value object]
+ (do try.monad
+ [.let [phase (sharing [archive state]
+ (is [archive state]
+ [archive state])
+ (is (-> archive Code state
+ (Try [state Analysis~]))
+ (as_expected phase)))]
+ [state value] (phase archive (` (.is .Any (, value))) state)
+ [state object] (phase archive (` (.is (..Object .Any) (, object))) state)]
+ (in [state (extension_analysis (symbol ..set|translation)
+ (list (text_analysis field) value object))])))
+
+ (def .public set
+ (syntax (_ [field <code>.any
+ value <code>.any
+ object <code>.any])
+ (in (list (` (.as .Any (set|analysis (, field) (, value) (, object))))))))
+ )
... else
(these))
@@ -217,7 +367,7 @@
@.python .python_function#
@.lua .lua_function#
(these))]
- (nominal.def .public (Object brand) Any)
+ (nominal.def .public (Object of) Any)
(with_expansions [<un_common> (for @.js (these [Symbol]
[Null]
@@ -229,12 +379,12 @@
@.ruby (these [Nil]))
<un_common> <un_common>]
(with_template [<name>]
- [(with_expansions [<brand> (template.symbol [<name> "'"])]
- (nominal.def <brand>
+ [(with_expansions [<of> (template.symbol [<name> "'"])]
+ (nominal.def <of>
Any
(type .public <name>
- (Object <brand>))))]
+ (Object <of>))))]
[Function]
<un_common>
@@ -510,7 +660,7 @@
(def (input_type input :it:)
(-> Input Code Code)
(let [:it: (if (the #try? input)
- (` (try.Try (, :it:)))
+ (` (Try (, :it:)))
:it:)]
(if (the #io? input)
(` (io.IO (, :it:)))
diff --git a/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/c++/runtime.lux b/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/c++/runtime.lux
new file mode 100644
index 000000000..7e29191ac
--- /dev/null
+++ b/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/c++/runtime.lux
@@ -0,0 +1,63 @@
+(.require
+ [library
+ [lux (.except)
+ [data
+ [text
+ ["%" \\format]]]
+ ["[0]" meta (.use "[1]#[0]" functor)
+ ["[0]" code]
+ [macro
+ [syntax (.only syntax)]]
+ [target
+ ["_" c++]]]]])
+
+(def .public (host_value of it)
+ (-> _.Type _.Expression
+ _.Expression)
+ (|> it
+ (_.do "get" (list) (list))
+ (_.as (_.* of))))
+
+(def .public namespace
+ _.Namespace
+ "lux")
+
+(def name
+ (syntax (_ [])
+ (|> meta.seed
+ (meta#each (|>> %.nat
+ (%.format ..namespace)
+ code.text
+ list)))))
+
+(with_expansions [<clean_up> (..name)]
+ (def .public declaration
+ _.Declaration
+ (let [clean_up (let [of (_.type_name "Of")
+ it (_.local "it")]
+ (_.function (_.local <clean_up>)
+ (list of)
+ (list [(_.* of) it])
+ _.void
+ (_.delete it)))]
+ (all _.then
+ (_.include "memory")
+
+ (<| (_.namespace ..namespace)
+ (all _.then
+ clean_up
+ )))))
+
+ (def .public clean_up
+ (-> _.Type
+ _.Expression)
+ (|>> (list)
+ (_.global [..namespace <clean_up>])))
+ )
+
+(def .public (lux_value of it)
+ (-> _.Type _.Expression
+ _.Expression)
+ (_.on (list (_.new of (list it))
+ (clean_up of))
+ (_.global [_.standard "shared_ptr"] (list _.void))))
diff --git a/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/c++/type.lux b/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/c++/type.lux
new file mode 100644
index 000000000..f091e288f
--- /dev/null
+++ b/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/c++/type.lux
@@ -0,0 +1,26 @@
+(.require
+ [library
+ [lux (.except i64)
+ [meta
+ [target
+ ["_" c++]]]]])
+
+(def .public bit
+ _.Type
+ (_.type ["" "bool"] (list)))
+
+(def .public i64
+ _.Type
+ (_.type ["" "int64_t"] (list)))
+
+(def .public f64
+ _.Type
+ (_.type ["" "double"] (list)))
+
+(def .public text
+ _.Type
+ (_.type [_.standard "u32string"] (list)))
+
+(def .public value
+ _.Type
+ (_.type [_.standard "shared_ptr"] (list (_.type ["" "void"] (list)))))
diff --git a/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/js/runtime.lux b/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/js/runtime.lux
index dbd9f5c45..13790c910 100644
--- a/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/js/runtime.lux
+++ b/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/js/runtime.lux
@@ -258,7 +258,7 @@
(lux//try op)
(with_vars [ex]
(_.try (_.return (..right (_.apply_1 op ..unit)))
- [ex (_.return (..left (|> ex (_.do "toString" (list)))))])))
+ [ex (_.return (..left (_.the "stack" ex)))])))
(runtime
(lux//program_args inputs)
@@ -751,7 +751,7 @@
(runtime
(io//error message)
- (_.throw message))
+ (_.throw (_.new (_.var "Error") (list message))))
(def runtime//io
Statement
diff --git a/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/jvm/debug.lux b/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/jvm/debug.lux
deleted file mode 100644
index 1d6adf5f6..000000000
--- a/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/jvm/debug.lux
+++ /dev/null
@@ -1,31 +0,0 @@
-(.require
- [library
- [lux (.except)
- [abstract
- [monad (.only do)]]
- [control
- ["[0]" io (.only IO)]
- ["[0]" try (.only Try)]]
- [data
- [binary (.only Binary)]
- [text
- ["%" \\format (.only format)]]]
- [world
- ["[0]" file (.only File)]]]])
-
-(def extension ".class")
-
-(def .public (write_class! name bytecode)
- (-> Text Binary (IO Text))
- (let [file_path (format name ..extension)]
- (do io.monad
- [outcome (do (try.with @)
- [file (is (IO (Try (File IO)))
- (file.get_file io.monad file.default file_path))]
- (of file over_write bytecode))]
- (in (when outcome
- {try.#Success definition}
- file_path
-
- {try.#Failure error}
- error)))))
diff --git a/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/jvm/runtime.lux b/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/jvm/runtime.lux
index 297504638..af848be72 100644
--- a/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/jvm/runtime.lux
+++ b/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/jvm/runtime.lux
@@ -375,7 +375,7 @@
_.areturn
))}))
-(def projection_type (type.method [(list) (list //type.tuple //type.offset) //type.value (list)]))
+(def projection_type (type.method [(list) (list //type.tuple //type.lefts) //type.value (list)]))
(def left_projection::name "left")
(def .public left_projection (..procedure ..left_projection::name ..projection_type))
@@ -452,7 +452,7 @@
$right
$tuple::size
(_.invokestatic (type.class "java.util.Arrays" (list)) "copyOfRange"
- (type.method [(list) (list //type.tuple //type.index //type.index) //type.tuple (list)])))]]
+ (type.method [(list) (list //type.tuple //type.lefts //type.lefts) //type.tuple (list)])))]]
(all _.composite
(_.set_label @loop)
$last_right $right
diff --git a/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/jvm/type.lux b/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/jvm/type.lux
index c178701b3..329c0a02f 100644
--- a/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/jvm/type.lux
+++ b/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/jvm/type.lux
@@ -8,17 +8,12 @@
(def .public frac (type.class "java.lang.Double" (list)))
(def .public text (type.class "java.lang.String" (list)))
-
(def .public value (type.class "java.lang.Object" (list)))
(def .public lefts type.int)
(def .public right? ..value)
(def .public variant (type.array ..value))
-
-(def .public offset type.int)
-(def .public index ..offset)
(def .public tuple (type.array ..value))
(def .public stack (type.array ..value))
-
(def .public error (type.class "java.lang.Throwable" (list)))
diff --git a/stdlib/source/library/lux/meta/target/c++.lux b/stdlib/source/library/lux/meta/target/c++.lux
index b8c2414f4..952cc0c0b 100644
--- a/stdlib/source/library/lux/meta/target/c++.lux
+++ b/stdlib/source/library/lux/meta/target/c++.lux
@@ -1,10 +1,12 @@
(.require
[library
- [lux (.except Code Type int)
+ [lux (.except Code Type Global Declaration int as function template local global type)
+ [abstract
+ [equivalence (.only Equivalence)]]
[control
["|" pipe]]
[data
- ["[0]" text (.only)
+ ["[0]" text (.only \n \t) (.use "[1]#[0]" equivalence)
["%" \\format]]
[collection
["[0]" list (.use "[1]#[0]" functor)]]]
@@ -17,32 +19,60 @@
[type
["[0]" nominal]]]]])
+(def parameter_separator ", ")
+(def term_delimiters ["(" ")"])
+(def type_delimiters ["<" ">"])
+
(nominal.def .public (Code of)
Text
+ (def .public equivalence
+ (All (_ of)
+ (Equivalence (Code of)))
+ (implementation
+ (def (= refererence it)
+ (text#= (nominal.representation refererence)
+ (nominal.representation it)))))
+
(def .public code
(-> (Code Any)
Text)
(|>> nominal.representation))
- (with_template [<type> <super>+]
- [(with_expansions [<of> (template.symbol [<type> "'"])]
- (nominal.def (<of> of)
- Any)
- (`` (type .public <type>
- (|> Any <of> (,, (template.spliced <super>+))))))]
+ (with_template [<super> <type>+]
+ [(`` (with_template [<type> <parameter>*']
+ [(with_expansions [<parameter>* (template.spliced <parameter>*')
+ <brand> (template.symbol [<type> "'"])]
+ (nominal.def (<brand> <parameter>*)
+ Any)
+
+ (.type .public <type>
+ (Ex (_ <parameter>*)
+ (<super> (<brand> <parameter>*)))))]
- [Type [Code]]
- [Expression [Code]]
- [Computation [Expression' Code]]
- )
+ (,, (template.spliced <type>+))))]
+
+ [Code
+ [[Type [of]]
+ [Expression [of]]
+ [Statement [of]]]]
+
+ [Expression
+ [[Computation [of]]
+ [Reference [of]]]]
+
+ [Type
+ [[Type_Name []]]]
- (with_template [<type> <super>+]
- [(with_expansions [<brand> (template.symbol [<type> "'"])]
- (nominal.def <brand> Any)
- (`` (type .public <type> (|> <brand> (,, (template.spliced <super>+))))))]
+ [Computation
+ [[Literal []]]]
- [Literal [Computation' Expression' Code]]
+ [Reference
+ [[Local []]
+ [Global []]]]
+
+ [Statement
+ [[Declaration []]]]
)
(def .public bool
@@ -69,7 +99,74 @@
[%.frac])
nominal.abstraction))
- (def .public (cast type term)
+ (.type .public Namespace
+ Text)
+
+ (def .public standard
+ Namespace
+ "std")
+
+ (def .public local
+ (-> Text
+ Local)
+ (|>> nominal.abstraction))
+
+ (def instantiation
+ (-> (List Type)
+ Text)
+ (|>> (|.when
+ (list)
+ ""
+
+ it
+ (|> it
+ (list#each ..code)
+ (text.interposed ..parameter_separator)
+ (text.enclosed ..type_delimiters)))))
+
+ (def .public (global [ns name] parameters)
+ (-> [Namespace Text] (List Type)
+ Global)
+ (nominal.abstraction
+ (let [instance (%.format name (instantiation parameters))]
+ (when ns
+ "" instance
+ _ (%.format ns "::" instance)))))
+
+ (def .public (type name parameters)
+ (-> [Namespace Text] (List Type)
+ Type)
+ (|> (..global name parameters)
+ nominal.transmutation))
+
+ (def .public type_name
+ (-> Text
+ Type_Name)
+ (|>> nominal.abstraction))
+
+ (with_template [<ns> <name>]
+ [(def .public <name>
+ Type
+ (..type [<ns> (template.text [<name>])] (list)))]
+
+ ["" void]
+ )
+
+ (def .public *
+ (-> Type
+ Type)
+ (|>> nominal.representation
+ (text.suffix "*")
+ nominal.abstraction))
+
+ (def .public deref
+ (-> Expression
+ Expression)
+ (|>> nominal.representation
+ (text.prefix "*")
+ nominal.abstraction))
+
+ (def .public (as type term)
(-> Type Expression
Computation)
(nominal.abstraction
@@ -82,16 +179,135 @@
(|>> %.int
nominal.abstraction))
+ (def application
+ (-> (List Expression)
+ Text)
+ (|>> (list#each ..code)
+ (text.interposed ..parameter_separator)
+ (text.enclosed ..term_delimiters)))
+
(def .public (on parameters function)
(-> (List Expression) Expression
Expression)
(nominal.abstraction
(%.format (nominal.representation function)
- "("
- (|> parameters
- (list#each (|>> nominal.representation))
- (text.interposed ", "))
- ")")))
+ (application parameters))))
+
+ (def .public (new of parameters)
+ (-> Type (List Expression)
+ Expression)
+ (nominal.abstraction
+ (%.format "new "
+ (nominal.representation of)
+ (application parameters))))
+
+ (def .public (do method types parameters object)
+ (-> Text (List Type) (List Expression) Expression
+ Expression)
+ (nominal.abstraction
+ (%.format (nominal.representation object)
+ "." method
+ (instantiation types)
+ (application parameters))))
+
+ (def .public (<< it to)
+ (-> Expression Expression
+ Expression)
+ (nominal.abstraction
+ (%.format (nominal.representation to)
+ " << "
+ (nominal.representation it))))
+
+ (def .public (include it)
+ (-> Text
+ Declaration)
+ (nominal.abstraction
+ (%.format "#include <" it ">")))
+
+ (def .public (then before after)
+ (All (_ of)
+ (-> (Statement of) (Statement of)
+ (Statement of)))
+ (nominal.abstraction
+ (%.format (nominal.representation before)
+ \n (nominal.representation after))))
+
+ (def statement
+ (-> Text
+ Statement)
+ (|>> (text.suffix ";")
+ nominal.abstraction))
+
+ (def .public ;
+ (-> Expression
+ Statement)
+ (|>> nominal.representation
+ ..statement))
+
+ (def .public delete
+ (-> Expression
+ Statement)
+ (|>> nominal.representation
+ (%.format "delete ")
+ ..statement))
+
+ (def template
+ (-> (List Type_Name)
+ Text)
+ (|>> (|.when
+ (list)
+ ""
+
+ it
+ (%.format "template"
+ " " (|> it
+ (list#each (|>> nominal.representation (%.format "typename ")))
+ (text.interposed ..parameter_separator)
+ (text.enclosed ..type_delimiters))
+ " "))))
+
+ (.type Argument
+ [Type Local])
+
+ (def (argument [type it])
+ (-> Argument
+ Text)
+ (%.format (nominal.representation type)
+ " " (nominal.representation it)))
+
+ (def arguments
+ (-> (List Argument)
+ Text)
+ (|>> (list#each ..argument)
+ (text.interposed ..parameter_separator)
+ (text.enclosed ..term_delimiters)))
+
+ (def block
+ (-> Statement
+ Text)
+ (let [\n\t (%.format \n \t)
+ <| (%.format "{" \n)
+ |> (%.format \n "}")]
+ (|>> nominal.representation
+ (text.replaced \n \n\t)
+ (text.enclosed [<| |>]))))
+
+ (def .public (function name types inputs output body)
+ (-> Local (List Type_Name) (List Argument) Type Statement
+ Declaration)
+ (nominal.abstraction
+ (%.format (..template types) (nominal.representation output)
+ " " (nominal.representation name)
+ (..arguments inputs)
+ " " (..block body))))
+
+ (def .public (namespace it body)
+ (-> Namespace Declaration
+ Declaration)
+ (nominal.abstraction
+ (%.format "namespace"
+ " " it
+ " " (..block body))))
... https://en.cppreference.com/w/cpp/types/integer
(with_template [<name>]
@@ -104,11 +320,31 @@
[int64_t]
)
+ (def safe
+ (-> Text
+ Text)
+ (let [\\'' (%.format "\" text.\'')]
+ (`` (|>> (,, (with_template [<find> <replace>]
+ [(text.replaced <find> <replace>)]
+
+ ["\" "\\"]
+ [text.\t "\t"]
+ [text.\v "\v"]
+ [text.\0 "\0"]
+ [text.\b "\b"]
+ [text.\f "\f"]
+ [text.\n "\n"]
+ [text.\r "\r"]
+ [text.\'' \\'']
+ ))
+ ))))
+
... https://en.cppreference.com/w/cpp/string/basic_string
(def .public u32string
(-> Text
Literal)
- (|>> %.text
+ (|>> ..safe
+ %.text
(%.format "U")
nominal.abstraction))
)
diff --git a/stdlib/source/library/lux/meta/target/jvm/type.lux b/stdlib/source/library/lux/meta/target/jvm/type.lux
index 0eff5b048..e1cbb4374 100644
--- a/stdlib/source/library/lux/meta/target/jvm/type.lux
+++ b/stdlib/source/library/lux/meta/target/jvm/type.lux
@@ -45,7 +45,9 @@
(with_template [<name> <style>]
[(def .public (<name> type)
- (All (_ category) (-> (Type category) (<style> category)))
+ (All (_ category)
+ (-> (Type category)
+ (<style> category)))
(let [[signature descriptor reflection] (representation type)]
<name>))]
@@ -77,28 +79,32 @@
)
(def .public (array type)
- (-> (Type Value) (Type Array))
+ (-> (Type Value)
+ (Type Array))
(abstraction
[(/signature.array (..signature type))
(/descriptor.array (..descriptor type))
(/reflection.array (..reflection type))]))
(def .public (class name parameters)
- (-> External (List (Type Parameter)) (Type Class))
+ (-> External (List (Type Parameter))
+ (Type Class))
(abstraction
[(/signature.class name (list#each ..signature parameters))
(/descriptor.class name)
(/reflection.class name)]))
(def .public (declaration name variables)
- (-> External (List (Type Var)) (Type Declaration))
+ (-> External (List (Type Var))
+ (Type Declaration))
(abstraction
[(/signature.declaration name (list#each ..signature variables))
(/descriptor.declaration name)
(/reflection.declaration name)]))
(def .public (as_class type)
- (-> (Type Declaration) (Type Class))
+ (-> (Type Declaration)
+ (Type Class))
(abstraction
(let [[signature descriptor reflection] (representation type)]
[(/signature.as_class signature)
@@ -113,14 +119,16 @@
/reflection.wildcard]))
(def .public (var name)
- (-> Text (Type Var))
+ (-> Text
+ (Type Var))
(abstraction
[(/signature.var name)
/descriptor.var
/reflection.var]))
(def .public (lower bound)
- (-> (Type Parameter) (Type Parameter))
+ (-> (Type Parameter)
+ (Type Parameter))
(abstraction
(let [[signature descriptor reflection] (representation bound)]
[(/signature.lower signature)
@@ -128,7 +136,8 @@
(/reflection.lower reflection)])))
(def .public (upper bound)
- (-> (Type Parameter) (Type Parameter))
+ (-> (Type Parameter)
+ (Type Parameter))
(abstraction
(let [[signature descriptor reflection] (representation bound)]
[(/signature.upper signature)
@@ -151,7 +160,8 @@
(as_expected ..void)]))
(def .public equivalence
- (All (_ category) (Equivalence (Type category)))
+ (All (_ category)
+ (Equivalence (Type category)))
(implementation
(def (= parameter subject)
(of /signature.equivalence =
@@ -159,14 +169,16 @@
(..signature subject)))))
(def .public hash
- (All (_ category) (Hash (Type category)))
+ (All (_ category)
+ (Hash (Type category)))
(implementation
(def equivalence ..equivalence)
(def hash (|>> ..signature (of /signature.hash hash)))))
(def .public (primitive? type)
- (-> (Type Value) (Either (Type Object)
- (Type Primitive)))
+ (-> (Type Value)
+ (Either (Type Object)
+ (Type Primitive)))
(if (`` (or (,, (with_template [<type>]
[(of ..equivalence = (is (Type Value) <type>) type)]
@@ -182,8 +194,9 @@
(|> type (as (Type Object)) {.#Left})))
(def .public (void? type)
- (-> (Type Return) (Either (Type Value)
- (Type Void)))
+ (-> (Type Return)
+ (Either (Type Value)
+ (Type Void)))
(if (`` (or (,, (with_template [<type>]
[(of ..equivalence = (is (Type Return) <type>) type)]
@@ -193,7 +206,8 @@
)
(def .public (class? type)
- (-> (Type Value) (Maybe External))
+ (-> (Type Value)
+ (Maybe External))
(let [repr (|> type ..descriptor /descriptor.descriptor)]
(if (and (text.starts_with? /descriptor.class_prefix repr)
(text.ends_with? /descriptor.class_suffix repr))
@@ -208,5 +222,6 @@
{.#None})))
(def .public format
- (All (_ a) (Format (Type a)))
+ (All (_ of)
+ (Format (Type of)))
(|>> ..signature /signature.signature))
diff --git a/stdlib/source/library/lux/meta/target/python.lux b/stdlib/source/library/lux/meta/target/python.lux
index a6d0968c5..c1c8fe105 100644
--- a/stdlib/source/library/lux/meta/target/python.lux
+++ b/stdlib/source/library/lux/meta/target/python.lux
@@ -1,7 +1,6 @@
(.require
[library
[lux (.except Location Code not or and list if int comment exec try the is def when)
- ["[0]" ffi]
[abstract
[equivalence (.only Equivalence)]
[hash (.only Hash)]
@@ -18,7 +17,6 @@
["n" nat]
["f" frac]]]
[meta
- ["@" target]
["[0]" code (.only)
["<[1]>" \\parser]]
[macro
@@ -34,14 +32,6 @@
(-> Text Text)
(text.enclosed ["(" ")"]))
-(for @.old (these (ffi.import java/lang/CharSequence
- "[1]::[0]")
-
- (ffi.import java/lang/String
- "[1]::[0]"
- (replace [java/lang/CharSequence java/lang/CharSequence] java/lang/String)))
- (these))
-
... Added the carriage return for better Windows compatibility.
(.def \n+
Text
@@ -50,12 +40,8 @@
(.def nested
(-> Text Text)
(.let [nested_new_line (format text.new_line text.tab)]
- (for @.old (|>> (format \n+)
- (as java/lang/String)
- (java/lang/String::replace (as java/lang/CharSequence text.new_line)
- (as java/lang/CharSequence nested_new_line)))
- (|>> (format \n+)
- (text.replaced text.new_line nested_new_line)))))
+ (|>> (format \n+)
+ (text.replaced text.new_line nested_new_line))))
(nominal.def .public (Code brand)
Text