aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/lux/control/parser/type.lux
diff options
context:
space:
mode:
Diffstat (limited to '')
-rw-r--r--stdlib/source/lux/control/parser/type.lux50
1 files changed, 25 insertions, 25 deletions
diff --git a/stdlib/source/lux/control/parser/type.lux b/stdlib/source/lux/control/parser/type.lux
index 56942e5c4..8625901af 100644
--- a/stdlib/source/lux/control/parser/type.lux
+++ b/stdlib/source/lux/control/parser/type.lux
@@ -19,7 +19,7 @@
["." code]]
["." type ("#@." equivalence)
["." check]]]
- ["." // (#+ Parser)])
+ ["." //])
(template [<name>]
[(exception: #export (<name> {type Type})
@@ -57,13 +57,13 @@
(type: #export Env
(Dictionary Nat [Type Code]))
-(type: #export (Poly a)
- (Parser [Env (List Type)] a))
+(type: #export (Parser a)
+ (//.Parser [Env (List Type)] a))
(def: #export fresh Env (dictionary.new nat.hash))
(def: (run' env types poly)
- (All [a] (-> Env (List Type) (Poly a) (Error a)))
+ (All [a] (-> Env (List Type) (Parser a) (Error a)))
(case (//.run [env types] poly)
(#error.Failure error)
(#error.Failure error)
@@ -77,16 +77,16 @@
(exception.throw unconsumed remaining))))
(def: #export (run type poly)
- (All [a] (-> Type (Poly a) (Error a)))
+ (All [a] (-> Type (Parser a) (Error a)))
(run' fresh (list type) poly))
(def: #export env
- (Poly Env)
+ (Parser Env)
(.function (_ [env inputs])
(#error.Success [[env inputs] env])))
(def: (with-env temp poly)
- (All [a] (-> Env (Poly a) (Poly a)))
+ (All [a] (-> Env (Parser a) (Parser a)))
(.function (_ [env inputs])
(case (//.run [temp inputs] poly)
(#error.Failure error)
@@ -96,7 +96,7 @@
(#error.Success [[env remaining] output]))))
(def: #export peek
- (Poly Type)
+ (Parser Type)
(.function (_ [env inputs])
(case inputs
#.Nil
@@ -106,7 +106,7 @@
(#error.Success [[env inputs] headT]))))
(def: #export any
- (Poly Type)
+ (Parser Type)
(.function (_ [env inputs])
(case inputs
#.Nil
@@ -116,7 +116,7 @@
(#error.Success [[env tail] headT]))))
(def: #export (local types poly)
- (All [a] (-> (List Type) (Poly a) (Poly a)))
+ (All [a] (-> (List Type) (Parser a) (Parser a)))
(.function (_ [env pass-through])
(case (run' env types poly)
(#error.Failure error)
@@ -130,7 +130,7 @@
(code.local-identifier ($_ text@compose "label" text.tab (nat@encode idx))))
(def: #export (with-extension type poly)
- (All [a] (-> Type (Poly a) (Poly [Code a])))
+ (All [a] (-> Type (Parser a) (Parser [Code a])))
(.function (_ [env inputs])
(let [current-id (dictionary.size env)
g!var (label current-id)]
@@ -145,7 +145,7 @@
(template [<name> <flattener> <tag> <exception>]
[(def: #export (<name> poly)
- (All [a] (-> (Poly a) (Poly a)))
+ (All [a] (-> (Parser a) (Parser a)))
(do //.monad
[headT any]
(let [members (<flattener> (type.un-name headT))]
@@ -158,7 +158,7 @@
)
(def: polymorphic'
- (Poly [Nat Type])
+ (Parser [Nat Type])
(do //.monad
[headT any
#let [[num-arg bodyT] (type.flatten-univ-q (type.un-name headT))]]
@@ -167,7 +167,7 @@
(wrap [num-arg bodyT]))))
(def: #export (polymorphic poly)
- (All [a] (-> (Poly a) (Poly [Code (List Code) a])))
+ (All [a] (-> (Parser a) (Parser [Code (List Code) a])))
(do //.monad
[headT any
funcI (:: @ map dictionary.size ..env)
@@ -204,7 +204,7 @@
(with-env env'))))
(def: #export (function in-poly out-poly)
- (All [i o] (-> (Poly i) (Poly o) (Poly [i o])))
+ (All [i o] (-> (Parser i) (Parser o) (Parser [i o])))
(do //.monad
[headT any
#let [[inputsT outputT] (type.flatten-function (type.un-name headT))]]
@@ -214,7 +214,7 @@
(//.fail (exception.construct not-function headT)))))
(def: #export (apply poly)
- (All [a] (-> (Poly a) (Poly a)))
+ (All [a] (-> (Parser a) (Parser a)))
(do //.monad
[headT any
#let [[funcT paramsT] (type.flatten-application (type.un-name headT))]]
@@ -224,7 +224,7 @@
(template [<name> <test>]
[(def: #export (<name> expected)
- (-> Type (Poly Any))
+ (-> Type (Parser Any))
(do //.monad
[actual any]
(if (<test> expected actual)
@@ -244,7 +244,7 @@
(|> env-level dec (n/- parameter-level) (n/* 2) (n/+ parameter-idx))))
(def: #export parameter
- (Poly Code)
+ (Parser Code)
(do //.monad
[env ..env
headT any]
@@ -261,7 +261,7 @@
(//.fail (exception.construct not-parameter headT)))))
(def: #export (parameter! id)
- (-> Nat (Poly Any))
+ (-> Nat (Parser Any))
(do //.monad
[env ..env
headT any]
@@ -275,7 +275,7 @@
(//.fail (exception.construct not-parameter headT)))))
(def: #export existential
- (Poly Nat)
+ (Parser Nat)
(do //.monad
[headT any]
(case headT
@@ -286,7 +286,7 @@
(//.fail (exception.construct not-existential headT)))))
(def: #export named
- (Poly [Name Type])
+ (Parser [Name Type])
(do //.monad
[inputT any]
(case inputT
@@ -297,7 +297,7 @@
(//.fail (exception.construct not-named inputT)))))
(def: #export (recursive poly)
- (All [a] (-> (Poly a) (Poly [Code a])))
+ (All [a] (-> (Parser a) (Parser [Code a])))
(do //.monad
[headT any]
(case (type.un-name headT)
@@ -313,7 +313,7 @@
(//.fail (exception.construct not-recursive headT)))))
(def: #export recursive-self
- (Poly Code)
+ (Parser Code)
(do //.monad
[env ..env
headT any]
@@ -327,7 +327,7 @@
(//.fail (exception.construct not-recursive headT)))))
(def: #export recursive-call
- (Poly Code)
+ (Parser Code)
(do //.monad
[env ..env
[funcT argsT] (apply (//.and any (//.many any)))
@@ -339,7 +339,7 @@
(wrap (` ((~+ allC))))))
(def: #export log!
- (All [a] (Poly a))
+ (All [a] (Parser a))
(do //.monad
[current any
#let [_ (.log! ($_ text@compose