aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/poly
diff options
context:
space:
mode:
Diffstat (limited to '')
-rw-r--r--stdlib/source/poly/lux/abstract/equivalence.lux32
-rw-r--r--stdlib/source/poly/lux/abstract/functor.lux28
-rw-r--r--stdlib/source/poly/lux/data/format/json.lux68
3 files changed, 64 insertions, 64 deletions
diff --git a/stdlib/source/poly/lux/abstract/equivalence.lux b/stdlib/source/poly/lux/abstract/equivalence.lux
index bc633d1ed..a75f56f2d 100644
--- a/stdlib/source/poly/lux/abstract/equivalence.lux
+++ b/stdlib/source/poly/lux/abstract/equivalence.lux
@@ -115,15 +115,15 @@
(in (` (: (~ (@Equivalence inputT))
(function ((~ g!_) (~ g!left) (~ g!right))
(case [(~ g!left) (~ g!right)]
- (~+ (list\join (list\map (function (_ [tag g!eq])
- (if (nat.= last tag)
- (list (` [((~ (code.nat (-- tag))) #1 (~ g!left))
- ((~ (code.nat (-- tag))) #1 (~ g!right))])
- (` ((~ g!eq) (~ g!left) (~ g!right))))
- (list (` [((~ (code.nat tag)) #0 (~ g!left))
- ((~ (code.nat tag)) #0 (~ g!right))])
- (` ((~ g!eq) (~ g!left) (~ g!right))))))
- (list.enumeration members))))
+ (~+ (list\conjoint (list\each (function (_ [tag g!eq])
+ (if (nat.= last tag)
+ (list (` [((~ (code.nat (-- tag))) #1 (~ g!left))
+ ((~ (code.nat (-- tag))) #1 (~ g!right))])
+ (` ((~ g!eq) (~ g!left) (~ g!right))))
+ (list (` [((~ (code.nat tag)) #0 (~ g!left))
+ ((~ (code.nat tag)) #0 (~ g!right))])
+ (` ((~ g!eq) (~ g!left) (~ g!right))))))
+ (list.enumeration members))))
(~ g!_)
#0))))))
... Tuples
@@ -131,13 +131,13 @@
[g!eqs (<type>.tuple (<>.many equivalence))
.let [g!_ (code.local_identifier "_____________")
indices (list.indices (list.size g!eqs))
- g!lefts (list\map (|>> nat\encoded (text\compose "left") code.local_identifier) indices)
- g!rights (list\map (|>> nat\encoded (text\compose "right") code.local_identifier) indices)]]
+ g!lefts (list\each (|>> nat\encoded (text\composite "left") code.local_identifier) indices)
+ g!rights (list\each (|>> nat\encoded (text\composite "right") code.local_identifier) indices)]]
(in (` (: (~ (@Equivalence inputT))
(function ((~ g!_) [(~+ g!lefts)] [(~+ g!rights)])
(and (~+ (|> (list.zipped/3 g!eqs g!lefts g!rights)
- (list\map (function (_ [g!eq g!left g!right])
- (` ((~ g!eq) (~ g!left) (~ g!right)))))))))))))
+ (list\each (function (_ [g!eq g!left g!right])
+ (` ((~ g!eq) (~ g!left) (~ g!right)))))))))))))
... Type recursion
(do !
[[g!self bodyC] (<type>.recursive equivalence)
@@ -156,13 +156,13 @@
(do !
[[funcC varsC bodyC] (<type>.polymorphic equivalence)]
(in (` (: (All [(~+ varsC)]
- (-> (~+ (list\map (|>> (~) ((~! /.Equivalence)) (`)) varsC))
+ (-> (~+ (list\each (|>> (~) ((~! /.Equivalence)) (`)) varsC))
((~! /.Equivalence) ((~ (poly.code *env* inputT)) (~+ varsC)))))
(function ((~ funcC) (~+ varsC))
(~ bodyC))))))
<type>.recursive_call
... If all else fails...
(|> <type>.any
- (\ ! map (|>> %.type (format "Cannot create Equivalence for: ") <>.failure))
- (\ ! join))
+ (\ ! each (|>> %.type (format "Cannot create Equivalence for: ") <>.failure))
+ (\ ! conjoint))
))))
diff --git a/stdlib/source/poly/lux/abstract/functor.lux b/stdlib/source/poly/lux/abstract/functor.lux
index d68d55af8..e607f1174 100644
--- a/stdlib/source/poly/lux/abstract/functor.lux
+++ b/stdlib/source/poly/lux/abstract/functor.lux
@@ -38,7 +38,7 @@
(function (_ unwrappedT)
(if (n.= 1 num_vars)
(` ((~! /.Functor) (~ (poly.code *env* unwrappedT))))
- (let [paramsC (|> num_vars -- list.indices (list\map (|>> %.nat code.local_identifier)))]
+ (let [paramsC (|> num_vars -- list.indices (list\each (|>> %.nat code.local_identifier)))]
(` (All [(~+ paramsC)]
((~! /.Functor) ((~ (poly.code *env* unwrappedT)) (~+ paramsC)))))))))
Arg<?> (: (-> Code (<type>.Parser Code))
@@ -55,13 +55,13 @@
membersC (<type>.variant (p.many (Arg<?> valueC)))
.let [last (-- (list.size membersC))]]
(in (` (case (~ valueC)
- (~+ (list\join (list\map (function (_ [tag memberC])
- (if (n.= last tag)
- (list (` ((~ (code.nat (-- tag))) #1 (~ valueC)))
- (` ((~ (code.nat (-- tag))) #1 (~ memberC))))
- (list (` ((~ (code.nat tag)) #0 (~ valueC)))
- (` ((~ (code.nat tag)) #0 (~ memberC))))))
- (list.enumeration membersC))))))))
+ (~+ (list\conjoint (list\each (function (_ [tag memberC])
+ (if (n.= last tag)
+ (list (` ((~ (code.nat (-- tag))) #1 (~ valueC)))
+ (` ((~ (code.nat (-- tag))) #1 (~ memberC))))
+ (list (` ((~ (code.nat tag)) #0 (~ valueC)))
+ (` ((~ (code.nat tag)) #0 (~ memberC))))))
+ (list.enumeration membersC))))))))
... Tuples
(do p.monad
[pairsCC (: (<type>.Parser (List [Code Code]))
@@ -73,11 +73,11 @@
[_ (in [])
memberC (Arg<?> slotC)]
(recur (++ idx)
- (list\compose pairsCC (list [slotC memberC])))))
+ (list\composite pairsCC (list [slotC memberC])))))
(in pairsCC)))))]
(in (` (case (~ valueC)
- [(~+ (list\map product.left pairsCC))]
- [(~+ (list\map product.right pairsCC))]))))
+ [(~+ (list\each product.left pairsCC))]
+ [(~+ (list\each product.right pairsCC))]))))
... Functions
(do !
[_ (in [])
@@ -87,14 +87,14 @@
(Arg<?> outL))
.let [inC+ (|> (list.size inT+)
list.indices
- (list\map (|>> %.nat (format "____________inC") code.local_identifier)))]]
+ (list\each (|>> %.nat (format "____________inC") code.local_identifier)))]]
(in (` (function ((~ g!) (~+ inC+))
(let [(~ outL) ((~ valueC) (~+ inC+))]
(~ outC))))))
... Recursion
(do p.monad
[_ <type>.recursive_call]
- (in (` ((~' map) (~ funcC) (~ valueC)))))
+ (in (` ((~' each) (~ funcC) (~ valueC)))))
... Parameters
(do p.monad
[_ <type>.any]
@@ -106,5 +106,5 @@
(p.failure (format "Cannot create Functor for: " (%.type inputT)))))]
(in (` (: (~ (@Functor inputT))
(implementation
- (def: ((~' map) (~ funcC) (~ inputC))
+ (def: ((~' each) (~ funcC) (~ inputC))
(~ outputC))))))))
diff --git a/stdlib/source/poly/lux/data/format/json.lux b/stdlib/source/poly/lux/data/format/json.lux
index be290d301..8de72193b 100644
--- a/stdlib/source/poly/lux/data/format/json.lux
+++ b/stdlib/source/poly/lux/data/format/json.lux
@@ -76,7 +76,7 @@
(def: encoded
(|>> .nat (\ nat_codec encoded)))
(def: decoded
- (|>> (\ nat_codec decoded) (\ try.functor map .int))))
+ (|>> (\ nat_codec decoded) (\ try.functor each .int))))
(def: (nullable writer)
{#.doc "Builds a JSON generator for potentially inexistent values."}
@@ -95,7 +95,7 @@
(\ ..int_codec encoded)))
(def: decoded
(|>> (\ ..int_codec decoded)
- (\ try.functor map (debug.private unit.in)))))
+ (\ try.functor each (debug.private unit.in)))))
(poly: encoded
(with_expansions
@@ -147,8 +147,8 @@
encoded))]
(in (` (: (~ (@JSON\encoded inputT))
(|>> ((~! dictionary.entries))
- ((~! list\map) (function ((~ g!_) [(~ g!key) (~ g!val)])
- [(~ g!key) ((~ =val=) (~ g!val))]))
+ ((~! list\each) (function ((~ g!_) [(~ g!key) (~ g!val)])
+ [(~ g!key) ((~ =val=) (~ g!val))]))
((~! dictionary.of_list) (~! text.hash))
#/.Object)))))
(do !
@@ -162,7 +162,7 @@
(<type>.exactly .List)
encoded))]
(in (` (: (~ (@JSON\encoded inputT))
- (|>> ((~! list\map) (~ =sub=)) ((~! row.of_list)) #/.Array)))))
+ (|>> ((~! list\each) (~ =sub=)) ((~! row.of_list)) #/.Array)))))
(do !
[.let [g!_ (code.local_identifier "_______")
g!input (code.local_identifier "_______input")]
@@ -171,28 +171,28 @@
(in (` (: (~ (@JSON\encoded inputT))
(function ((~ g!_) (~ g!input))
(case (~ g!input)
- (~+ (list\join (list\map (function (_ [tag g!encoded])
- (if (n.= last tag)
- (.list (` ((~ (code.nat (-- tag))) #1 (~ g!input)))
- (` ((~! /.json) [(~ (code.frac (..tag (-- tag))))
- #1
- ((~ g!encoded) (~ g!input))])))
- (.list (` ((~ (code.nat tag)) #0 (~ g!input)))
- (` ((~! /.json) [(~ (code.frac (..tag tag)))
- #0
- ((~ g!encoded) (~ g!input))])))))
- (list.enumeration members))))))))))
+ (~+ (list\conjoint (list\each (function (_ [tag g!encoded])
+ (if (n.= last tag)
+ (.list (` ((~ (code.nat (-- tag))) #1 (~ g!input)))
+ (` ((~! /.json) [(~ (code.frac (..tag (-- tag))))
+ #1
+ ((~ g!encoded) (~ g!input))])))
+ (.list (` ((~ (code.nat tag)) #0 (~ g!input)))
+ (` ((~! /.json) [(~ (code.frac (..tag tag)))
+ #0
+ ((~ g!encoded) (~ g!input))])))))
+ (list.enumeration members))))))))))
(do !
[g!encoders (<type>.tuple (<>.many encoded))
.let [g!_ (code.local_identifier "_______")
g!members (|> (list.size g!encoders)
list.indices
- (list\map (|>> n\encoded code.local_identifier)))]]
+ (list\each (|>> n\encoded code.local_identifier)))]]
(in (` (: (~ (@JSON\encoded inputT))
(function ((~ g!_) [(~+ g!members)])
- ((~! /.json) [(~+ (list\map (function (_ [g!member g!encoded])
- (` ((~ g!encoded) (~ g!member))))
- (list.zipped/2 g!members g!encoders)))]))))))
+ ((~! /.json) [(~+ (list\each (function (_ [g!member g!encoded])
+ (` ((~ g!encoded) (~ g!member))))
+ (list.zipped/2 g!members g!encoders)))]))))))
... Type recursion
(do !
[[selfC non_recC] (<type>.recursive encoded)
@@ -209,8 +209,8 @@
(do !
[[funcC varsC bodyC] (<type>.polymorphic encoded)]
(in (` (: (All [(~+ varsC)]
- (-> (~+ (list\map (function (_ varC) (` (-> (~ varC) /.JSON)))
- varsC))
+ (-> (~+ (list\each (function (_ varC) (` (-> (~ varC) /.JSON)))
+ varsC))
(-> ((~ (poly.code *env* inputT)) (~+ varsC))
/.JSON)))
(function ((~ funcC) (~+ varsC))
@@ -282,17 +282,17 @@
.let [last (-- (list.size members))]]
(in (` (: (~ (@JSON\decoded inputT))
($_ ((~! <>.or))
- (~+ (list\map (function (_ [tag memberC])
- (if (n.= last tag)
- (` (|> (~ memberC)
- ((~! <>.after) ((~! </>.boolean!) (~ (code.bit #1))))
- ((~! <>.after) ((~! </>.number!) (~ (code.frac (..tag (-- tag))))))
- ((~! </>.array))))
- (` (|> (~ memberC)
- ((~! <>.after) ((~! </>.boolean!) (~ (code.bit #0))))
- ((~! <>.after) ((~! </>.number!) (~ (code.frac (..tag tag)))))
- ((~! </>.array))))))
- (list.enumeration members))))))))
+ (~+ (list\each (function (_ [tag memberC])
+ (if (n.= last tag)
+ (` (|> (~ memberC)
+ ((~! <>.after) ((~! </>.boolean!) (~ (code.bit #1))))
+ ((~! <>.after) ((~! </>.number!) (~ (code.frac (..tag (-- tag))))))
+ ((~! </>.array))))
+ (` (|> (~ memberC)
+ ((~! <>.after) ((~! </>.boolean!) (~ (code.bit #0))))
+ ((~! <>.after) ((~! </>.number!) (~ (code.frac (..tag tag)))))
+ ((~! </>.array))))))
+ (list.enumeration members))))))))
(do !
[g!decoders (<type>.tuple (<>.many decoded))]
(in (` (: (~ (@JSON\decoded inputT))
@@ -313,7 +313,7 @@
(do !
[[funcC varsC bodyC] (<type>.polymorphic decoded)]
(in (` (: (All [(~+ varsC)]
- (-> (~+ (list\map (|>> (~) </>.Parser (`)) varsC))
+ (-> (~+ (list\each (|>> (~) </>.Parser (`)) varsC))
(</>.Parser ((~ (poly.code *env* inputT)) (~+ varsC)))))
(function ((~ funcC) (~+ varsC))
(~ bodyC))))))