aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/lux/lang
diff options
context:
space:
mode:
authorEduardo Julian2018-04-05 07:48:25 -0400
committerEduardo Julian2018-04-05 07:48:25 -0400
commit435771d3c4d4ffa791805e7006ee3bde488a4090 (patch)
tree693b9e2a6d8c6ddf4e439336e5bfcd665c9955cd /stdlib/source/lux/lang
parent3de94c8a341ef3f19fd75eeeb98e5333d2fe89d0 (diff)
- Improved the syntax for the "lux.function" macro.
Diffstat (limited to 'stdlib/source/lux/lang')
-rw-r--r--stdlib/source/lux/lang/syntax.lux4
-rw-r--r--stdlib/source/lux/lang/type.lux4
-rw-r--r--stdlib/source/lux/lang/type/check.lux54
3 files changed, 31 insertions, 31 deletions
diff --git a/stdlib/source/lux/lang/syntax.lux b/stdlib/source/lux/lang/syntax.lux
index 60bf3c11a..88a784980 100644
--- a/stdlib/source/lux/lang/syntax.lux
+++ b/stdlib/source/lux/lang/syntax.lux
@@ -304,7 +304,7 @@
(def: frac-ratio-fragment
(l.Lexer Frac)
(<| (p.codec number.Codec<Text,Frac>)
- (:: p.Monad<Parser> map (function [digits]
+ (:: p.Monad<Parser> map (function (_ digits)
(format digits ".0")))
rich-digits^))
@@ -600,7 +600,7 @@
(def: (ast current-module aliases)
(-> Text Aliases Cursor (l.Lexer [Cursor Code]))
(: (-> Cursor (l.Lexer [Cursor Code]))
- (function ast' [where]
+ (function (ast' where)
(do p.Monad<Parser>
[where (left-padding^ where)]
($_ p.either
diff --git a/stdlib/source/lux/lang/type.lux b/stdlib/source/lux/lang/type.lux
index 33cb2a033..35c2cd29c 100644
--- a/stdlib/source/lux/lang/type.lux
+++ b/stdlib/source/lux/lang/type.lux
@@ -49,7 +49,7 @@
[(#.Primitive xname xparams) (#.Primitive yname yparams)]
(and (text/= xname yname)
(n/= (list.size yparams) (list.size xparams))
- (list/fold (.function [[x y] prev] (and prev (= x y)))
+ (list/fold (.function (_ [x y] prev) (and prev (= x y)))
true
(list.zip2 xparams yparams)))
@@ -81,7 +81,7 @@
[(#.ExQ xenv xbody) (#.ExQ yenv ybody)])
(and (n/= (list.size yenv) (list.size xenv))
(= xbody ybody)
- (list/fold (.function [[x y] prev] (and prev (= x y)))
+ (list/fold (.function (_ [x y] prev) (and prev (= x y)))
true
(list.zip2 xenv yenv)))
diff --git a/stdlib/source/lux/lang/type/check.lux b/stdlib/source/lux/lang/type/check.lux
index ccb7780e2..7b7c1e3ee 100644
--- a/stdlib/source/lux/lang/type/check.lux
+++ b/stdlib/source/lux/lang/type/check.lux
@@ -48,7 +48,7 @@
(struct: #export _ (Functor Check)
(def: (map f fa)
- (function [context]
+ (function (_ context)
(case (fa context)
(#e.Error error)
(#e.Error error)
@@ -61,11 +61,11 @@
(def: functor Functor<Check>)
(def: (wrap x)
- (function [context]
+ (function (_ context)
(#e.Success [context x])))
(def: (apply ff fa)
- (function [context]
+ (function (_ context)
(case (ff context)
(#e.Success [context' f])
(case (fa context')
@@ -84,7 +84,7 @@
(def: applicative Applicative<Check>)
(def: (join ffa)
- (function [context]
+ (function (_ context)
(case (ffa context)
(#e.Success [context' fa])
(case (fa context')
@@ -155,13 +155,13 @@
(def: #export (throw exception message)
(All [e a] (-> (ex.Exception e) e (Check a)))
- (function [context]
+ (function (_ context)
(ex.throw exception message)))
(def: #export existential
{#.doc "A producer of existential types."}
(Check [Nat Type])
- (function [context]
+ (function (_ context)
(let [id (get@ #.ex-counter context)]
(#e.Success [(update@ #.ex-counter n/inc context)
[id (#.Ex id)]]))))
@@ -169,7 +169,7 @@
(do-template [<name> <outputT> <fail> <succeed>]
[(def: #export (<name> id)
(-> Var (Check <outputT>))
- (function [context]
+ (function (_ context)
(case (|> context (get@ #.var-bindings) (var::get id))
(^or (#.Some (#.Some (#.Var _)))
(#.Some #.None))
@@ -187,7 +187,7 @@
(def: (peek id)
(-> Var (Check Type))
- (function [context]
+ (function (_ context)
(case (|> context (get@ #.var-bindings) (var::get id))
(#.Some (#.Some bound))
(#e.Success [context bound])
@@ -200,7 +200,7 @@
(def: #export (write type id)
(-> Type Var (Check Unit))
- (function [context]
+ (function (_ context)
(case (|> context (get@ #.var-bindings) (var::get id))
(#.Some (#.Some bound))
(ex.throw Cannot-Rebind-Var [id type bound])
@@ -214,7 +214,7 @@
(def: (update type id)
(-> Type Var (Check Unit))
- (function [context]
+ (function (_ context)
(case (|> context (get@ #.var-bindings) (var::get id))
(#.Some _)
(#e.Success [(update@ #.var-bindings (var::put id (#.Some type)) context)
@@ -225,7 +225,7 @@
(def: #export var
(Check [Var Type])
- (function [context]
+ (function (_ context)
(let [id (get@ #.var-counter context)]
(#e.Success [(|> context
(update@ #.var-counter n/inc)
@@ -234,13 +234,13 @@
(def: get-bindings
(Check (List [Var (Maybe Type)]))
- (function [context]
+ (function (_ context)
(#e.Success [context
(get@ #.var-bindings context)])))
(def: (set-bindings value)
(-> (List [Var (Maybe Type)]) (Check Unit))
- (function [context]
+ (function (_ context)
(#e.Success [(set@ #.var-bindings value context)
[]])))
@@ -258,7 +258,7 @@
(apply-type! funcT' argT)))
_
- (function [context]
+ (function (_ context)
(case (type.apply (list argT) funcT)
#.None
(ex.throw Invalid-Type-Application [funcT argT])
@@ -272,7 +272,7 @@
(def: #export (ring id)
(-> Var (Check Ring))
- (function [context]
+ (function (_ context)
(loop [current id
output (set.add id empty-ring)]
(case (|> context (get@ #.var-bindings) (var::get current))
@@ -301,7 +301,7 @@
(def: (attempt op)
(All [a] (-> (Check a) (Check (Maybe a))))
- (function [context]
+ (function (_ context)
(case (op context)
(#e.Success [context' output])
(#e.Success [context' (#.Some output)])
@@ -311,19 +311,19 @@
(def: #export (fail message)
(All [a] (-> Text (Check a)))
- (function [context]
+ (function (_ context)
(#e.Error message)))
(def: #export (assert message test)
(-> Text Bool (Check Unit))
- (function [context]
+ (function (_ context)
(if test
(#e.Success [context []])
(#e.Error message))))
(def: (either left right)
(All [a] (-> (Check a) (Check a) (Check a)))
- (function [context]
+ (function (_ context)
(case (left context)
(#e.Success [context' output])
(#e.Success [context' output])
@@ -334,7 +334,7 @@
(def: (assumed? [e a] assumptions)
(-> [Type Type] (List Assumption) (Maybe Bool))
(:: maybe.Monad<Maybe> map product.right
- (list.find (function [[[fe fa] status]]
+ (list.find (function (_ [[fe fa] status])
(and (type/= e fe)
(type/= a fa)))
assumptions)))
@@ -421,7 +421,7 @@
(wrap assumptions)
## Fuse 2 rings
(do @
- [_ (monad.fold @ (function [interpose to]
+ [_ (monad.fold @ (function (_ interpose to)
(do @
[_ (link-3 interpose to idE)]
(wrap interpose)))
@@ -446,7 +446,7 @@
(def: (with-error-stack on-error check)
(All [a] (-> (-> Unit Text) (Check a) (Check a)))
- (function [context]
+ (function (_ context)
(case (check context)
(#e.Error error)
(#e.Error (case error
@@ -519,7 +519,7 @@
(if (is? expected actual)
(check/wrap assumptions)
(with-error-stack
- (function [_] (ex.construct Type-Check-Failed [expected actual]))
+ (function (_ _) (ex.construct Type-Check-Failed [expected actual]))
(case [expected actual]
[(#.Var idE) (#.Var idA)]
(check-vars check' assumptions idE idA)
@@ -527,13 +527,13 @@
[(#.Var id) _]
(on id actual
(check/wrap assumptions)
- (function [bound]
+ (function (_ bound)
(check' bound actual assumptions)))
[_ (#.Var id)]
(on id expected
(check/wrap assumptions)
- (function [bound]
+ (function (_ bound)
(check' expected bound assumptions)))
(^template [<fe> <fa>]
@@ -586,7 +586,7 @@
(list.size a-params)))
(do Monad<Check>
[assumptions (monad.fold Monad<Check>
- (function [[e a] assumptions] (check' e a assumptions))
+ (function (_ [e a] assumptions) (check' e a assumptions))
assumptions
(list.zip2 e-params a-params))]
(check/wrap assumptions))
@@ -641,7 +641,7 @@
(def: #export get-context
(Check Type-Context)
- (function [context]
+ (function (_ context)
(#e.Success [context context])))
(def: #export (clean inputT)