diff options
Diffstat (limited to '')
-rw-r--r-- | stdlib/source/lux.lux | 66 | ||||
-rw-r--r-- | stdlib/source/lux/control/contract.lux | 37 | ||||
-rw-r--r-- | stdlib/source/lux/control/pipe.lux (renamed from stdlib/source/lux/pipe.lux) | 0 | ||||
-rw-r--r-- | stdlib/source/lux/data/coll/vector.lux | 1 | ||||
-rw-r--r-- | stdlib/source/lux/data/format/json.lux | 3 | ||||
-rw-r--r-- | stdlib/source/lux/data/text/lexer.lux (renamed from stdlib/source/lux/lexer.lux) | 0 | ||||
-rw-r--r-- | stdlib/source/lux/data/text/regex.lux (renamed from stdlib/source/lux/lexer/regex.lux) | 4 | ||||
-rw-r--r-- | stdlib/source/lux/type/auto.lux | 12 |
8 files changed, 46 insertions, 77 deletions
diff --git a/stdlib/source/lux.lux b/stdlib/source/lux.lux index 541b4bcdc..557992ba4 100644 --- a/stdlib/source/lux.lux +++ b/stdlib/source/lux.lux @@ -5591,36 +5591,6 @@ _ (fail "Wrong syntax for :!!"))) -(def: #hidden hack_Text/append - (-> Text Text Text) - Text/append) - -(def: get-cursor - (Lux Cursor) - (lambda [state] - (let [{#;info info #;source source #;modules modules #;scopes scopes - #;type-vars types #;host host #;seed seed - #;expected expected #;cursor cursor - #;scope-type-vars scope-type-vars} state] - (#;Right [state cursor])))) - -(macro: #export (with-cursor tokens) - {#;doc (doc "Given some text, appends to it a prefix for identifying where the text comes from." - "For example:" - (with-cursor (format "User: " user-id)) - "Would be the same as:" - (format "[the-module,the-line,the-column] " (format "User: " user-id)))} - (case tokens - (^ (list message)) - (do Monad<Lux> - [cursor get-cursor] - (let [[module line column] cursor - cursor-prefix ($_ hack_Text/append "[" module "," (Nat/encode line) "," (Nat/encode column) "] ")] - (wrap (list (` (hack_Text/append (~ (text$ cursor-prefix)) (~ message))))))) - - _ - (fail "Wrong syntax for @"))) - (macro: #export (undefined tokens) {#;doc (doc "Meant to be used as a stand-in for functions with undefined implementations." "Undefined expressions will type-check against everything, so they make good dummy implementations." @@ -5630,45 +5600,11 @@ "If an undefined expression is ever evaluated, it will raise an error.")} (case tokens #;Nil - (return (list (` (error! (with-cursor "Undefined behavior."))))) + (return (list (` (error! "Undefined behavior.")))) _ (fail "Wrong syntax for undefined"))) -(macro: #export (@pre tokens) - {#;doc (doc "Pre-conditions." - "Given a test and an expression to run, only runs the expression if the test passes." - "Otherwise, an error is raised." - (@pre (i.= 4 (i.+ 2 2)) - (foo 123 456 789)))} - (case tokens - (^ (list test expr)) - (return (list (` (if (~ test) - (~ expr) - (error! (with-cursor (~ (text$ (Text/append "Pre-condition failed: " (ast-to-text test)))))))))) - - _ - (fail "Wrong syntax for @pre"))) - -(macro: #export (@post tokens) - {#;doc (doc "Post-conditions." - "Given a predicate and an expression to run, evaluates the expression and then tests the output with the predicate." - "If the predicate returns true, returns the value of the expression." - "Otherwise, an error is raised." - (@post i.even? - (i.+ 2 2)))} - (case tokens - (^ (list test expr)) - (do Monad<Lux> - [g!output (gensym "")] - (wrap (list (` (let [(~ g!output) (~ expr)] - (if ((~ test) (~ g!output)) - (~ g!output) - (error! (with-cursor (~ (text$ (Text/append "Post-condition failed: " (ast-to-text test)))))))))))) - - _ - (fail "Wrong syntax for @post"))) - (macro: #export (type-of tokens) {#;doc (doc "Generates the type corresponding to a given definition or variable." (let [my-num (: Int 123)] diff --git a/stdlib/source/lux/control/contract.lux b/stdlib/source/lux/control/contract.lux new file mode 100644 index 000000000..2f347dfa5 --- /dev/null +++ b/stdlib/source/lux/control/contract.lux @@ -0,0 +1,37 @@ +(;module: + lux + (lux (control monad) + (data text/format) + [compiler #+ Monad<Lux>] + (macro [ast] + ["s" syntax #+ syntax:]))) + +(def: #export (assert! message test) + (-> Text Bool []) + (if test + [] + (error! message))) + +(syntax: #export (@pre test expr) + {#;doc (doc "Pre-conditions." + "Given a test and an expression to run, only runs the expression if the test passes." + "Otherwise, an error is raised." + (@pre (i.= 4 (i.+ 2 2)) + (foo 123 456 789)))} + (wrap (list (` (exec (assert! (~ (ast;text (format "Pre-condition failed: " (%ast test)))) + (~ test)) + (~ expr)))))) + +(syntax: #export (@post test expr) + {#;doc (doc "Post-conditions." + "Given a predicate and an expression to run, evaluates the expression and then tests the output with the predicate." + "If the predicate returns true, returns the value of the expression." + "Otherwise, an error is raised." + (@post i.even? + (i.+ 2 2)))} + (do @ + [g!output (compiler;gensym "")] + (wrap (list (` (let [(~ g!output) (~ expr)] + (exec (assert! (~ (ast;text (format "Post-condition failed: " (%ast test)))) + ((~ test) (~ g!output))) + (~ g!output)))))))) diff --git a/stdlib/source/lux/pipe.lux b/stdlib/source/lux/control/pipe.lux index cfb05491d..cfb05491d 100644 --- a/stdlib/source/lux/pipe.lux +++ b/stdlib/source/lux/control/pipe.lux diff --git a/stdlib/source/lux/data/coll/vector.lux b/stdlib/source/lux/data/coll/vector.lux index b0ef6aa46..1c4a1dd9d 100644 --- a/stdlib/source/lux/data/coll/vector.lux +++ b/stdlib/source/lux/data/coll/vector.lux @@ -15,7 +15,6 @@ [compiler #+ with-gensyms] (macro [ast] ["s" syntax #+ syntax: Syntax]) - [pipe] )) ## This implementation of vectors is based on Clojure's diff --git a/stdlib/source/lux/data/format/json.lux b/stdlib/source/lux/data/format/json.lux index 066777fdf..153920700 100644 --- a/stdlib/source/lux/data/format/json.lux +++ b/stdlib/source/lux/data/format/json.lux @@ -10,6 +10,7 @@ (data [bool] [text "Text/" Eq<Text> Monoid<Text>] text/format + (text [lexer #+ Lexer Monad<Lexer>]) [number #* "Real/" Codec<Text,Real>] maybe [char "Char/" Eq<Char> Codec<Text,Char>] @@ -24,7 +25,7 @@ [ast] [poly #+ poly:]) [type] - [lexer #+ Lexer Monad<Lexer>])) + )) ## [Types] (do-template [<name> <type>] diff --git a/stdlib/source/lux/lexer.lux b/stdlib/source/lux/data/text/lexer.lux index e28cb0a68..e28cb0a68 100644 --- a/stdlib/source/lux/lexer.lux +++ b/stdlib/source/lux/data/text/lexer.lux diff --git a/stdlib/source/lux/lexer/regex.lux b/stdlib/source/lux/data/text/regex.lux index 616f02086..21358c9b0 100644 --- a/stdlib/source/lux/lexer/regex.lux +++ b/stdlib/source/lux/data/text/regex.lux @@ -3,14 +3,14 @@ (lux (control monad) (data [char] [text] + ["&" text/lexer #+ Lexer Monad<Lexer>] text/format [number "Int/" Codec<Text,Int>] [product] (coll [list "" Fold<List> "List/" Monad<List>])) [compiler #- run] (macro [ast] - ["s" syntax #+ syntax:]) - ["&" lexer #+ Lexer Monad<Lexer>])) + ["s" syntax #+ syntax:]))) ## [Utils] (def: #hidden (->Text lexer^) diff --git a/stdlib/source/lux/type/auto.lux b/stdlib/source/lux/type/auto.lux index fa658ffb8..7059536c3 100644 --- a/stdlib/source/lux/type/auto.lux +++ b/stdlib/source/lux/type/auto.lux @@ -278,11 +278,7 @@ (list [alt-name =deps])))) List/join) #;Nil - (compiler;fail (format "No alternatives." - "\n" - (|> alts - (List/map product;left) - (%list %ident)))) + (compiler;fail (format "No alternatives for " (%type (type;function input-types output-type)))) found (wrap found)))) @@ -339,7 +335,7 @@ (::: = (list;n.range +1 +10) (list;n.range +1 +10)) - "Functor map" + "(Functor List) map" (::: map n.inc (list;n.range +0 +9)) "Caveat emptor: You need to make sure to import the module of any structure you want to use." "Otherwise, this macro won't find it.")} @@ -363,8 +359,8 @@ (compiler;fail (format "Too many options available: " (|> chosen-ones (List/map (. %ident product;left)) - (text;join-with ", ") - ))))) + (text;join-with ", ")) + " --- for type: " (%type sig-type))))) (#;Right [args _]) (do @ |