aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/lux/target/python.lux
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib/source/lux/target/python.lux')
-rw-r--r--stdlib/source/lux/target/python.lux123
1 files changed, 63 insertions, 60 deletions
diff --git a/stdlib/source/lux/target/python.lux b/stdlib/source/lux/target/python.lux
index b71947d0b..3f0211e33 100644
--- a/stdlib/source/lux/target/python.lux
+++ b/stdlib/source/lux/target/python.lux
@@ -1,15 +1,12 @@
(.module:
- [lux (#- Code not or and list if cond int comment)
+ [lux (#- Location Code not or and list if cond int comment)
[abstract
["." enum]]
[control
[pipe (#+ new> case> cond>)]
[parser
- ["s" code]]]
+ ["<.>" code]]]
[data
- [number
- ["n" nat]
- ["f" frac]]
["." text
["%" format (#+ format)]]
[collection
@@ -18,15 +15,21 @@
["." template]
["." code]
[syntax (#+ syntax:)]]
+ [math
+ [number
+ ["n" nat]
+ ["f" frac]]]
[type
abstract]])
-(def: expression (-> Text Text) (text.enclose ["(" ")"]))
+(def: expression
+ (-> Text Text)
+ (text.enclose ["(" ")"]))
(def: nest
(-> Text Text)
- (|>> (format text.new-line)
- (text.replace-all text.new-line (format text.new-line text.tab))))
+ (|>> (format text.new_line)
+ (text.replace_all text.new_line (format text.new_line text.tab))))
(abstract: #export (Code brand)
Text
@@ -40,7 +43,7 @@
(|>> :representation))
(template [<type> <super>]
- [(with-expansions [<brand> (template.identifier [<type> "'"])]
+ [(with_expansions [<brand> (template.identifier [<type> "'"])]
(`` (abstract: #export (<brand> brand) Any))
(`` (type: #export (<type> brand)
(<super> (<brand> brand)))))]
@@ -53,7 +56,7 @@
)
(template [<type> <super>]
- [(with-expansions [<brand> (template.identifier [<type> "'"])]
+ [(with_expansions [<brand> (template.identifier [<type> "'"])]
(`` (abstract: #export <brand> Any))
(`` (type: #export <type> (<super> <brand>))))]
@@ -108,11 +111,11 @@
(-> Frac Literal)
(`` (|>> (cond> (~~ (template [<lux> <python>]
[[(f.= <lux>)]
- [(new> (format "float(" text.double-quote <python> text.double-quote ")") [])]]
+ [(new> (format "float(" text.double_quote <python> text.double_quote ")") [])]]
- [f.positive-infinity "inf"]
- [f.negative-infinity "-inf"]
- [f.not-a-number "nan"]
+ [f.positive_infinity "inf"]
+ [f.negative_infinity "-inf"]
+ [f.not_a_number "nan"]
))
## else
@@ -122,43 +125,43 @@
(def: sanitize
(-> Text Text)
(`` (|>> (~~ (template [<find> <replace>]
- [(text.replace-all <find> <replace>)]
+ [(text.replace_all <find> <replace>)]
["\" "\\"]
[text.tab "\t"]
- [text.vertical-tab "\v"]
+ [text.vertical_tab "\v"]
[text.null "\0"]
- [text.back-space "\b"]
- [text.form-feed "\f"]
- [text.new-line "\n"]
- [text.carriage-return "\r"]
- [text.double-quote (format "\" text.double-quote)]
+ [text.back_space "\b"]
+ [text.form_feed "\f"]
+ [text.new_line "\n"]
+ [text.carriage_return "\r"]
+ [text.double_quote (format "\" text.double_quote)]
))
)))
(def: #export string
(-> Text Literal)
(|>> ..sanitize
- (text.enclose [text.double-quote text.double-quote])
+ (text.enclose [text.double_quote text.double_quote])
:abstraction))
- (def: (composite-literal left-delimiter right-delimiter entry-serializer)
+ (def: (composite_literal left_delimiter right_delimiter entry_serializer)
(All [a]
(-> Text Text (-> a Text)
(-> (List a) Literal)))
(function (_ entries)
(<| :abstraction
..expression
- (format left-delimiter
+ (format left_delimiter
(|> entries
- (list\map entry-serializer)
- (text.join-with ", "))
- right-delimiter))))
+ (list\map entry_serializer)
+ (text.join_with ", "))
+ right_delimiter))))
(template [<name> <pre> <post>]
[(def: #export <name>
(-> (List (Expression Any)) Literal)
- (composite-literal <pre> <post> ..code))]
+ (composite_literal <pre> <post> ..code))]
[tuple "(" ")"]
[list "[" "]"]
@@ -170,7 +173,7 @@
..expression
(format (:representation list) "[" (:representation from) ":" (:representation to) "]")))
- (def: #export (slice-from from list)
+ (def: #export (slice_from from list)
(-> (Expression Any) (Expression Any) Access)
(<| :abstraction
..expression
@@ -178,21 +181,21 @@
(def: #export dict
(-> (List [(Expression Any) (Expression Any)]) (Computation Any))
- (composite-literal "{" "}" (.function (_ [k v]) (format (:representation k) " : " (:representation v)))))
+ (composite_literal "{" "}" (.function (_ [k v]) (format (:representation k) " : " (:representation v)))))
(def: #export (apply/* func args)
(-> (Expression Any) (List (Expression Any)) (Computation Any))
(<| :abstraction
..expression
- (format (:representation func) "(" (text.join-with ", " (list\map ..code args)) ")")))
+ (format (:representation func) "(" (text.join_with ", " (list\map ..code args)) ")")))
(template [<name> <brand> <prefix>]
[(def: (<name> var)
(-> (Expression Any) Text)
(format <prefix> (:representation var)))]
- [splat-poly Poly "*"]
- [splat-keyword Keyword "**"]
+ [splat_poly Poly "*"]
+ [splat_keyword Keyword "**"]
)
(template [<name> <splat>]
@@ -203,11 +206,11 @@
(format (:representation func)
(format "(" (|> args
(list\map (function (_ arg) (format (:representation arg) ", ")))
- (text.join-with ""))
+ (text.join_with ""))
(<splat> extra) ")"))))]
- [apply-poly splat-poly]
- [apply-keyword splat-keyword]
+ [apply_poly splat_poly]
+ [apply_keyword splat_keyword]
)
(def: #export (the name object)
@@ -224,8 +227,8 @@
(-> (Expression Any) (Computation Any)))
(|>> (..the method) (<apply> args extra)))]
- [do-poly apply-poly]
- [do-keyword apply-keyword]
+ [do_poly apply_poly]
+ [do_keyword apply_keyword]
)
(def: #export (nth idx array)
@@ -257,11 +260,11 @@
[/ "/"]
[% "%"]
[** "**"]
- [bit-or "|"]
- [bit-and "&"]
- [bit-xor "^"]
- [bit-shl "<<"]
- [bit-shr ">>"]
+ [bit_or "|"]
+ [bit_and "&"]
+ [bit_xor "^"]
+ [bit_shl "<<"]
+ [bit_shr ">>"]
[or "or"]
[and "and"]
@@ -277,13 +280,13 @@
(-> (List (Var Any)) (Expression Any) (Computation Any))
(<| :abstraction
..expression
- (format "lambda " (|> arguments (list\map ..code) (text.join-with ", ")) ": "
+ (format "lambda " (|> arguments (list\map ..code) (text.join_with ", ")) ": "
(:representation body))))
(def: #export (set vars value)
(-> (List (Location Any)) (Expression Any) (Statement Any))
(:abstraction
- (format (|> vars (list\map ..code) (text.join-with ", "))
+ (format (|> vars (list\map ..code) (text.join_with ", "))
" = "
(:representation value))))
@@ -296,7 +299,7 @@
(:abstraction
(format "if " (:representation test) ":"
(..nest (:representation then!))
- text.new-line "else:"
+ text.new_line "else:"
(..nest (:representation else!)))))
(def: #export (when test then!)
@@ -309,7 +312,7 @@
(-> (Statement Any) (Statement Any) (Statement Any))
(:abstraction
(format (:representation pre!)
- text.new-line
+ text.new_line
(:representation post!))))
(template [<keyword> <0>]
@@ -327,7 +330,7 @@
(format "while " (:representation test) ":"
(..nest (:representation body!)))))
- (def: #export (for-in var inputs body!)
+ (def: #export (for_in var inputs body!)
(-> SVar (Expression Any) (Statement Any) Loop)
(:abstraction
(format "for " (:representation var) " in " (:representation inputs) ":"
@@ -353,10 +356,10 @@
(..nest (:representation body!))
(|> excepts
(list\map (function (_ [classes exception catch!])
- (format text.new-line "except (" (text.join-with ", " (list\map ..code classes))
+ (format text.new_line "except (" (text.join_with ", " (list\map ..code classes))
") as " (:representation exception) ":"
(..nest (:representation catch!)))))
- (text.join-with "")))))
+ (text.join_with "")))))
(template [<name> <keyword>]
[(def: #export (<name> message)
@@ -373,16 +376,16 @@
(-> SVar (List (Ex [k] (Var k))) (Statement Any) (Statement Any))
(:abstraction
(format "def " (:representation name)
- "(" (|> args (list\map ..code) (text.join-with ", ")) "):"
+ "(" (|> args (list\map ..code) (text.join_with ", ")) "):"
(..nest (:representation body)))))
- (def: #export (import module-name)
+ (def: #export (import module_name)
(-> Text (Statement Any))
- (:abstraction (format "import " module-name)))
+ (:abstraction (format "import " module_name)))
(def: #export (comment commentary on)
(All [brand] (-> Text (Code brand) (Code brand)))
- (:abstraction (format "# " (..sanitize commentary) text.new-line
+ (:abstraction (format "# " (..sanitize commentary) text.new_line
(:representation on))))
)
@@ -393,20 +396,20 @@
else!
(list.reverse clauses)))
-(syntax: (arity-inputs {arity s.nat})
+(syntax: (arity_inputs {arity <code>.nat})
(wrap (case arity
0 (.list)
_ (|> (dec arity)
(enum.range n.enum 0)
- (list\map (|>> %.nat code.local-identifier))))))
+ (list\map (|>> %.nat code.local_identifier))))))
-(syntax: (arity-types {arity s.nat})
+(syntax: (arity_types {arity <code>.nat})
(wrap (list.repeat arity (` (Expression Any)))))
(template [<arity> <function>+]
- [(with-expansions [<apply> (template.identifier ["apply/" <arity>])
- <inputs> (arity-inputs <arity>)
- <types> (arity-types <arity>)
+ [(with_expansions [<apply> (template.identifier ["apply/" <arity>])
+ <inputs> (arity_inputs <arity>)
+ <types> (arity_types <arity>)
<definitions> (template.splice <function>+)]
(def: #export (<apply> function <inputs>)
(-> (Expression Any) <types> (Computation Any))