diff options
Diffstat (limited to '')
-rw-r--r-- | stdlib/source/lux/abstract/apply.lux | 4 | ||||
-rw-r--r-- | stdlib/source/lux/abstract/codec.lux | 4 | ||||
-rw-r--r-- | stdlib/source/lux/abstract/comonad.lux | 2 | ||||
-rw-r--r-- | stdlib/source/lux/abstract/comonad/cofree.lux | 4 | ||||
-rw-r--r-- | stdlib/source/lux/abstract/enum.lux | 2 | ||||
-rw-r--r-- | stdlib/source/lux/abstract/equivalence.lux | 8 | ||||
-rw-r--r-- | stdlib/source/lux/abstract/fold.lux | 2 | ||||
-rw-r--r-- | stdlib/source/lux/abstract/functor.lux | 8 | ||||
-rw-r--r-- | stdlib/source/lux/abstract/functor/contravariant.lux | 2 | ||||
-rw-r--r-- | stdlib/source/lux/abstract/hash.lux | 6 | ||||
-rw-r--r-- | stdlib/source/lux/abstract/interval.lux | 29 | ||||
-rw-r--r-- | stdlib/source/lux/abstract/monad.lux | 2 | ||||
-rw-r--r-- | stdlib/source/lux/abstract/monad/free.lux | 6 | ||||
-rw-r--r-- | stdlib/source/lux/abstract/monad/indexed.lux | 2 | ||||
-rw-r--r-- | stdlib/source/lux/abstract/monoid.lux | 4 | ||||
-rw-r--r-- | stdlib/source/lux/abstract/order.lux | 6 | ||||
-rw-r--r-- | stdlib/source/lux/abstract/predicate.lux | 4 |
17 files changed, 49 insertions, 46 deletions
diff --git a/stdlib/source/lux/abstract/apply.lux b/stdlib/source/lux/abstract/apply.lux index 21d3fb2df..6f0e61ba8 100644 --- a/stdlib/source/lux/abstract/apply.lux +++ b/stdlib/source/lux/abstract/apply.lux @@ -4,7 +4,7 @@ [monad (#+ Monad)] ["." functor (#+ Functor)]]) -(signature: #export (Apply f) +(interface: #export (Apply f) {#.doc "Applicative functors."} (: (Functor f) &functor) @@ -12,7 +12,7 @@ (-> (f (-> a b)) (f a) (f b))) apply)) -(structure: #export (compose f-monad f-apply g-apply) +(implementation: #export (compose f-monad f-apply g-apply) {#.doc "Applicative functor composition."} (All [F G] (-> (Monad F) (Apply F) (Apply G) diff --git a/stdlib/source/lux/abstract/codec.lux b/stdlib/source/lux/abstract/codec.lux index ad59ce450..454b64cb5 100644 --- a/stdlib/source/lux/abstract/codec.lux +++ b/stdlib/source/lux/abstract/codec.lux @@ -6,14 +6,14 @@ [monad (#+ do)] ["." functor]]) -(signature: #export (Codec m a) +(interface: #export (Codec m a) {#.doc "A way to move back-and-forth between a type and an alternative representation for it."} (: (-> a m) encode) (: (-> m (Try a)) decode)) -(structure: #export (compose cb-codec ba-codec) +(implementation: #export (compose cb-codec ba-codec) {#.doc "Codec composition."} (All [a b c] (-> (Codec c b) (Codec b a) diff --git a/stdlib/source/lux/abstract/comonad.lux b/stdlib/source/lux/abstract/comonad.lux index eeccf9351..63565bd3a 100644 --- a/stdlib/source/lux/abstract/comonad.lux +++ b/stdlib/source/lux/abstract/comonad.lux @@ -11,7 +11,7 @@ [// [functor (#+ Functor)]]) -(signature: #export (CoMonad w) +(interface: #export (CoMonad w) {#.doc (doc "CoMonads are the opposite/complement to monads." "CoMonadic structures are often infinite in size and built upon lazily-evaluated functions.")} (: (Functor w) diff --git a/stdlib/source/lux/abstract/comonad/cofree.lux b/stdlib/source/lux/abstract/comonad/cofree.lux index 8e43cd9bf..64413f1ce 100644 --- a/stdlib/source/lux/abstract/comonad/cofree.lux +++ b/stdlib/source/lux/abstract/comonad/cofree.lux @@ -8,13 +8,13 @@ {#.doc "The CoFree CoMonad."} [a (F (CoFree F a))]) -(structure: #export (functor dsl) +(implementation: #export (functor dsl) (All [F] (-> (Functor F) (Functor (CoFree F)))) (def: (map f [head tail]) [(f head) (\ dsl map (map f) tail)])) -(structure: #export (comonad dsl) +(implementation: #export (comonad dsl) (All [F] (-> (Functor F) (CoMonad (CoFree F)))) (def: &functor (..functor dsl)) diff --git a/stdlib/source/lux/abstract/enum.lux b/stdlib/source/lux/abstract/enum.lux index 0c099feb2..d98848f78 100644 --- a/stdlib/source/lux/abstract/enum.lux +++ b/stdlib/source/lux/abstract/enum.lux @@ -3,7 +3,7 @@ [// ["." order (#+ Order)]]) -(signature: #export (Enum e) +(interface: #export (Enum e) {#.doc "Enumerable types, with a notion of moving forward and backwards through a type's instances."} (: (Order e) &order) (: (-> e e) succ) diff --git a/stdlib/source/lux/abstract/equivalence.lux b/stdlib/source/lux/abstract/equivalence.lux index 3948d12bd..58d644c9b 100644 --- a/stdlib/source/lux/abstract/equivalence.lux +++ b/stdlib/source/lux/abstract/equivalence.lux @@ -4,21 +4,21 @@ [functor ["." contravariant]]]) -(signature: #export (Equivalence a) +(interface: #export (Equivalence a) {#.doc "Equivalence for a type's instances."} (: (-> a a Bit) =)) (def: #export (rec sub) (All [a] (-> (-> (Equivalence a) (Equivalence a)) (Equivalence a))) - (structure + (implementation (def: (= left right) (sub = left right)))) -(structure: #export functor +(implementation: #export functor (contravariant.Functor Equivalence) (def: (map f equivalence) - (structure + (implementation (def: (= reference sample) (\ equivalence = (f reference) (f sample)))))) diff --git a/stdlib/source/lux/abstract/fold.lux b/stdlib/source/lux/abstract/fold.lux index fd309b5f0..3f957bb55 100644 --- a/stdlib/source/lux/abstract/fold.lux +++ b/stdlib/source/lux/abstract/fold.lux @@ -3,7 +3,7 @@ [// [monoid (#+ Monoid)]]) -(signature: #export (Fold F) +(interface: #export (Fold F) {#.doc "Iterate over a structure's values to build a summary value."} (: (All [a b] (-> (-> b a a) a (F b) a)) diff --git a/stdlib/source/lux/abstract/functor.lux b/stdlib/source/lux/abstract/functor.lux index 03c10eaaf..d3012b686 100644 --- a/stdlib/source/lux/abstract/functor.lux +++ b/stdlib/source/lux/abstract/functor.lux @@ -1,6 +1,6 @@ (.module: lux) -(signature: #export (Functor f) +(interface: #export (Functor f) (: (All [a b] (-> (-> a b) (-> (f a) (f b)))) @@ -14,7 +14,7 @@ (def: #export (sum (^open "f\.") (^open "g\.")) (All [F G] (-> (Functor F) (Functor G) (Functor (..Or F G)))) - (structure + (implementation (def: (map f fa|ga) (case fa|ga (#.Left fa) @@ -28,7 +28,7 @@ (def: #export (product (^open "f\.") (^open "g\.")) (All [F G] (-> (Functor F) (Functor G) (Functor (..And F G)))) - (structure + (implementation (def: (map f [fa ga]) [(f\map f fa) (g\map f ga)]))) @@ -39,6 +39,6 @@ (def: #export (compose (^open "f\.") (^open "g\.")) {#.doc "Functor composition."} (All [F G] (-> (Functor F) (Functor G) (Functor (..Then F G)))) - (structure + (implementation (def: (map f fga) (f\map (g\map f) fga)))) diff --git a/stdlib/source/lux/abstract/functor/contravariant.lux b/stdlib/source/lux/abstract/functor/contravariant.lux index 79ae218fa..d91813e1f 100644 --- a/stdlib/source/lux/abstract/functor/contravariant.lux +++ b/stdlib/source/lux/abstract/functor/contravariant.lux @@ -1,7 +1,7 @@ (.module: [lux #*]) -(signature: #export (Functor f) +(interface: #export (Functor f) (: (All [a b] (-> (-> b a) (-> (f a) (f b)))) diff --git a/stdlib/source/lux/abstract/hash.lux b/stdlib/source/lux/abstract/hash.lux index 9a8b44dfb..14857ef18 100644 --- a/stdlib/source/lux/abstract/hash.lux +++ b/stdlib/source/lux/abstract/hash.lux @@ -5,7 +5,7 @@ [functor ["." contravariant]]]) -(signature: #export (Hash a) +(interface: #export (Hash a) {#.doc (doc "A way to produce hash-codes for a type's instances." "A necessity when working with some data-structures, such as dictionaries or sets.")} (: (Equivalence a) @@ -13,11 +13,11 @@ (: (-> a Nat) hash)) -(structure: #export functor +(implementation: #export functor (contravariant.Functor Hash) (def: (map f super) - (structure + (implementation (def: &equivalence (\ equivalence.functor map f (\ super &equivalence))) diff --git a/stdlib/source/lux/abstract/interval.lux b/stdlib/source/lux/abstract/interval.lux index fbe3a4c8a..e43529890 100644 --- a/stdlib/source/lux/abstract/interval.lux +++ b/stdlib/source/lux/abstract/interval.lux @@ -6,7 +6,7 @@ ["." order] [enum (#+ Enum)]]) -(signature: #export (Interval a) +(interface: #export (Interval a) {#.doc "A representation of top and bottom boundaries for an ordered type."} (: (Enum a) &enum) @@ -19,14 +19,14 @@ (def: #export (between enum bottom top) (All [a] (-> (Enum a) a a (Interval a))) - (structure + (implementation (def: &enum enum) (def: bottom bottom) (def: top top))) (def: #export (singleton enum elem) (All [a] (-> (Enum a) a (Interval a))) - (structure + (implementation (def: &enum enum) (def: bottom elem) (def: top elem))) @@ -74,22 +74,25 @@ (def: #export (union left right) (All [a] (-> (Interval a) (Interval a) (Interval a))) - (structure (def: &enum (get@ #&enum right)) - (def: bottom (order.min (\ right &order) (\ left bottom) (\ right bottom))) - (def: top (order.max (\ right &order) (\ left top) (\ right top))))) + (implementation + (def: &enum (get@ #&enum right)) + (def: bottom (order.min (\ right &order) (\ left bottom) (\ right bottom))) + (def: top (order.max (\ right &order) (\ left top) (\ right top))))) (def: #export (intersection left right) (All [a] (-> (Interval a) (Interval a) (Interval a))) - (structure (def: &enum (get@ #&enum right)) - (def: bottom (order.max (\ right &order) (\ left bottom) (\ right bottom))) - (def: top (order.min (\ right &order) (\ left top) (\ right top))))) + (implementation + (def: &enum (get@ #&enum right)) + (def: bottom (order.max (\ right &order) (\ left bottom) (\ right bottom))) + (def: top (order.min (\ right &order) (\ left top) (\ right top))))) (def: #export (complement interval) (All [a] (-> (Interval a) (Interval a))) (let [(^open ".") interval] - (structure (def: &enum (get@ #&enum interval)) - (def: bottom (succ top)) - (def: top (pred bottom))))) + (implementation + (def: &enum (get@ #&enum interval)) + (def: bottom (succ top)) + (def: top (pred bottom))))) (def: #export (precedes? reference sample) (All [a] (-> (Interval a) (Interval a) Bit)) @@ -139,7 +142,7 @@ [finishes? ,\top order.>= ,\bottom] ) -(structure: #export equivalence (All [a] (Equivalence (Interval a))) +(implementation: #export equivalence (All [a] (Equivalence (Interval a))) (def: (= reference sample) (let [(^open ",\.") reference] (and (,\= ,\bottom (\ sample bottom)) diff --git a/stdlib/source/lux/abstract/monad.lux b/stdlib/source/lux/abstract/monad.lux index 900d5cca4..d32bdacbb 100644 --- a/stdlib/source/lux/abstract/monad.lux +++ b/stdlib/source/lux/abstract/monad.lux @@ -42,7 +42,7 @@ _ #.Nil)) -(signature: #export (Monad m) +(interface: #export (Monad m) (: (Functor m) &functor) (: (All [a] diff --git a/stdlib/source/lux/abstract/monad/free.lux b/stdlib/source/lux/abstract/monad/free.lux index 3eb01064d..7a9efbeea 100644 --- a/stdlib/source/lux/abstract/monad/free.lux +++ b/stdlib/source/lux/abstract/monad/free.lux @@ -10,7 +10,7 @@ (#Pure a) (#Effect (F (Free F a)))) -(structure: #export (functor dsl) +(implementation: #export (functor dsl) (All [F] (-> (Functor F) (Functor (Free F)))) (def: (map f ea) @@ -21,7 +21,7 @@ (#Effect value) (#Effect (\ dsl map (map f) value))))) -(structure: #export (apply dsl) +(implementation: #export (apply dsl) (All [F] (-> (Functor F) (Apply (Free F)))) (def: &functor (..functor dsl)) @@ -42,7 +42,7 @@ ff)) ))) -(structure: #export (monad dsl) +(implementation: #export (monad dsl) (All [F] (-> (Functor F) (Monad (Free F)))) (def: &functor (..functor dsl)) diff --git a/stdlib/source/lux/abstract/monad/indexed.lux b/stdlib/source/lux/abstract/monad/indexed.lux index b6c603d0c..5a5a63b27 100644 --- a/stdlib/source/lux/abstract/monad/indexed.lux +++ b/stdlib/source/lux/abstract/monad/indexed.lux @@ -11,7 +11,7 @@ [syntax (#+ syntax:)] ["." code]]]) -(signature: #export (IxMonad m) +(interface: #export (IxMonad m) (: (All [p a] (-> a (m p p a))) wrap) diff --git a/stdlib/source/lux/abstract/monoid.lux b/stdlib/source/lux/abstract/monoid.lux index c87cf8b40..2b5560421 100644 --- a/stdlib/source/lux/abstract/monoid.lux +++ b/stdlib/source/lux/abstract/monoid.lux @@ -1,7 +1,7 @@ (.module: [lux #*]) -(signature: #export (Monoid a) +(interface: #export (Monoid a) {#.doc (doc "A way to compose values." "Includes an identity value which does not alter any other value when combined with.")} (: a @@ -11,7 +11,7 @@ (def: #export (compose left right) (All [l r] (-> (Monoid l) (Monoid r) (Monoid [l r]))) - (structure + (implementation (def: identity [(\ left identity) (\ right identity)]) diff --git a/stdlib/source/lux/abstract/order.lux b/stdlib/source/lux/abstract/order.lux index 21f5739d2..9d031bca2 100644 --- a/stdlib/source/lux/abstract/order.lux +++ b/stdlib/source/lux/abstract/order.lux @@ -7,7 +7,7 @@ [functor ["." contravariant]]]) -(signature: #export (Order a) +(interface: #export (Order a) {#.doc "A signature for types that possess some sense of ordering among their elements."} (: (Equivalence a) @@ -45,11 +45,11 @@ Choice (if (\ order < y x) y x)) -(structure: #export functor +(implementation: #export functor (contravariant.Functor Order) (def: (map f order) - (structure + (implementation (def: &equivalence (\ equivalence.functor map f (\ order &equivalence))) diff --git a/stdlib/source/lux/abstract/predicate.lux b/stdlib/source/lux/abstract/predicate.lux index 13aa9a083..03b071fa4 100644 --- a/stdlib/source/lux/abstract/predicate.lux +++ b/stdlib/source/lux/abstract/predicate.lux @@ -26,7 +26,7 @@ ) (template [<name> <identity> <composition>] - [(structure: #export <name> + [(implementation: #export <name> (All [a] (Monoid (Predicate a))) (def: identity <identity>) @@ -53,7 +53,7 @@ (function (recur input) (predicate recur input))) -(structure: #export functor +(implementation: #export functor (contravariant.Functor Predicate) (def: (map f fb) |