aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/lux/debug.lux
diff options
context:
space:
mode:
Diffstat (limited to '')
-rw-r--r--stdlib/source/lux/debug.lux95
1 files changed, 57 insertions, 38 deletions
diff --git a/stdlib/source/lux/debug.lux b/stdlib/source/lux/debug.lux
index d0ceb4b5e..962ffeefe 100644
--- a/stdlib/source/lux/debug.lux
+++ b/stdlib/source/lux/debug.lux
@@ -3,6 +3,7 @@
["@" target]
["." type]
["." ffi (#+ import:)]
+ ["." meta]
[abstract
["." monad (#+ do)]]
[control
@@ -23,7 +24,6 @@
["." array]
["." list ("#\." functor)]
["." dictionary]]]
- ["." meta]
[macro
["." template]
["." syntax (#+ syntax:)]
@@ -31,6 +31,7 @@
[math
[number
[ratio (#+ Ratio)]
+ ["n" nat]
["i" int]]]
[time (#+ Time)
[instant (#+ Instant)]
@@ -95,7 +96,8 @@
(import: Object
["#::."
- (type [] Class)]))
+ (class [] Class)
+ (to_s [] ffi.String)]))
@.php
(as_is (import: (gettype [.Any] ffi.String))
@@ -116,13 +118,26 @@
(def: Inspector
(.type (Format Any)))
+(for {@.lua (def: (tuple_array tuple)
+ (-> (array.Array Any) (array.Array Any))
+ (array.from_list
+ (loop [idx 0]
+ (let [member ("lua array read" idx tuple)]
+ (if ("lua object nil?" member)
+ #.Nil
+ (#.Cons member (recur (inc idx))))))))}
+ (as_is))
+
(def: (inspect_tuple inspect)
(-> Inspector Inspector)
- (|>> (:coerce (array.Array Any))
- array.to_list
- (list\map inspect)
- (text.join_with " ")
- (text.enclose ["[" "]"])))
+ (with_expansions [<adaption> (for {@.lua (~~ (as_is ..tuple_array))}
+ (~~ (as_is)))]
+ (`` (|>> (:coerce (array.Array Any))
+ <adaption>
+ array.to_list
+ (list\map inspect)
+ (text.join_with " ")
+ (text.enclose ["[" "]"])))))
(def: #export (inspect value)
Inspector
@@ -201,19 +216,19 @@
@.python
(case (..str (..type value))
- (^template [<type_of> <then>]
- [<type_of>
+ (^template [<type_of> <class_of> <then>]
+ [(^or <type_of> <class_of>)
(`` (|> value (~~ (template.splice <then>))))])
- (["<type 'bool'>" [(:coerce .Bit) %.bit]]
- ["<type 'int'>" [(:coerce .Int) %.int]]
- ["<type 'float'>" [(:coerce .Frac) %.frac]]
- ["<type 'str'>" [(:coerce .Text) %.text]]
- ["<type 'unicode'>" [(:coerce .Text) %.text]])
+ (["<type 'bool'>" "<class 'bool'>" [(:coerce .Bit) %.bit]]
+ ["<type 'int'>" "<class 'int'>" [(:coerce .Int) %.int]]
+ ["<type 'float'>" "<class 'float'>" [(:coerce .Frac) %.frac]]
+ ["<type 'str'>" "<class 'str'>" [(:coerce .Text) %.text]]
+ ["<type 'unicode'>" "<class 'unicode'>" [(:coerce .Text) %.text]])
- "<type 'list'>"
+ (^or "<type 'list'>" "<class 'list'>")
(inspect_tuple inspect value)
- "<type 'tuple'>"
+ (^or "<type 'tuple'>" "<type 'tuple'>")
(let [variant (:coerce (array.Array Any) value)]
(case (array.size variant)
3 (let [variant_tag ("python array read" 0 variant)
@@ -252,31 +267,37 @@
(let [variant_tag ("lua object get" "_lux_tag" value)
variant_flag ("lua object get" "_lux_flag" value)
variant_value ("lua object get" "_lux_value" value)]
- (if (not (or ("lua object nil?" variant_tag)
- ("lua object nil?" variant_flag)
- ("lua object nil?" variant_value)))
+ (if (or ("lua object nil?" variant_tag)
+ ("lua object nil?" variant_value))
+ (inspect_tuple inspect value)
(|> (%.format (|> variant_tag (:coerce .Nat) %.nat)
" " (%.bit (not ("lua object nil?" variant_flag)))
" " (inspect variant_value))
- (text.enclose ["(" ")"]))
- (inspect_tuple inspect value)))
+ (text.enclose ["(" ")"]))))
_
(..tostring value))
@.ruby
- (template.with [(class_of <literal>)
- [(Object::type (:coerce ..Object <literal>))]]
- (let [value_class (Object::type (:coerce ..Object value))]
+ (template.let [(class_of <literal>)
+ [(|> <literal>
+ (:coerce ..Object)
+ (Object::class []))]
+
+ (to_s <object>)
+ [(|> <object>
+ (:coerce ..Object)
+ (Object::to_s []))]]
+ (let [value_class (class_of value)]
(`` (cond (~~ (template [<literal> <type> <format>]
[(is? (class_of <literal>) value_class)
(|> value (:coerce <type>) <format>)]
[#0 Bit %.bit]
[#1 Bit %.bit]
- [+123 Int %.int]
- [+123.456 Frac %.frac]
- ["+123.456" Text %.text]
+ [+1 Int %.int]
+ [+1.0 Frac %.frac]
+ ["" Text %.text]
[("ruby object nil") Any (new> "nil" [])]
))
@@ -284,20 +305,19 @@
(let [variant_tag ("ruby object get" "_lux_tag" value)
variant_flag ("ruby object get" "_lux_flag" value)
variant_value ("ruby object get" "_lux_value" value)]
- (if (not (or ("ruby object nil?" variant_tag)
- ("ruby object nil?" variant_flag)
- ("ruby object nil?" variant_value)))
+ (if (or ("ruby object nil?" variant_tag)
+ ("ruby object nil?" variant_value))
+ (inspect_tuple inspect value)
(|> (%.format (|> variant_tag (:coerce .Nat) %.nat)
" " (%.bit (not ("ruby object nil?" variant_flag)))
" " (inspect variant_value))
- (text.enclose ["(" ")"]))
- (inspect_tuple inspect value)))
+ (text.enclose ["(" ")"]))))
(is? (class_of [[] []]) value_class)
(inspect_tuple inspect value)
## else
- (:coerce Text ("ruby object do" "to_s" value))))))
+ (to_s value)))))
@.php
(case (..gettype value)
@@ -315,14 +335,13 @@
(let [variant_tag ("php object get" "_lux_tag" value)
variant_flag ("php object get" "_lux_flag" value)
variant_value ("php object get" "_lux_value" value)]
- (if (not (or ("php object null?" variant_tag)
- ("php object null?" variant_flag)
- ("php object null?" variant_value)))
+ (if (or ("php object null?" variant_tag)
+ ("php object null?" variant_value))
+ (..strval value)
(|> (%.format (|> variant_tag (:coerce .Nat) %.nat)
" " (%.bit (not ("php object null?" variant_flag)))
" " (inspect variant_value))
- (text.enclose ["(" ")"]))
- (..strval value)))
+ (text.enclose ["(" ")"]))))
_
(..strval value))