aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/lux.lux
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib/source/lux.lux')
-rw-r--r--stdlib/source/lux.lux138
1 files changed, 69 insertions, 69 deletions
diff --git a/stdlib/source/lux.lux b/stdlib/source/lux.lux
index bb66813cc..1307231e2 100644
--- a/stdlib/source/lux.lux
+++ b/stdlib/source/lux.lux
@@ -126,7 +126,7 @@
## #UnitT
## (#SumT Type Type)
## (#ProdT Type Type)
-## (#LambdaT Type Type)
+## (#FunctionT Type Type)
## (#BoundT Nat)
## (#VarT Nat)
## (#ExT Nat)
@@ -154,7 +154,7 @@
TypePair
(+3 ## "lux;ProdT"
TypePair
- (+3 ## "lux;LambdaT"
+ (+3 ## "lux;FunctionT"
TypePair
(+3 ## "lux;BoundT"
Nat
@@ -178,7 +178,7 @@
(#Cons (+6 "UnitT")
(#Cons (+6 "SumT")
(#Cons (+6 "ProdT")
- (#Cons (+6 "LambdaT")
+ (#Cons (+6 "FunctionT")
(#Cons (+6 "BoundT")
(#Cons (+6 "VarT")
(#Cons (+6 "ExT")
@@ -650,9 +650,9 @@
(_lux_def Lux
(#NamedT ["lux" "Lux"]
(#UnivQ #Nil
- (#LambdaT Compiler
- (#AppT (#AppT Either Text)
- (#ProdT Compiler (#BoundT +1))))))
+ (#FunctionT Compiler
+ (#AppT (#AppT Either Text)
+ (#ProdT Compiler (#BoundT +1))))))
(#Cons [["lux" "doc"] (#TextA "Computations that can have access to the state of the compiler.
These computations may fail, or modify the state of the compiler.")]
@@ -663,7 +663,7 @@
## (-> (List AST) (Lux (List AST))))
(_lux_def Macro
(#NamedT ["lux" "Macro"]
- (#LambdaT ASTList (#AppT Lux ASTList)))
+ (#FunctionT ASTList (#AppT Lux ASTList)))
(#Cons [["lux" "doc"] (#TextA "Functions that run at compile-time and allow you to transform and extend the language in powerful ways.")]
default-def-meta-exported))
@@ -673,20 +673,20 @@
#Nil)
(_lux_def _meta
- (_lux_: (#LambdaT (#AppT AST'
- (#AppT Meta Cursor))
- AST)
+ (_lux_: (#FunctionT (#AppT AST'
+ (#AppT Meta Cursor))
+ AST)
(_lux_function _ data
[_cursor data]))
#Nil)
(_lux_def return
(_lux_: (#UnivQ #Nil
- (#LambdaT (#BoundT +1)
- (#LambdaT Compiler
- (#AppT (#AppT Either Text)
- (#ProdT Compiler
- (#BoundT +1))))))
+ (#FunctionT (#BoundT +1)
+ (#FunctionT Compiler
+ (#AppT (#AppT Either Text)
+ (#ProdT Compiler
+ (#BoundT +1))))))
(_lux_function _ val
(_lux_function _ state
(#Right state val))))
@@ -694,73 +694,73 @@
(_lux_def fail
(_lux_: (#UnivQ #Nil
- (#LambdaT Text
- (#LambdaT Compiler
- (#AppT (#AppT Either Text)
- (#ProdT Compiler
- (#BoundT +1))))))
+ (#FunctionT Text
+ (#FunctionT Compiler
+ (#AppT (#AppT Either Text)
+ (#ProdT Compiler
+ (#BoundT +1))))))
(_lux_function _ msg
(_lux_function _ state
(#Left msg))))
#Nil)
(_lux_def bool$
- (_lux_: (#LambdaT Bool AST)
+ (_lux_: (#FunctionT Bool AST)
(_lux_function _ value (_meta (#BoolS value))))
#Nil)
(_lux_def nat$
- (_lux_: (#LambdaT Nat AST)
+ (_lux_: (#FunctionT Nat AST)
(_lux_function _ value (_meta (#NatS value))))
#Nil)
(_lux_def int$
- (_lux_: (#LambdaT Int AST)
+ (_lux_: (#FunctionT Int AST)
(_lux_function _ value (_meta (#IntS value))))
#Nil)
(_lux_def deg$
- (_lux_: (#LambdaT Deg AST)
+ (_lux_: (#FunctionT Deg AST)
(_lux_function _ value (_meta (#DegS value))))
#Nil)
(_lux_def real$
- (_lux_: (#LambdaT Real AST)
+ (_lux_: (#FunctionT Real AST)
(_lux_function _ value (_meta (#RealS value))))
#Nil)
(_lux_def char$
- (_lux_: (#LambdaT Char AST)
+ (_lux_: (#FunctionT Char AST)
(_lux_function _ value (_meta (#CharS value))))
#Nil)
(_lux_def text$
- (_lux_: (#LambdaT Text AST)
+ (_lux_: (#FunctionT Text AST)
(_lux_function _ text (_meta (#TextS text))))
#Nil)
(_lux_def symbol$
- (_lux_: (#LambdaT Ident AST)
+ (_lux_: (#FunctionT Ident AST)
(_lux_function _ ident (_meta (#SymbolS ident))))
#Nil)
(_lux_def tag$
- (_lux_: (#LambdaT Ident AST)
+ (_lux_: (#FunctionT Ident AST)
(_lux_function _ ident (_meta (#TagS ident))))
#Nil)
(_lux_def form$
- (_lux_: (#LambdaT (#AppT List AST) AST)
+ (_lux_: (#FunctionT (#AppT List AST) AST)
(_lux_function _ tokens (_meta (#FormS tokens))))
#Nil)
(_lux_def tuple$
- (_lux_: (#LambdaT (#AppT List AST) AST)
+ (_lux_: (#FunctionT (#AppT List AST) AST)
(_lux_function _ tokens (_meta (#TupleS tokens))))
#Nil)
(_lux_def record$
- (_lux_: (#LambdaT (#AppT List (#ProdT AST AST)) AST)
+ (_lux_: (#FunctionT (#AppT List (#ProdT AST AST)) AST)
(_lux_function _ tokens (_meta (#RecordS tokens))))
#Nil)
@@ -849,7 +849,7 @@
#Nil)
(_lux_def with-export-meta
- (_lux_: (#LambdaT AST AST)
+ (_lux_: (#FunctionT AST AST)
(function'' [tail]
(form$ (#Cons (tag$ ["lux" "Cons"])
(#Cons export?-meta
@@ -857,7 +857,7 @@
#Nil)
(_lux_def with-hidden-meta
- (_lux_: (#LambdaT AST AST)
+ (_lux_: (#FunctionT AST AST)
(function'' [tail]
(form$ (#Cons (tag$ ["lux" "Cons"])
(#Cons hidden?-meta
@@ -865,7 +865,7 @@
#Nil)
(_lux_def with-macro-meta
- (_lux_: (#LambdaT AST AST)
+ (_lux_: (#FunctionT AST AST)
(function'' [tail]
(form$ (#Cons (tag$ ["lux" "Cons"])
(#Cons macro?-meta
@@ -995,9 +995,9 @@
#Nil
(#UnivQ #Nil
(#UnivQ #Nil
- (#LambdaT (#LambdaT (#BoundT +3) (#BoundT +1))
- (#LambdaT ($' List (#BoundT +3))
- ($' List (#BoundT +1))))))
+ (#FunctionT (#FunctionT (#BoundT +3) (#BoundT +1))
+ (#FunctionT ($' List (#BoundT +3))
+ ($' List (#BoundT +1))))))
(_lux_case xs
#Nil
#Nil
@@ -1012,7 +1012,7 @@
(def:'' (make-env xs ys)
#Nil
- (#LambdaT ($' List Text) (#LambdaT ($' List AST) RepEnv))
+ (#FunctionT ($' List Text) (#FunctionT ($' List AST) RepEnv))
(_lux_case [xs ys]
[(#Cons x xs') (#Cons y ys')]
(#Cons [x y] (make-env xs' ys'))
@@ -1022,12 +1022,12 @@
(def:'' (Text/= x y)
#Nil
- (#LambdaT Text (#LambdaT Text Bool))
+ (#FunctionT Text (#FunctionT Text Bool))
(_lux_proc ["text" "="] [x y]))
(def:'' (get-rep key env)
#Nil
- (#LambdaT Text (#LambdaT RepEnv ($' Maybe AST)))
+ (#FunctionT Text (#FunctionT RepEnv ($' Maybe AST)))
(_lux_case env
#Nil
#None
@@ -1042,7 +1042,7 @@
(def:'' (replace-syntax reps syntax)
#Nil
- (#LambdaT RepEnv (#LambdaT AST AST))
+ (#FunctionT RepEnv (#FunctionT AST AST))
(_lux_case syntax
[_ (#SymbolS "" name)]
(_lux_case (get-rep name reps)
@@ -1059,7 +1059,7 @@
[meta (#TupleS (map (replace-syntax reps) members))]
[meta (#RecordS slots)]
- [meta (#RecordS (map (_lux_: (#LambdaT (#ProdT AST AST) (#ProdT AST AST))
+ [meta (#RecordS (map (_lux_: (#FunctionT (#ProdT AST AST) (#ProdT AST AST))
(function'' [slot]
(_lux_case slot
[k v]
@@ -1072,13 +1072,13 @@
(def:'' (update-bounds ast)
#Nil
- (#LambdaT AST AST)
+ (#FunctionT AST AST)
(_lux_case ast
[_ (#TupleS members)]
(tuple$ (map update-bounds members))
[_ (#RecordS pairs)]
- (record$ (map (_lux_: (#LambdaT (#ProdT AST AST) (#ProdT AST AST))
+ (record$ (map (_lux_: (#FunctionT (#ProdT AST AST) (#ProdT AST AST))
(function'' [pair]
(let'' [name val] pair
[name (update-bounds val)])))
@@ -1096,10 +1096,10 @@
(def:'' (parse-quantified-args args next)
#Nil
## (-> (List AST) (-> (List Text) (Lux (List AST))) (Lux (List AST)))
- (#LambdaT ($' List AST)
- (#LambdaT (#LambdaT ($' List Text) (#AppT Lux ($' List AST)))
- (#AppT Lux ($' List AST))
- ))
+ (#FunctionT ($' List AST)
+ (#FunctionT (#FunctionT ($' List Text) (#AppT Lux ($' List AST)))
+ (#AppT Lux ($' List AST))
+ ))
(_lux_case args
#Nil
(next #Nil)
@@ -1113,18 +1113,18 @@
(def:'' (make-bound idx)
#Nil
- (#LambdaT Nat AST)
+ (#FunctionT Nat AST)
(form$ (#Cons (tag$ ["lux" "BoundT"]) (#Cons (nat$ idx) #Nil))))
(def:'' (fold f init xs)
#Nil
## (All [a b] (-> (-> b a a) a (List b) a))
- (#UnivQ #Nil (#UnivQ #Nil (#LambdaT (#LambdaT (#BoundT +1)
- (#LambdaT (#BoundT +3)
- (#BoundT +3)))
- (#LambdaT (#BoundT +3)
- (#LambdaT ($' List (#BoundT +1))
- (#BoundT +3))))))
+ (#UnivQ #Nil (#UnivQ #Nil (#FunctionT (#FunctionT (#BoundT +1)
+ (#FunctionT (#BoundT +3)
+ (#BoundT +3)))
+ (#FunctionT (#BoundT +3)
+ (#FunctionT ($' List (#BoundT +1))
+ (#BoundT +3))))))
(_lux_case xs
#Nil
init
@@ -1135,7 +1135,7 @@
(def:'' (length list)
#Nil
(#UnivQ #Nil
- (#LambdaT ($' List (#BoundT +1)) Int))
+ (#FunctionT ($' List (#BoundT +1)) Int))
(fold (function'' [_ acc] (_lux_proc ["int" "+"] [1 acc])) 0 list))
(macro:' #export (All tokens)
@@ -1158,7 +1158,7 @@
(#Cons [_ (#TupleS args)] (#Cons body #Nil))
(parse-quantified-args args
(function'' [names]
- (let'' body' (fold (_lux_: (#LambdaT Text (#LambdaT AST AST))
+ (let'' body' (fold (_lux_: (#FunctionT Text (#FunctionT AST AST))
(function'' [name' body']
(form$ (#Cons (tag$ ["lux" "UnivQ"])
(#Cons (tag$ ["lux" "Nil"])
@@ -1209,7 +1209,7 @@
(#Cons [_ (#TupleS args)] (#Cons body #Nil))
(parse-quantified-args args
(function'' [names]
- (let'' body' (fold (_lux_: (#LambdaT Text (#LambdaT AST AST))
+ (let'' body' (fold (_lux_: (#FunctionT Text (#FunctionT AST AST))
(function'' [name' body']
(form$ (#Cons (tag$ ["lux" "ExQ"])
(#Cons (tag$ ["lux" "Nil"])
@@ -1240,7 +1240,7 @@
(def:'' (reverse list)
#Nil
- (All [a] (#LambdaT ($' List a) ($' List a)))
+ (All [a] (#FunctionT ($' List a) ($' List a)))
(fold (function'' [head tail] (#Cons head tail))
#Nil
list))
@@ -1253,8 +1253,8 @@
#;Nil)
(_lux_case (reverse tokens)
(#Cons output inputs)
- (return (#Cons (fold (_lux_: (#LambdaT AST (#LambdaT AST AST))
- (function'' [i o] (form$ (#Cons (tag$ ["lux" "LambdaT"]) (#Cons i (#Cons o #Nil))))))
+ (return (#Cons (fold (_lux_: (#FunctionT AST (#FunctionT AST AST))
+ (function'' [i o] (form$ (#Cons (tag$ ["lux" "FunctionT"]) (#Cons i (#Cons o #Nil))))))
output
inputs)
#Nil))
@@ -3385,8 +3385,8 @@
_
type)
- (#LambdaT ?input ?output)
- (#LambdaT (beta-reduce env ?input) (beta-reduce env ?output))
+ (#FunctionT ?input ?output)
+ (#FunctionT (beta-reduce env ?input) (beta-reduce env ?output))
(#BoundT idx)
(case (nth (_lux_proc ["nat" "to-int"] [idx]) env)
@@ -3435,7 +3435,7 @@
[flatten-variant #;SumT]
[flatten-tuple #;ProdT]
- [flatten-lambda #;LambdaT]
+ [flatten-lambda #;FunctionT]
[flatten-app #;AppT]
)
@@ -4228,7 +4228,7 @@
(#ProdT _)
($_ Text/append "[" (|> (flatten-tuple type) (map Type/show) (interpose " ") reverse (fold Text/append "")) "]")
- (#LambdaT _)
+ (#FunctionT _)
($_ Text/append "(-> " (|> (flatten-lambda type) (map Type/show) (interpose " ") reverse (fold Text/append "")) ")")
(#BoundT id)
@@ -4826,7 +4826,7 @@
(^template [<tag>]
(<tag> left right)
(<tag> (beta-reduce env left) (beta-reduce env right)))
- ([#;LambdaT]
+ ([#;FunctionT]
[#;AppT])
(^template [<tag>]
@@ -5098,8 +5098,8 @@
(` (<tag> (~ (type-to-ast left)) (~ (type-to-ast right)))))
([#SumT] [#ProdT])
- (#LambdaT in out)
- (` (#LambdaT (~ (type-to-ast in)) (~ (type-to-ast out))))
+ (#FunctionT in out)
+ (` (#FunctionT (~ (type-to-ast in)) (~ (type-to-ast out))))
(#BoundT idx)
(` (#BoundT (~ (nat$ idx))))