From 031f26b3fc854ec565957011bbcdcafb9fe19d9e Mon Sep 17 00:00:00 2001 From: Brian Marick Date: Sun, 6 May 2018 13:49:13 -0500 Subject: [PATCH 1/5] Minor improvements --- examples/src/PrismsForSumTypes.purs | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/examples/src/PrismsForSumTypes.purs b/examples/src/PrismsForSumTypes.purs index f0fa331..2dfa3e4 100644 --- a/examples/src/PrismsForSumTypes.purs +++ b/examples/src/PrismsForSumTypes.purs @@ -7,13 +7,13 @@ module PrismsForSumTypes where Use a Prism if you want to write code like this: preview prismForSolidFill $ Solid Color.white - -- (Just rgba 255 255 255 1.0) + -- Just Color.white preview prismForSolidFill NoFill -- Nothing review prismForSolidFill Color.white - -- (Solid rgba 255 255 255 1.0) + -- Solid Color.white -} {- If you want to try out examples, paste the following into the repl. @@ -159,9 +159,7 @@ l2 = review linearFocus { color1 : Color.black } - {------ Constructing more specific prisms ------} - --- `only` is used to check for a specific value: + {------ Use `only` to focus on specific values ------} whiteToBlackFocus :: Prism' Fill Unit whiteToBlackFocus = only fillWhiteToBlack @@ -181,6 +179,8 @@ o3 = is whiteToBlackFocus fillRadial :: Boolean -- Note that `only` requires `Fill` to implement `Eq`. -- It's the only prism constructor that does. + {------ Use `nearly` to focus on a sub-case ------} + -- `nearly` is typically used to look for a specific case (like other -- prisms), but also accepts only values that are close to some target From aa6ed53131b1cd1db8775303fee1d5950895d0ad Mon Sep 17 00:00:00 2001 From: Brian Marick Date: Sun, 6 May 2018 13:49:59 -0500 Subject: [PATCH 2/5] Add API documentation for `Prism` --- src/Data/Lens/Prism.purs | 108 ++++++++++++++++++++++++++++++++++++--- 1 file changed, 102 insertions(+), 6 deletions(-) diff --git a/src/Data/Lens/Prism.purs b/src/Data/Lens/Prism.purs index 3869a4e..98ea193 100644 --- a/src/Data/Lens/Prism.purs +++ b/src/Data/Lens/Prism.purs @@ -1,7 +1,45 @@ --- | This module defines functions for working with prisms. +-- | Prisms are used for selecting cases of a type, most often a sum +-- | type. Consider this: +-- | +-- | ```purescript +-- | data Fill -- think of a paint program filling a shape +-- | = Solid Color +-- | ... +-- | ``` +-- | +-- | A prism that focuses on `Solid` fills would be written like this: +-- | +-- | ```purescript +-- | solidFocus :: Prism' Fill Color +-- | solidFocus = prism' Solid case _ of +-- | Solid color -> Just color +-- | _ -> Nothing +-- | ``` +-- | +-- | ... and used like this: +-- | +-- | ```purescript +-- | preview solidFocus (Solid Color.white) == Just Color.white +-- | preview solidFocus NoFill == Nothing +-- | +-- | is solidFocus (Solid Color.white) == true +-- | ``` +-- | +-- | `review` can be used to go from a `Color` to a `Fill`: +-- | +-- | ```purescript +-- | review solidFocus Color.white == Solid Color.white +-- | ``` +-- | +-- | For more information, see `PrismsForSumTypes` in the +-- | `examples/src` directory. + module Data.Lens.Prism - ( prism, prism', review, nearly, only, clonePrism, withPrism, matching + ( prism, prism' + , only, nearly + , review , is, isn't + , clonePrism, withPrism, matching , module ExportTypes ) where @@ -18,23 +56,79 @@ import Data.Profunctor (dimap, rmap) import Data.Profunctor.Choice (right) import Data.Newtype (under) --- | Create a `Prism` from a constructor/pattern pair. +-- | Create a `Prism` from a constructor and a "focus" function that +-- | produces an `Either`: +-- | +-- | ```purescript +-- | solidFocus' :: Prism' Fill Color +-- | solidFocus' = prism Solid case _ of +-- | Solid color -> Right color +-- | anotherCase -> Left anotherCase +-- | ``` prism :: forall s t a b. (b -> t) -> (s -> Either t a) -> Prism s t a b prism to fro pab = dimap fro (either id id) (right (rmap to pab)) +-- | Create a `Prism` from a constructor and a "focus" function that +-- | produces an `Maybe`: +-- | +-- | ```purescript +-- | solidFocus' :: Prism' Fill Color +-- | solidFocus' = prism' Solid case _ of +-- | Solid color -> Just color +-- | _ -> Nothing +-- | ``` prism' :: forall s a. (a -> s) -> (s -> Maybe a) -> Prism' s a prism' to fro = prism to (\s -> maybe (Left s) Right (fro s)) --- | Review a value through a `Prism`. -review :: forall s t a b. Review s t a b -> b -> t -review = under Tagged +-- | Create a prism that focuses on only some of the values of a case, +-- | such as solid colors that are "bright enough": +-- | +-- | ```purescript +-- | brightSolidFocus :: Prism' Fill Unit +-- | brightSolidFocus = nearly (Solid referenceColor) predicate +-- | where +-- | referenceColor = Color.graytone 0.8 +-- | predicate = case _ of +-- | Solid color -> +-- | Color.brightness color >= Color.brightness referenceColor +-- | _ -> +-- | false +-- | +-- | preview brightSolidFocus (Solid Color.white) == Just unit +-- | preview brightSolidFocus (Solid Color.black) == Nothing +-- | preview brightSolidFocus NoFill == Nothing +-- | +-- | is brightSolidFocus (Solid Color.white) == true +-- | review brightSolidFocus unit == Color.graytone 0.8 +-- | ``` + nearly :: forall a. a -> (a -> Boolean) -> Prism' a Unit nearly x f = prism' (const x) (guard <<< f) +-- | `only` focuses not just on a case, but a specific value of that case. +-- | +-- | ```purescript +-- | solidWhiteFocus :: Prism' Fill Unit +-- | solidWhiteFocus = only $ Solid Color.white +-- | +-- | is solidWhiteFocus (Solid Color.white) == true +-- | preview solidWhiteFocus (Solid Color.white) == Just unit +-- | review solidWhiteFocus unit == Solid Color.white +-- | ``` only :: forall a. Eq a => a -> Prism a a Unit Unit only x = nearly x (_ == x) + +-- | Create the "whole" corresponding to a specific "part": +-- | +-- | ```purescript +-- | -- solidFocus is a `Prism Fill Color` +-- | review solidFocus Color.white == Solid Color.white +-- | ``` +review :: forall s t a b. Review s t a b -> b -> t +review = under Tagged + clonePrism :: forall s t a b. APrism s t a b -> Prism s t a b clonePrism l = withPrism l \x y p -> prism x y p @@ -45,8 +139,10 @@ withPrism l f = case l (Market id Right) of matching :: forall s t a b. APrism s t a b -> s -> Either t a matching l = withPrism l \_ f -> f +--| Would `preview prism` produce a `Just`? is :: forall s t a b r. HeytingAlgebra r => APrism s t a b -> s -> r is l = either (const ff) (const tt) <<< matching l +--| Would `preview prism` produce a `Nothing`? isn't :: forall s t a b r. HeytingAlgebra r => APrism s t a b -> s -> r isn't l = not <<< is l From ef9e53eb32fa359d2a71693a9f5826b271f19683 Mon Sep 17 00:00:00 2001 From: Brian Marick Date: Mon, 7 May 2018 12:56:54 -0500 Subject: [PATCH 3/5] Traversal commentary --- src/Data/Lens/Traversal.purs | 61 +++++++++++++++++++++++++++++++++--- 1 file changed, 57 insertions(+), 4 deletions(-) diff --git a/src/Data/Lens/Traversal.purs b/src/Data/Lens/Traversal.purs index 7ba9d99..f86405a 100644 --- a/src/Data/Lens/Traversal.purs +++ b/src/Data/Lens/Traversal.purs @@ -1,12 +1,30 @@ --- | This module defines functions for working with traversals. +-- | `Traversal` is an optic that focuses on zero or more functor values. An +-- | `Array` would be a typical example: +-- | +-- | ```purescript +-- | over traversed negate [1, 2, 3] == [-1, -2, -3] +-- | preview traversed [1, 2, 3] == Just 1 +-- | firstOf traversed [1, 2, 3] == Just 1 -- same as `preview` +-- | lastOf traversed [1, 2, 3] == Just 3 +-- | ``` +-- | +-- | `view` might surprise you. It assumes that the wrapped values +-- | are a monoid, and `append`s them together: +-- | +-- | ```purescript +-- | view traversed ["D", "a", "w", "n"] == "Dawn" +-- | ``` +-- | +-- | Many of the functions you'll use are documented in `Data.Lens.Fold`. + module Data.Lens.Traversal ( traversed + , element , traverseOf , sequenceOf , failover , elementsOf , itraverseOf - , element , module ExportTypes ) where @@ -24,7 +42,12 @@ import Data.Traversable (class Traversable, traverse) import Data.Tuple (Tuple(..), uncurry) import Data.Newtype (under, unwrap) --- | Create a `Traversal` which traverses the elements of a `Traversable` functor. +-- | A `Traversal` for the elements of a `Traversable` functor. +-- | +-- | ```purescript +-- | over traversed negate [1, 2, 3] == [-1,-2,-3] +-- | over traversed negate (Just 3) == Just -3 +-- | ``` traversed :: forall t a b. Traversable t => Traversal (t a) (t b) a b traversed = wander traverse @@ -37,6 +60,29 @@ traverseOf = under Star -- | Sequence the foci of a `Traversal`, pulling out an `Applicative` effect. -- | If you do not need the result, see `sequenceOf_` for `Fold`s. +-- | +-- | `sequenceOf traversed` has the same result as `Data.Traversable.sequence`: +-- | +-- | ```purescript +-- | sequenceOf traversed (Just [1, 2]) == [Just 1, Just 2] +-- | sequence (Just [1, 2]) == [Just 1, Just 2] +-- | ``` +-- | +-- | An example with effects: +-- | ```purescript +-- | > array = [random, random] +-- | > :t array +-- | Array (Eff ... Number) +-- | +-- | > effect = sequenceOf traversed array +-- | > :t effect +-- | Eff ... (Array Number) +-- | +-- | > effect >>= logShow +-- | [0.15556037108154985,0.28500369615270515] +-- | unit +-- | ``` + sequenceOf :: forall f s t a . Applicative f @@ -56,7 +102,14 @@ failover t f s = case unwrap (t $ Star $ Tuple (Disj true) <<< f) s of Tuple (Disj true) x -> pure x Tuple (Disj false) _ -> empty --- | Affine traversal the `n`-th focus of a `Traversal`. +-- | Combine an index and a traversal to narrow the focus to a single +-- | element. This is called an "affine traversal". Compare to `Data.Lens.Index`. +-- | +-- | ```purescript +-- | set (element 2 traversed) 8888 [0, 0, 3] == [0, 0, 8888] +-- | preview (element 2 traversed) [0, 0, 3] == Just 3 +-- | ``` + element :: forall p s t a . Wander p From 5bc06447f93bbc990ff688767b4b7ed59d93b29a Mon Sep 17 00:00:00 2001 From: Brian Marick Date: Mon, 7 May 2018 17:37:35 -0500 Subject: [PATCH 4/5] Minor improvements to function documentation --- src/Data/Lens/Prism.purs | 28 ++++++++++++++-------------- 1 file changed, 14 insertions(+), 14 deletions(-) diff --git a/src/Data/Lens/Prism.purs b/src/Data/Lens/Prism.purs index 98ea193..c974c7b 100644 --- a/src/Data/Lens/Prism.purs +++ b/src/Data/Lens/Prism.purs @@ -3,11 +3,12 @@ -- | -- | ```purescript -- | data Fill -- think of a paint program filling a shape --- | = Solid Color --- | ... +-- | = NoFill +-- | | Solid Color +-- | | ... -- | ``` -- | --- | A prism that focuses on `Solid` fills would be written like this: +-- | A prism that focuses on `Solid` fills could be written like this: -- | -- | ```purescript -- | solidFocus :: Prism' Fill Color @@ -31,15 +32,15 @@ -- | review solidFocus Color.white == Solid Color.white -- | ``` -- | --- | For more information, see `PrismsForSumTypes` in the +-- | For more information, see `PrismsForSumTypes.purs` in the -- | `examples/src` directory. module Data.Lens.Prism ( prism, prism' , only, nearly , review - , is, isn't - , clonePrism, withPrism, matching + , is, isn't, matching + , clonePrism, withPrism , module ExportTypes ) where @@ -60,8 +61,8 @@ import Data.Newtype (under) -- | produces an `Either`: -- | -- | ```purescript --- | solidFocus' :: Prism' Fill Color --- | solidFocus' = prism Solid case _ of +-- | solidFocus :: Prism' Fill Color +-- | solidFocus = prism Solid case _ of -- | Solid color -> Right color -- | anotherCase -> Left anotherCase -- | ``` @@ -69,11 +70,11 @@ prism :: forall s t a b. (b -> t) -> (s -> Either t a) -> Prism s t a b prism to fro pab = dimap fro (either id id) (right (rmap to pab)) -- | Create a `Prism` from a constructor and a "focus" function that --- | produces an `Maybe`: +-- | produces a `Maybe`: -- | -- | ```purescript --- | solidFocus' :: Prism' Fill Color --- | solidFocus' = prism' Solid case _ of +-- | solidFocus :: Prism' Fill Color +-- | solidFocus = prism' Solid case _ of -- | Solid color -> Just color -- | _ -> Nothing -- | ``` @@ -123,7 +124,6 @@ only x = nearly x (_ == x) -- | Create the "whole" corresponding to a specific "part": -- | -- | ```purescript --- | -- solidFocus is a `Prism Fill Color` -- | review solidFocus Color.white == Solid Color.white -- | ``` review :: forall s t a b. Review s t a b -> b -> t @@ -139,10 +139,10 @@ withPrism l f = case l (Market id Right) of matching :: forall s t a b. APrism s t a b -> s -> Either t a matching l = withPrism l \_ f -> f ---| Would `preview prism` produce a `Just`? +--| Ask if `preview prism` would produce a `Just`. is :: forall s t a b r. HeytingAlgebra r => APrism s t a b -> s -> r is l = either (const ff) (const tt) <<< matching l ---| Would `preview prism` produce a `Nothing`? +--| Ask if `preview prism` would produce a `Nothing`. isn't :: forall s t a b r. HeytingAlgebra r => APrism s t a b -> s -> r isn't l = not <<< is l From 0397cd7ef39dfbd85d2cd7e20dfc80c06ecaa835 Mon Sep 17 00:00:00 2001 From: Brian Marick Date: Sat, 12 May 2018 16:01:41 -0500 Subject: [PATCH 5/5] Addressed comments on previous version --- src/Data/Lens/Prism.purs | 72 +++++++++++++++++++++++++----------- src/Data/Lens/Traversal.purs | 8 ++-- 2 files changed, 55 insertions(+), 25 deletions(-) diff --git a/src/Data/Lens/Prism.purs b/src/Data/Lens/Prism.purs index c974c7b..23bb6f5 100644 --- a/src/Data/Lens/Prism.purs +++ b/src/Data/Lens/Prism.purs @@ -34,9 +34,40 @@ -- | -- | For more information, see `PrismsForSumTypes.purs` in the -- | `examples/src` directory. +-- | +-- | --------------- +-- | +-- | A well-behaved `Prism` will follow these laws: +-- | +-- | **review-preview**: `preview` retrieves what `review` creates. Equationally: +-- | +-- | ```purescript +-- | review prism >>> preview prism ≡ Just +-- | ``` +-- | +-- | An example: +-- | +-- | ```purescript +-- | Color.white # review solidFocus # preview solidFocus +-- | == Just Color.white +-- | ``` +-- | +-- | **preview-review**: If `preview` retrieves something, `review` can create +-- | the original from that something. Equationally: +-- | +-- | ```purescript +-- | if preview prism s ≡ Just a then review prism a ≡ s +-- | ``` +-- | +-- | An example: +-- | +-- | ```purescript +-- | Solid Color.white # preview solidFocus <#> review solidFocus +-- | == Solid Color.white +-- | ``` module Data.Lens.Prism - ( prism, prism' + ( prism', prism , only, nearly , review , is, isn't, matching @@ -57,7 +88,7 @@ import Data.Profunctor (dimap, rmap) import Data.Profunctor.Choice (right) import Data.Newtype (under) --- | Create a `Prism` from a constructor and a "focus" function that +-- | Create a `Prism` from a constructor and a matcher function that -- | produces an `Either`: -- | -- | ```purescript @@ -66,10 +97,14 @@ import Data.Newtype (under) -- | Solid color -> Right color -- | anotherCase -> Left anotherCase -- | ``` +-- | +-- | _Note_: The matcher function returns a result wrapped in `Either t` +-- | to allow for type-changing prisms in the case where the input does +-- | not match. prism :: forall s t a b. (b -> t) -> (s -> Either t a) -> Prism s t a b prism to fro pab = dimap fro (either id id) (right (rmap to pab)) --- | Create a `Prism` from a constructor and a "focus" function that +-- | Create a `Prism` from a constructor and a matcher function that -- | produces a `Maybe`: -- | -- | ```purescript @@ -81,29 +116,18 @@ prism to fro pab = dimap fro (either id id) (right (rmap to pab)) prism' :: forall s a. (a -> s) -> (s -> Maybe a) -> Prism' s a prism' to fro = prism to (\s -> maybe (Left s) Right (fro s)) --- | Create a prism that focuses on only some of the values of a case, --- | such as solid colors that are "bright enough": +-- | `nearly` is a variant of `only`. Like `only`, `nearly` produces +-- | a prism that matches +-- | a single value. Unlike `only`, it uses a predicate you supply +-- | instead of depending on `class Eq`: -- | -- | ```purescript --- | brightSolidFocus :: Prism' Fill Unit --- | brightSolidFocus = nearly (Solid referenceColor) predicate +-- | solidWhiteFocus :: Prism' Fill Unit +-- | solidWhiteFocus = nearly (Solid Color.white) predicate -- | where --- | referenceColor = Color.graytone 0.8 --- | predicate = case _ of --- | Solid color -> --- | Color.brightness color >= Color.brightness referenceColor --- | _ -> --- | false --- | --- | preview brightSolidFocus (Solid Color.white) == Just unit --- | preview brightSolidFocus (Solid Color.black) == Nothing --- | preview brightSolidFocus NoFill == Nothing --- | --- | is brightSolidFocus (Solid Color.white) == true --- | review brightSolidFocus unit == Color.graytone 0.8 +-- | predicate candidate = +-- | color.toHexString == Color.white.toHexString -- | ``` - - nearly :: forall a. a -> (a -> Boolean) -> Prism' a Unit nearly x f = prism' (const x) (guard <<< f) @@ -117,6 +141,10 @@ nearly x f = prism' (const x) (guard <<< f) -- | preview solidWhiteFocus (Solid Color.white) == Just unit -- | review solidWhiteFocus unit == Solid Color.white -- | ``` +-- | +-- | *Note*: `only` depends on `Eq`. Strange definitions of `(==)` +-- | (for example, that it counts any `Fill` as being equal to `Solid Color.white`) +-- | will create a prism that violates the preview-review law. only :: forall a. Eq a => a -> Prism a a Unit Unit only x = nearly x (_ == x) diff --git a/src/Data/Lens/Traversal.purs b/src/Data/Lens/Traversal.purs index f86405a..9109c58 100644 --- a/src/Data/Lens/Traversal.purs +++ b/src/Data/Lens/Traversal.purs @@ -1,4 +1,4 @@ --- | `Traversal` is an optic that focuses on zero or more functor values. An +-- | `Traversal` is an optic that focuses on zero or more values. An -- | `Array` would be a typical example: -- | -- | ```purescript @@ -103,13 +103,15 @@ failover t f s = case unwrap (t $ Star $ Tuple (Disj true) <<< f) s of Tuple (Disj false) _ -> empty -- | Combine an index and a traversal to narrow the focus to a single --- | element. This is called an "affine traversal". Compare to `Data.Lens.Index`. +-- | element. Compare to `Data.Lens.Index`. -- | -- | ```purescript -- | set (element 2 traversed) 8888 [0, 0, 3] == [0, 0, 8888] -- | preview (element 2 traversed) [0, 0, 3] == Just 3 -- | ``` - +-- | The resulting traversal is called an *affine traversal*, which +-- | means that the traversal focuses on one or zero (if the index is out of range) +-- | results. element :: forall p s t a . Wander p