aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/library/lux/type/resource.lux
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib/source/library/lux/type/resource.lux')
-rw-r--r--stdlib/source/library/lux/type/resource.lux52
1 files changed, 26 insertions, 26 deletions
diff --git a/stdlib/source/library/lux/type/resource.lux b/stdlib/source/library/lux/type/resource.lux
index 5fc4e760a..dc321578e 100644
--- a/stdlib/source/library/lux/type/resource.lux
+++ b/stdlib/source/library/lux/type/resource.lux
@@ -48,9 +48,9 @@
(implementation: (indexed Monad<m>)
(All [m] (-> (Monad m) (IxMonad (Procedure m))))
- (def: (wrap value)
+ (def: (in value)
(function (_ keys)
- (\ Monad<m> wrap [keys value])))
+ (\ Monad<m> in [keys value])))
(def: (bind f input)
(function (_ keysI)
@@ -67,14 +67,14 @@
(All [v] (-> (Linear <m> v) (<m> v)))
(do <monad>
[[_ output] (procedure [])]
- (wrap output)))
+ (in output)))
(def: #export (<lift> procedure)
(All [v] (-> (<m> v) (Linear <m> v)))
(function (_ keys)
(do <monad>
[output procedure]
- (wrap [keys output]))))]
+ (in [keys output]))))]
[pure Identity identity.monad run_pure lift_pure]
[sync IO io.monad run_sync lift_sync]
@@ -106,7 +106,7 @@
[(def: #export (<name> value)
(All [v] (Ex [k] (-> v (Affine <m> (Key <mode> k) (Res k v)))))
(function (_ keys)
- (\ <monad> wrap [[(<key> []) keys] (:abstraction value)])))]
+ (\ <monad> in [[(<key> []) keys] (:abstraction value)])))]
[ordered_pure Identity identity.monad Ordered ordered_key]
[ordered_sync IO io.monad Ordered ordered_key]
@@ -121,7 +121,7 @@
(All [v k m]
(-> (Res k v) (Relevant <m> (Key m k) v)))
(function (_ [key keys])
- (\ <monad> wrap [keys (:representation resource)])))]
+ (\ <monad> in [keys (:representation resource)])))]
[read_pure Identity identity.monad]
[read_sync IO io.monad]
@@ -140,25 +140,25 @@
(do {! <>.monad}
[done? <code>.end?]
(if done?
- (wrap (list))
+ (in (list))
(do !
[head <code>.nat
_ (<>.assert (exception.construct ..index_cannot_be_repeated head)
(not (set.member? seen head)))
tail (recur (set.add head seen))]
- (wrap (list& head tail))))))))
+ (in (list& head tail))))))))
(def: (no_op Monad<m>)
(All [m] (-> (Monad m) (Linear m Any)))
(function (_ context)
- (\ Monad<m> wrap [context []])))
+ (\ Monad<m> in [context []])))
(template [<name> <m> <monad>]
[(syntax: #export (<name> {swaps ..indices})
(macro.with_gensyms [g!_ g!context]
(case swaps
#.Nil
- (wrap (list (` ((~! no_op) <monad>))))
+ (in (list (` ((~! no_op) <monad>))))
(#.Cons head tail)
(do {! meta.monad}
@@ -168,20 +168,20 @@
(function (_ from to)
(do maybe.monad
[input (list.nth from g!inputs)]
- (wrap (row.add input to))))
+ (in (row.add input to))))
(: (Row Code) row.empty)
swaps)
maybe.assume
row.to_list)
g!inputsT+ (list\map (|>> (~) (..Key ..Commutative) (`)) g!inputs)
g!outputsT+ (list\map (|>> (~) (..Key ..Commutative) (`)) g!outputs)]]
- (wrap (list (` (: (All [(~+ g!inputs) (~ g!context)]
- (Procedure (~! <m>)
- [(~+ g!inputsT+) (~ g!context)]
- [(~+ g!outputsT+) (~ g!context)]
- .Any))
- (function ((~ g!_) [(~+ g!inputs) (~ g!context)])
- (\ (~! <monad>) (~' wrap) [[(~+ g!outputs) (~ g!context)] []]))))))))))]
+ (in (list (` (: (All [(~+ g!inputs) (~ g!context)]
+ (Procedure (~! <m>)
+ [(~+ g!inputsT+) (~ g!context)]
+ [(~+ g!outputsT+) (~ g!context)]
+ .Any))
+ (function ((~ g!_) [(~+ g!inputs) (~ g!context)])
+ (\ (~! <monad>) (~' in) [[(~+ g!outputs) (~ g!context)] []]))))))))))]
[exchange_pure Identity identity.monad]
[exchange_sync IO io.monad]
@@ -194,20 +194,20 @@
[raw <code>.nat
_ (<>.assert (exception.construct ..amount_cannot_be_zero [])
(n.> 0 raw))]
- (wrap raw)))
+ (in raw)))
(template [<name> <m> <monad> <from> <to>]
[(syntax: #export (<name> {amount ..amount})
(macro.with_gensyms [g!_ g!context]
(do {! meta.monad}
[g!keys (<| (monad.seq !) (list.repeat amount) (macro.gensym "keys"))]
- (wrap (list (` (: (All [(~+ g!keys) (~ g!context)]
- (Procedure (~! <m>)
- [<from> (~ g!context)]
- [<to> (~ g!context)]
- .Any))
- (function ((~ g!_) [<from> (~ g!context)])
- (\ (~! <monad>) (~' wrap) [[<to> (~ g!context)] []])))))))))]
+ (in (list (` (: (All [(~+ g!keys) (~ g!context)]
+ (Procedure (~! <m>)
+ [<from> (~ g!context)]
+ [<to> (~ g!context)]
+ .Any))
+ (function ((~ g!_) [<from> (~ g!context)])
+ (\ (~! <monad>) (~' in) [[<to> (~ g!context)] []])))))))))]
[group_pure Identity identity.monad (~+ g!keys) [(~+ g!keys)]]
[group_sync IO io.monad (~+ g!keys) [(~+ g!keys)]]