aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source
diff options
context:
space:
mode:
authorEduardo Julian2018-07-04 21:34:07 -0400
committerEduardo Julian2018-07-04 21:34:07 -0400
commit4bc58162f3d381abf33c936eafc976a2f422258c (patch)
treef975876db8c07f2c2dc788a7d0ee02c891f1c167 /stdlib/source
parent7585d987ad3898859ce817ad9857dccb6e788c6b (diff)
- Re-named Bound to Paremeter.
Diffstat (limited to 'stdlib/source')
-rw-r--r--stdlib/source/lux.lux100
-rw-r--r--stdlib/source/lux/control/concatenative.lux6
-rw-r--r--stdlib/source/lux/lang/compiler/analysis/inference.lux16
-rw-r--r--stdlib/source/lux/lang/compiler/extension/analysis/host.jvm.lux8
-rw-r--r--stdlib/source/lux/lang/type.lux8
-rw-r--r--stdlib/source/lux/lang/type/check.lux2
-rw-r--r--stdlib/source/lux/macro/poly.lux32
-rw-r--r--stdlib/source/lux/macro/poly/equality.lux4
-rw-r--r--stdlib/source/lux/macro/poly/functor.lux2
-rw-r--r--stdlib/source/lux/macro/poly/json.lux4
-rw-r--r--stdlib/source/lux/type/object/interface.lux8
11 files changed, 95 insertions, 95 deletions
diff --git a/stdlib/source/lux.lux b/stdlib/source/lux.lux
index 31f5165ea..d68ef26ad 100644
--- a/stdlib/source/lux.lux
+++ b/stdlib/source/lux.lux
@@ -196,7 +196,7 @@
## (#Sum Type Type)
## (#Product Type Type)
## (#Function Type Type)
-## (#Bound Nat)
+## (#Parameter Nat)
## (#Var Nat)
## (#Ex Nat)
## (#UnivQ (List Type) Type)
@@ -222,7 +222,7 @@
Type-Pair
(+1 ## "lux.Function"
Type-Pair
- (+1 ## "lux.Bound"
+ (+1 ## "lux.Parameter"
Nat
(+1 ## "lux.Var"
Nat
@@ -246,7 +246,7 @@
(#Cons [dummy-cursor (+5 "Sum")]
(#Cons [dummy-cursor (+5 "Product")]
(#Cons [dummy-cursor (+5 "Function")]
- (#Cons [dummy-cursor (+5 "Bound")]
+ (#Cons [dummy-cursor (+5 "Parameter")]
(#Cons [dummy-cursor (+5 "Var")]
(#Cons [dummy-cursor (+5 "Ex")]
(#Cons [dummy-cursor (+5 "UnivQ")]
@@ -288,8 +288,8 @@
(#Named ["lux" "Ann"]
(#UnivQ #Nil
(#UnivQ #Nil
- (#Product (#Bound +3)
- (#Bound +1)))))
+ (#Product (#Parameter +3)
+ (#Parameter +1)))))
[dummy-cursor
(+10 (#Cons [[dummy-cursor (+7 ["lux" "tags"])]
[dummy-cursor (+9 (#Cons [dummy-cursor (+5 "meta")]
@@ -319,9 +319,9 @@
## (#Record (List [(w (Code' w)) (w (Code' w))])))
("lux def" Code'
(#Named ["lux" "Code'"]
- ("lux case" ("lux check type" (#Apply (#Apply (#Bound +1)
- (#Bound +0))
- (#Bound +1)))
+ ("lux case" ("lux check type" (#Apply (#Apply (#Parameter +1)
+ (#Parameter +0))
+ (#Parameter +1)))
{Code
("lux case" ("lux check type" (#Apply Code List))
{Code-List
@@ -486,8 +486,8 @@
(#Product ## "lux.counter"
Nat
## "lux.mappings"
- (#Apply (#Product (#Bound +3)
- (#Bound +1))
+ (#Apply (#Product (#Parameter +3)
+ (#Parameter +1))
List)))))
(record$ (#Cons [(tag$ ["lux" "tags"])
(tuple$ (#Cons (text$ "counter") (#Cons (text$ "mappings") #Nil)))]
@@ -539,9 +539,9 @@
(#UnivQ #Nil
(#UnivQ #Nil
(#Sum ## "lux.Left"
- (#Bound +3)
+ (#Parameter +3)
## "lux.Right"
- (#Bound +1)))))
+ (#Parameter +1)))))
(record$ (#Cons [(tag$ ["lux" "tags"])
(tuple$ (#Cons (text$ "Left") (#Cons (text$ "Right") #Nil)))]
(#Cons [(tag$ ["lux" "type-args"])
@@ -756,7 +756,7 @@
(#Named ["lux" "Meta"]
(#UnivQ #Nil
(#Function Lux
- (#Apply (#Product Lux (#Bound +1))
+ (#Apply (#Product Lux (#Parameter +1))
(#Apply Text Either)))))
(record$ (#Cons [(tag$ ["lux" "doc"])
(text$ "Computations that can have access to the state of the compiler.
@@ -778,10 +778,10 @@
## Base functions & macros
("lux def" return
("lux check" (#UnivQ #Nil
- (#Function (#Bound +1)
+ (#Function (#Parameter +1)
(#Function Lux
(#Apply (#Product Lux
- (#Bound +1))
+ (#Parameter +1))
(#Apply Text Either)))))
("lux function" _ val
("lux function" _ state
@@ -793,7 +793,7 @@
(#Function Text
(#Function Lux
(#Apply (#Product Lux
- (#Bound +1))
+ (#Parameter +1))
(#Apply Text Either)))))
("lux function" _ msg
("lux function" _ state
@@ -1052,9 +1052,9 @@
#Nil
(#UnivQ #Nil
(#UnivQ #Nil
- (#Function (#Function (#Bound +3) (#Bound +1))
- (#Function ($' List (#Bound +3))
- ($' List (#Bound +1))))))
+ (#Function (#Function (#Parameter +3) (#Parameter +1))
+ (#Function ($' List (#Parameter +3))
+ ($' List (#Parameter +1))))))
("lux case" xs
{#Nil
#Nil
@@ -1151,25 +1151,25 @@
("lux coerce" Int subject)
("lux coerce" Int param))))
-(def:'' (update-bounds code)
+(def:'' (update-parameters code)
#Nil
(#Function Code Code)
("lux case" code
{[_ (#Tuple members)]
- (tuple$ (list/map update-bounds members))
+ (tuple$ (list/map update-parameters members))
[_ (#Record pairs)]
(record$ (list/map ("lux check" (#Function (#Product Code Code) (#Product Code Code))
(function'' [pair]
(let'' [name val] pair
- [name (update-bounds val)])))
+ [name (update-parameters val)])))
pairs))
- [_ (#Form (#Cons [_ (#Tag "lux" "Bound")] (#Cons [_ (#Nat idx)] #Nil)))]
- (form$ (#Cons (tag$ ["lux" "Bound"]) (#Cons (nat$ (n/+ +2 idx)) #Nil)))
+ [_ (#Form (#Cons [_ (#Tag "lux" "Parameter")] (#Cons [_ (#Nat idx)] #Nil)))]
+ (form$ (#Cons (tag$ ["lux" "Parameter"]) (#Cons (nat$ (n/+ +2 idx)) #Nil)))
[_ (#Form members)]
- (form$ (list/map update-bounds members))
+ (form$ (list/map update-parameters members))
_
code}))
@@ -1192,20 +1192,20 @@
(fail "Expected symbol.")}
))
-(def:'' (make-bound idx)
+(def:'' (make-parameter idx)
#Nil
(#Function Nat Code)
- (form$ (#Cons (tag$ ["lux" "Bound"]) (#Cons (nat$ idx) #Nil))))
+ (form$ (#Cons (tag$ ["lux" "Parameter"]) (#Cons (nat$ idx) #Nil))))
(def:'' (list/fold f init xs)
#Nil
## (All [a b] (-> (-> b a a) a (List b) a))
- (#UnivQ #Nil (#UnivQ #Nil (#Function (#Function (#Bound +1)
- (#Function (#Bound +3)
- (#Bound +3)))
- (#Function (#Bound +3)
- (#Function ($' List (#Bound +1))
- (#Bound +3))))))
+ (#UnivQ #Nil (#UnivQ #Nil (#Function (#Function (#Parameter +1)
+ (#Function (#Parameter +3)
+ (#Parameter +3)))
+ (#Function (#Parameter +3)
+ (#Function ($' List (#Parameter +1))
+ (#Parameter +3))))))
("lux case" xs
{#Nil
init
@@ -1216,7 +1216,7 @@
(def:'' (list/size list)
#Nil
(#UnivQ #Nil
- (#Function ($' List (#Bound +1)) Nat))
+ (#Function ($' List (#Parameter +1)) Nat))
(list/fold (function'' [_ acc] (n/+ +1 acc)) +0 list))
(macro:' #export (All tokens)
@@ -1244,8 +1244,8 @@
(function'' [name' body']
(form$ (#Cons (tag$ ["lux" "UnivQ"])
(#Cons (tag$ ["lux" "Nil"])
- (#Cons (replace-syntax (#Cons [name' (make-bound +1)] #Nil)
- (update-bounds body')) #Nil))))))
+ (#Cons (replace-syntax (#Cons [name' (make-parameter +1)] #Nil)
+ (update-parameters body')) #Nil))))))
body
names)
(return (#Cons ("lux case" [(text/= "" self-name) names]
@@ -1256,7 +1256,7 @@
body'
[false _]
- (replace-syntax (#Cons [self-name (make-bound (n/* +2 (n/- +1 (list/size names))))]
+ (replace-syntax (#Cons [self-name (make-parameter (n/* +2 (n/- +1 (list/size names))))]
#Nil)
body')})
#Nil)))))
@@ -1292,8 +1292,8 @@
(function'' [name' body']
(form$ (#Cons (tag$ ["lux" "ExQ"])
(#Cons (tag$ ["lux" "Nil"])
- (#Cons (replace-syntax (#Cons [name' (make-bound +1)] #Nil)
- (update-bounds body')) #Nil))))))
+ (#Cons (replace-syntax (#Cons [name' (make-parameter +1)] #Nil)
+ (update-parameters body')) #Nil))))))
body
names)
(return (#Cons ("lux case" [(text/= "" self-name) names]
@@ -1304,7 +1304,7 @@
body'
[false _]
- (replace-syntax (#Cons [self-name (make-bound (n/* +2 (n/- +1 (list/size names))))]
+ (replace-syntax (#Cons [self-name (make-parameter (n/* +2 (n/- +1 (list/size names))))]
#Nil)
body')})
#Nil)))))
@@ -2964,8 +2964,8 @@
[Int (List Self)])")])
("lux case" tokens
{(#Cons [_ (#Symbol "" name)] (#Cons body #Nil))
- (let' [body' (replace-syntax (list [name (` (#.Apply (~ (make-bound +1)) (~ (make-bound +0))))])
- (update-bounds body))]
+ (let' [body' (replace-syntax (list [name (` (#.Apply (~ (make-parameter +1)) (~ (make-parameter +0))))])
+ (update-parameters body))]
(return (list (` (#.Apply .Nothing (#.UnivQ #.Nil (~ body')))))))
_
@@ -3698,10 +3698,10 @@
(#Function ?input ?output)
(#Function (beta-reduce env ?input) (beta-reduce env ?output))
- (#Bound idx)
+ (#Parameter idx)
(case (nth idx env)
- (#Some bound)
- bound
+ (#Some parameter)
+ parameter
_
type)
@@ -4576,7 +4576,7 @@
(#Function _)
($_ text/compose "(-> " (|> (flatten-lambda type) (list/map type/show) (interpose " ") list/reverse (list/fold text/compose "")) ")")
- (#Bound id)
+ (#Parameter id)
(nat/encode id)
(#Var id)
@@ -5219,7 +5219,7 @@
([#.UnivQ]
[#.ExQ])
- (#.Bound idx)
+ (#.Parameter idx)
(default type (list.nth idx env))
_
@@ -5468,8 +5468,8 @@
(#Function in out)
(` (#Function (~ (type-to-code in)) (~ (type-to-code out))))
- (#Bound idx)
- (` (#Bound (~ (nat$ idx))))
+ (#Parameter idx)
+ (` (#Parameter (~ (nat$ idx))))
(#Var id)
(` (#Var (~ (nat$ id))))
@@ -5627,7 +5627,7 @@
(macro: #export (with-expansions tokens)
{#.doc (doc "Controlled macro-expansion."
"Bind an arbitraty number of Codes resulting from macro-expansion to local bindings."
- "Wherever a binding appears, the bound Codes will be spliced in there."
+ "Wherever a binding appears, the bound codes will be spliced in there."
(test: "Code operations & structures"
(with-expansions
[<tests> (do-template [<expr> <text> <pattern>]
diff --git a/stdlib/source/lux/control/concatenative.lux b/stdlib/source/lux/control/concatenative.lux
index 2b91cac0e..70756c5c6 100644
--- a/stdlib/source/lux/control/concatenative.lux
+++ b/stdlib/source/lux/control/concatenative.lux
@@ -32,7 +32,7 @@
(def: bottom^
(s.Syntax Nat)
- (s.form (p.after (s.this (` #.Bound)) s.nat)))
+ (s.form (p.after (s.this (` #.Parameter)) s.nat)))
(def: stack^
(s.Syntax Stack)
@@ -68,8 +68,8 @@
(code.replace (code.local-symbol from) to pre))
aliased
aliases))]
- (case [(|> inputs (get@ #bottom) (maybe/map (|>> code.nat (~) #.Bound (`))))
- (|> outputs (get@ #bottom) (maybe/map (|>> code.nat (~) #.Bound (`))))]
+ (case [(|> inputs (get@ #bottom) (maybe/map (|>> code.nat (~) #.Parameter (`))))
+ (|> outputs (get@ #bottom) (maybe/map (|>> code.nat (~) #.Parameter (`))))]
[(#.Some bottomI) (#.Some bottomO)]
(monad.do @
[inputC (singleton (macro.expand-all (stack-fold (get@ #top inputs) bottomI)))
diff --git a/stdlib/source/lux/lang/compiler/analysis/inference.lux b/stdlib/source/lux/lang/compiler/analysis/inference.lux
index 5e3fb0cfe..42ab27a6c 100644
--- a/stdlib/source/lux/lang/compiler/analysis/inference.lux
+++ b/stdlib/source/lux/lang/compiler/analysis/inference.lux
@@ -43,30 +43,30 @@
[invalid-type-application]
)
-(def: (replace bound-idx replacement type)
+(def: (replace parameter-idx replacement type)
(-> Nat Type Type Type)
(case type
(#.Primitive name params)
- (#.Primitive name (list/map (replace bound-idx replacement) params))
+ (#.Primitive name (list/map (replace parameter-idx replacement) params))
(^template [<tag>]
(<tag> left right)
- (<tag> (replace bound-idx replacement left)
- (replace bound-idx replacement right)))
+ (<tag> (replace parameter-idx replacement left)
+ (replace parameter-idx replacement right)))
([#.Sum]
[#.Product]
[#.Function]
[#.Apply])
- (#.Bound idx)
- (if (n/= bound-idx idx)
+ (#.Parameter idx)
+ (if (n/= parameter-idx idx)
replacement
type)
(^template [<tag>]
(<tag> env quantified)
- (<tag> (list/map (replace bound-idx replacement) env)
- (replace (n/+ +2 bound-idx) replacement quantified)))
+ (<tag> (list/map (replace parameter-idx replacement) env)
+ (replace (n/+ +2 parameter-idx) replacement quantified)))
([#.UnivQ]
[#.ExQ])
diff --git a/stdlib/source/lux/lang/compiler/extension/analysis/host.jvm.lux b/stdlib/source/lux/lang/compiler/extension/analysis/host.jvm.lux
index 2de55b223..9b742b415 100644
--- a/stdlib/source/lux/lang/compiler/extension/analysis/host.jvm.lux
+++ b/stdlib/source/lux/lang/compiler/extension/analysis/host.jvm.lux
@@ -597,7 +597,7 @@
arity
(|> (list.n/range +0 (dec arity))
list.reverse
- (list/map (|>> (n/* +2) inc #.Bound))
+ (list/map (|>> (n/* +2) inc #.Parameter))
(#.Primitive class-name)
(type.univ-q arity)))))
@@ -959,16 +959,16 @@
true
(list.zip2 arg-classes parameters))))))
-(def: idx-to-bound
+(def: idx-to-parameter
(-> Nat Type)
- (|>> (n/* +2) inc #.Bound))
+ (|>> (n/* +2) inc #.Parameter))
(def: (type-vars amount offset)
(-> Nat Nat (List Type))
(if (n/= +0 amount)
(list)
(|> (list.n/range offset (|> amount dec (n/+ offset)))
- (list/map idx-to-bound))))
+ (list/map idx-to-parameter))))
(def: (method-to-type method-style method)
(-> Method-style Method (Meta [Type (List Type)]))
diff --git a/stdlib/source/lux/lang/type.lux b/stdlib/source/lux/lang/type.lux
index acc3d9046..cd18e103d 100644
--- a/stdlib/source/lux/lang/type.lux
+++ b/stdlib/source/lux/lang/type.lux
@@ -37,7 +37,7 @@
([#.UnivQ]
[#.ExQ])
- (#.Bound idx)
+ (#.Parameter idx)
(maybe.default (error! (text/compose "Unknown type var: " (nat/encode idx)))
(list.nth idx env))
@@ -59,7 +59,7 @@
(^template [<tag>]
[(<tag> xid) (<tag> yid)]
(n/= yid xid))
- ([#.Var] [#.Ex] [#.Bound])
+ ([#.Var] [#.Ex] [#.Parameter])
(^or [(#.Function xleft xright) (#.Function yleft yright)]
[(#.Apply xleft xright) (#.Apply yleft yright)])
@@ -172,7 +172,7 @@
(^template [<tag>]
(<tag> idx)
(` (<tag> (~ (code.nat idx)))))
- ([#.Var] [#.Ex] [#.Bound])
+ ([#.Var] [#.Ex] [#.Parameter])
(^template [<tag>]
(<tag> left right)
@@ -223,7 +223,7 @@
(list/fold text/compose ""))
" " (to-text out) ")"))
- (#.Bound idx)
+ (#.Parameter idx)
(nat/encode idx)
(#.Var id)
diff --git a/stdlib/source/lux/lang/type/check.lux b/stdlib/source/lux/lang/type/check.lux
index 2e255d47c..482ea66bf 100644
--- a/stdlib/source/lux/lang/type/check.lux
+++ b/stdlib/source/lux/lang/type/check.lux
@@ -651,7 +651,7 @@
[paramsT+' (monad.map @ clean paramsT+)]
(wrap (#.Primitive name paramsT+')))
- (^or (#.Bound _) (#.Ex _) (#.Named _))
+ (^or (#.Parameter _) (#.Ex _) (#.Named _))
(:: Monad<Check> wrap inputT)
(^template [<tag>]
diff --git a/stdlib/source/lux/macro/poly.lux b/stdlib/source/lux/macro/poly.lux
index 39c3ffbbb..2eb2e9ebc 100644
--- a/stdlib/source/lux/macro/poly.lux
+++ b/stdlib/source/lux/macro/poly.lux
@@ -155,7 +155,7 @@
(recur (inc current-arg)
(|> env'
(dict.put funcI [headT funcL])
- (dict.put (inc funcI) [(#.Bound (inc funcI)) varL]))
+ (dict.put (inc funcI) [(#.Parameter (inc funcI)) varL]))
(#.Cons varL all-varsL)))
(let [partialI (|> current-arg (n/* +2) (n/+ funcI))
partial-varI (inc partialI)
@@ -166,7 +166,7 @@
(recur (inc current-arg)
(|> env'
(dict.put partialI [.Nothing partialC])
- (dict.put partial-varI [(#.Bound partial-varI) partial-varL]))
+ (dict.put partial-varI [(#.Parameter partial-varI) partial-varL]))
(#.Cons partial-varL all-varsL))))
[all-varsL env']))]]
(|> (do @
@@ -213,26 +213,26 @@
(def: (adjusted-idx env idx)
(-> Env Nat Nat)
(let [env-level (n// +2 (dict.size env))
- bound-level (n// +2 idx)
- bound-idx (n/% +2 idx)]
- (|> env-level dec (n/- bound-level) (n/* +2) (n/+ bound-idx))))
+ parameter-level (n// +2 idx)
+ parameter-idx (n/% +2 idx)]
+ (|> env-level dec (n/- parameter-level) (n/* +2) (n/+ parameter-idx))))
-(def: #export bound
+(def: #export parameter
(Poly Code)
(do p.Monad<Parser>
[env ..env
headT any]
(case headT
- (#.Bound idx)
+ (#.Parameter idx)
(case (dict.get (adjusted-idx env idx) env)
(#.Some [poly-type poly-code])
(wrap poly-code)
#.None
- (p.fail ($_ text/compose "Unknown bound type: " (type.to-text headT))))
+ (p.fail ($_ text/compose "Unknown parameter type: " (type.to-text headT))))
_
- (p.fail ($_ text/compose "Not a bound type: " (type.to-text headT))))))
+ (p.fail ($_ text/compose "Not a parameter type: " (type.to-text headT))))))
(def: #export (var id)
(-> Nat (Poly Any))
@@ -240,15 +240,15 @@
[env ..env
headT any]
(case headT
- (#.Bound idx)
+ (#.Parameter idx)
(if (n/= id (adjusted-idx env idx))
(wrap [])
- (p.fail ($_ text/compose "Wrong bound type.\n"
+ (p.fail ($_ text/compose "Wrong parameter type.\n"
"Expected: " (nat/encode id) "\n"
" Actual: " (nat/encode idx))))
_
- (p.fail ($_ text/compose "Not a bound type: " (type.to-text headT))))))
+ (p.fail ($_ text/compose "Not a parameter type: " (type.to-text headT))))))
(exception: #export (not-existential-type {type Type})
(type.to-text type))
@@ -297,7 +297,7 @@
[env ..env
headT any]
(case (type.un-name headT)
- (^multi (#.Apply (#.Named ["lux" "Nothing"] _) (#.Bound funcT-idx))
+ (^multi (#.Apply (#.Named ["lux" "Nothing"] _) (#.Parameter funcT-idx))
(n/= +0 (adjusted-idx env funcT-idx))
[(dict.get +0 env) (#.Some [self-type self-call])])
(wrap self-call)
@@ -313,7 +313,7 @@
_ (local (list funcT) (var +0))
allC (let [allT (list& funcT argsT)]
(|> allT
- (monad.map @ (function.constant bound))
+ (monad.map @ (function.constant parameter))
(local allT)))]
(wrap (` ((~+ allC))))))
@@ -398,13 +398,13 @@
(` (<tag> (~ (code.nat idx)))))
([#.Var] [#.Ex])
- (#.Bound idx)
+ (#.Parameter idx)
(let [idx (adjusted-idx env idx)]
(if (n/= +0 idx)
(|> (dict.get idx env) maybe.assume product.left (to-code env))
(` (.$ (~ (code.nat (dec idx)))))))
- (#.Apply (#.Named ["lux" "Nothing"] _) (#.Bound idx))
+ (#.Apply (#.Named ["lux" "Nothing"] _) (#.Parameter idx))
(let [idx (adjusted-idx env idx)]
(if (n/= +0 idx)
(|> (dict.get idx env) maybe.assume product.left (to-code env))
diff --git a/stdlib/source/lux/macro/poly/equality.lux b/stdlib/source/lux/macro/poly/equality.lux
index bdf70d622..c834509d8 100644
--- a/stdlib/source/lux/macro/poly/equality.lux
+++ b/stdlib/source/lux/macro/poly/equality.lux
@@ -132,8 +132,8 @@
(do @
[[funcC argsC] (poly.apply (p.seq Eq<?> (p.many Eq<?>)))]
(wrap (` ((~ funcC) (~+ argsC)))))
- ## Bound type-vars
- poly.bound
+ ## Parameters
+ poly.parameter
## Polymorphism
(do @
[[funcC varsC bodyC] (poly.polymorphic Eq<?>)]
diff --git a/stdlib/source/lux/macro/poly/functor.lux b/stdlib/source/lux/macro/poly/functor.lux
index 525b292c7..bf9421cde 100644
--- a/stdlib/source/lux/macro/poly/functor.lux
+++ b/stdlib/source/lux/macro/poly/functor.lux
@@ -82,7 +82,7 @@
(do p.Monad<Parser>
[_ poly.recursive-call]
(wrap (` ((~' map) (~ funcC) (~ valueC)))))
- ## Bound type-variables
+ ## Parameters
(do p.Monad<Parser>
[_ poly.any]
(wrap valueC))
diff --git a/stdlib/source/lux/macro/poly/json.lux b/stdlib/source/lux/macro/poly/json.lux
index ba8512835..dac1874e9 100644
--- a/stdlib/source/lux/macro/poly/json.lux
+++ b/stdlib/source/lux/macro/poly/json.lux
@@ -189,7 +189,7 @@
//.JSON)))
(function ((~ funcC) (~+ varsC))
(~ bodyC))))))
- poly.bound
+ poly.parameter
poly.recursive-call
## If all else fails...
(p.fail (format "Cannot create JSON encoder for: " (type.to-text inputT)))
@@ -284,7 +284,7 @@
(//.Reader ((~ (poly.to-code *env* inputT)) (~+ varsC)))))
(function ((~ funcC) (~+ varsC))
(~ bodyC))))))
- poly.bound
+ poly.parameter
poly.recursive-call
## If all else fails...
(p.fail (format "Cannot create JSON decoder for: " (type.to-text inputT)))
diff --git a/stdlib/source/lux/type/object/interface.lux b/stdlib/source/lux/type/object/interface.lux
index 393fa929f..e4b08c9ac 100644
--- a/stdlib/source/lux/type/object/interface.lux
+++ b/stdlib/source/lux/type/object/interface.lux
@@ -184,10 +184,10 @@
size
(|> (dec size)
(list.n/range +0)
- (list/map (|>> (n/* +2) inc code.nat (~) #.Bound (`)))
+ (list/map (|>> (n/* +2) inc code.nat (~) #.Parameter (`)))
(list.zip2 (list.reverse mappings))
- (list/fold (function (_ [mappingC boundC] genericC)
- (code.replace boundC mappingC genericC))
+ (list/fold (function (_ [mappingC parameterC] genericC)
+ (code.replace parameterC mappingC genericC))
typeC))))
(def: referenceS
@@ -335,7 +335,7 @@
(^template [<tag>]
(<tag> idx)
(meta/wrap (` (<tag> (~ (code.nat idx))))))
- ([#.Bound]
+ ([#.Parameter]
[#.Var]
[#.Ex])