diff options
Diffstat (limited to 'stdlib/source/lux/abstract')
-rw-r--r-- | stdlib/source/lux/abstract/codec.lux | 3 | ||||
-rw-r--r-- | stdlib/source/lux/abstract/enum.lux | 1 | ||||
-rw-r--r-- | stdlib/source/lux/abstract/monad.lux | 42 |
3 files changed, 24 insertions, 22 deletions
diff --git a/stdlib/source/lux/abstract/codec.lux b/stdlib/source/lux/abstract/codec.lux index abe80ba4a..f0056f176 100644 --- a/stdlib/source/lux/abstract/codec.lux +++ b/stdlib/source/lux/abstract/codec.lux @@ -3,7 +3,8 @@ [data ["." error (#+ Error)]]] [// - monad]) + [monad (#+ do)] + ["." functor]]) (signature: #export (Codec m a) {#.doc "A way to move back-and-forth between a type and an alternative representation for it."} diff --git a/stdlib/source/lux/abstract/enum.lux b/stdlib/source/lux/abstract/enum.lux index 5bbb7df38..07d7f0ec5 100644 --- a/stdlib/source/lux/abstract/enum.lux +++ b/stdlib/source/lux/abstract/enum.lux @@ -1,6 +1,7 @@ (.module: [lux #*] [// + [equivalence (#+)] ["." order]]) (signature: #export (Enum e) diff --git a/stdlib/source/lux/abstract/monad.lux b/stdlib/source/lux/abstract/monad.lux index 0e509c64e..0772d8c98 100644 --- a/stdlib/source/lux/abstract/monad.lux +++ b/stdlib/source/lux/abstract/monad.lux @@ -3,7 +3,7 @@ [// ["." functor (#+ Functor)]]) -(def: (list;fold f init xs) +(def: (list@fold f init xs) (All [a b] (-> (-> b a a) a (List b) a)) (case xs @@ -11,9 +11,9 @@ init (#.Cons x xs') - (list;fold f (f x init) xs'))) + (list@fold f (f x init) xs'))) -(def: (list;size xs) +(def: (list@size xs) (All [a] (-> (List a) Nat)) (loop [counter 0 xs xs] @@ -27,7 +27,7 @@ (def: (reverse xs) (All [a] (-> (List a) (List a))) - (list;fold (function (_ head tail) (#.Cons head tail)) + (list@fold (function (_ head tail) (#.Cons head tail)) #.Nil xs)) @@ -60,11 +60,11 @@ (wrap (f3 z))))} (case tokens (#.Cons monad (#.Cons [_ (#.Tuple bindings)] (#.Cons body #.Nil))) - (if (|> bindings list;size (n/% 2) (n/= 0)) + (if (|> bindings list@size (n/% 2) (n/= 0)) (let [g!_ (: Code [_cursor (#.Identifier ["" " _ "])]) g!map (: Code [_cursor (#.Identifier ["" " map "])]) g!join (: Code [_cursor (#.Identifier ["" " join "])]) - body' (list;fold (: (-> [Code Code] Code Code) + body' (list@fold (: (-> [Code Code] Code Code) (function (_ binding body') (let [[var value] binding] (case var @@ -94,55 +94,55 @@ (All [M a] (-> (Monad M) (List (M a)) (M (List a)))) - (let [(^open "!;.") monad] + (let [(^open "!@.") monad] (function (recur xs) (case xs #.Nil - (!;wrap #.Nil) + (!@wrap #.Nil) (#.Cons x xs') (|> x - (!;map (function (_ _x) - (!;map (|>> (#.Cons _x)) (recur xs')))) - !;join))))) + (!@map (function (_ _x) + (!@map (|>> (#.Cons _x)) (recur xs')))) + !@join))))) (def: #export (map monad f) {#.doc "Apply a monadic function to all values in a list."} (All [M a b] (-> (Monad M) (-> a (M b)) (List a) (M (List b)))) - (let [(^open "!;.") monad] + (let [(^open "!@.") monad] (function (recur xs) (case xs #.Nil - (!;wrap #.Nil) + (!@wrap #.Nil) (#.Cons x xs') (|> (f x) - (!;map (function (_ _x) - (!;map (|>> (#.Cons _x)) (recur xs')))) - !;join))))) + (!@map (function (_ _x) + (!@map (|>> (#.Cons _x)) (recur xs')))) + !@join))))) (def: #export (filter Monad<!> f) {#.doc "Filter the values in a list with a monadic function."} (All [! a b] (-> (Monad !) (-> a (! Bit)) (List a) (! (List a)))) - (let [(^open "!;.") Monad<!>] + (let [(^open "!@.") Monad<!>] (function (recur xs) (case xs #.Nil - (!;wrap #.Nil) + (!@wrap #.Nil) (#.Cons head xs') (|> (f head) - (!;map (function (_ verdict) - (!;map (function (_ tail) + (!@map (function (_ verdict) + (!@map (function (_ tail) (if verdict (#.Cons head tail) tail)) (recur xs')))) - !;join))))) + !@join))))) (def: #export (fold monad f init xs) {#.doc "Fold a list with a monadic function."} |