aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/library/lux/ffi.py.lux
diff options
context:
space:
mode:
Diffstat (limited to '')
-rw-r--r--stdlib/source/library/lux/ffi.py.lux130
1 files changed, 65 insertions, 65 deletions
diff --git a/stdlib/source/library/lux/ffi.py.lux b/stdlib/source/library/lux/ffi.py.lux
index 36196c8dc..150cbf578 100644
--- a/stdlib/source/library/lux/ffi.py.lux
+++ b/stdlib/source/library/lux/ffi.py.lux
@@ -235,76 +235,76 @@
#.Nil
(` ("python import" (~ (code.text class)))))]
- (wrap (list& (` (type: (~ g!type)
- (..Object (primitive (~ (code.text real_class))))))
- (list\map (function (_ member)
- (case member
- (#Constructor inputsT)
- (let [g!inputs (input_variables inputsT)]
- (` (def: ((~ (qualify "new"))
- [(~+ (list\map product.right g!inputs))])
- (-> [(~+ (list\map noneable_type inputsT))]
- (~ g!type))
- (:assume
- ("python apply"
- (:as ..Function (~ imported))
- (~+ (list\map (with_none g!temp) g!inputs)))))))
+ (in (list& (` (type: (~ g!type)
+ (..Object (primitive (~ (code.text real_class))))))
+ (list\map (function (_ member)
+ (case member
+ (#Constructor inputsT)
+ (let [g!inputs (input_variables inputsT)]
+ (` (def: ((~ (qualify "new"))
+ [(~+ (list\map product.right g!inputs))])
+ (-> [(~+ (list\map noneable_type inputsT))]
+ (~ g!type))
+ (:assume
+ ("python apply"
+ (:as ..Function (~ imported))
+ (~+ (list\map (with_none g!temp) g!inputs)))))))
+
+ (#Field [static? field fieldT])
+ (if static?
+ (` ((~! syntax:) ((~ (qualify field)))
+ (\ (~! meta.monad) (~' in)
+ (list (` (.:as (~ (noneable_type fieldT))
+ ("python object get" (~ (code.text field))
+ (:as (..Object .Any) (~ imported)))))))))
+ (` (def: ((~ (qualify field))
+ (~ g!object))
+ (-> (~ g!type)
+ (~ (noneable_type fieldT)))
+ (:assume
+ (~ (without_none g!temp fieldT (` ("python object get" (~ (code.text field))
+ (:as (..Object .Any) (~ g!object))))))))))
+
+ (#Method method)
+ (case method
+ (#Static [method alias inputsT io? try? outputT])
+ (..make_function (qualify (maybe.default method alias))
+ g!temp
+ (` ("python object get" (~ (code.text method))
+ (:as (..Object .Any) (~ imported))))
+ inputsT
+ io?
+ try?
+ outputT)
- (#Field [static? field fieldT])
- (if static?
- (` ((~! syntax:) ((~ (qualify field)))
- (\ (~! meta.monad) (~' wrap)
- (list (` (.:as (~ (noneable_type fieldT))
- ("python object get" (~ (code.text field))
- (:as (..Object .Any) (~ imported)))))))))
- (` (def: ((~ (qualify field))
+ (#Virtual [method alias inputsT io? try? outputT])
+ (let [g!inputs (input_variables inputsT)]
+ (` (def: ((~ (qualify (maybe.default method alias)))
+ [(~+ (list\map product.right g!inputs))]
(~ g!object))
- (-> (~ g!type)
- (~ (noneable_type fieldT)))
+ (-> [(~+ (list\map noneable_type inputsT))]
+ (~ g!type)
+ (~ (|> (noneable_type outputT)
+ (try_type try?)
+ (io_type io?))))
(:assume
- (~ (without_none g!temp fieldT (` ("python object get" (~ (code.text field))
- (:as (..Object .Any) (~ g!object))))))))))
-
- (#Method method)
- (case method
- (#Static [method alias inputsT io? try? outputT])
- (..make_function (qualify (maybe.default method alias))
- g!temp
- (` ("python object get" (~ (code.text method))
- (:as (..Object .Any) (~ imported))))
- inputsT
- io?
- try?
- outputT)
-
- (#Virtual [method alias inputsT io? try? outputT])
- (let [g!inputs (input_variables inputsT)]
- (` (def: ((~ (qualify (maybe.default method alias)))
- [(~+ (list\map product.right g!inputs))]
- (~ g!object))
- (-> [(~+ (list\map noneable_type inputsT))]
- (~ g!type)
- (~ (|> (noneable_type outputT)
- (try_type try?)
- (io_type io?))))
- (:assume
- (~ (<| (with_io io?)
- (with_try try?)
- (without_none g!temp outputT)
- (` ("python object do"
- (~ (code.text method))
- (~ g!object)
- (~+ (list\map (with_none g!temp) g!inputs)))))))))))))
- members)))))
+ (~ (<| (with_io io?)
+ (with_try try?)
+ (without_none g!temp outputT)
+ (` ("python object do"
+ (~ (code.text method))
+ (~ g!object)
+ (~+ (list\map (with_none g!temp) g!inputs)))))))))))))
+ members)))))
(#Function [name alias inputsT io? try? outputT])
- (wrap (list (..make_function (code.local_identifier (maybe.default name alias))
- g!temp
- (` ("python constant" (~ (code.text name))))
- inputsT
- io?
- try?
- outputT)))
+ (in (list (..make_function (code.local_identifier (maybe.default name alias))
+ g!temp
+ (` ("python constant" (~ (code.text name))))
+ inputsT
+ io?
+ try?
+ outputT)))
)))
(template: #export (lambda <inputs> <output>)