Skip to content

Commit ffaac75

Browse files
committed
Prepare for 2.0 release
1 parent be6ecac commit ffaac75

29 files changed

+261
-288
lines changed

bower.json

Lines changed: 8 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -12,16 +12,15 @@
1212
"url": "git://github.com/purescript-contrib/purescript-profunctor-lenses.git"
1313
},
1414
"dependencies": {
15-
"purescript-const": "^1.0.0",
16-
"purescript-functor-coproducts": "^1.0.0",
17-
"purescript-functor-products": "^1.0.0",
18-
"purescript-identity": "^1.0.0",
19-
"purescript-profunctor": "^1.0.0",
20-
"purescript-sets": "^1.0.0",
21-
"purescript-unsafe-coerce": "^1.0.0",
22-
"purescript-transformers": "^1.0.0"
15+
"purescript-const": "^2.0.0",
16+
"purescript-functors": "^1.0.0",
17+
"purescript-identity": "^2.0.0",
18+
"purescript-profunctor": "^2.0.0",
19+
"purescript-sets": "^2.0.0",
20+
"purescript-unsafe-coerce": "^2.0.0",
21+
"purescript-transformers": "^2.0.1"
2322
},
2423
"devDependencies": {
25-
"purescript-console": "^1.0.0"
24+
"purescript-console": "^2.0.0"
2625
}
2726
}

src/Data/Lens.purs

Lines changed: 7 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -22,12 +22,12 @@ module Data.Lens
2222
, module Data.Lens.Common
2323
) where
2424

25-
import Data.Lens.Iso (AnIso, AnIsoP, Iso, IsoP, Optic, Exchange(..), Re(..), au, auf, cloneIso, curried, flipped, iso, re, runRe, uncurried, under, withIso)
26-
import Data.Lens.Lens (ALens, ALensP, Lens, LensP, cloneLens, lens, lens', withLens)
27-
import Data.Lens.Prism (APrism, APrismP, Prism, PrismP, Review, ReviewP, clonePrism, is, isn't, matching, nearly, only, prism, prism', review, withPrism)
28-
import Data.Lens.Traversal (Traversal, TraversalP, element, elementsOf, failover, itraverseOf, sequenceOf, traverseOf, traversed)
29-
import Data.Lens.Types
30-
import Data.Lens.Setter (IndexedSetter, Setter, SetterP, Indexed(..), addModifying, addOver, appendModifying, appendOver, assign, assignJust, conjModifying, conjOver, disjModifying, disjOver, divModifying, divOver, iover, modifying, mulModifying, mulOver, over, set, setJust, subModifying, subOver, (%=), (%~), (&&=), (&&~), (*=), (*~), (++=), (++~), (+=), (+~), (-=), (-~), (.=), (.~), (//=), (//~), (<>=), (<>~), (?=), (?~), (||=), (||~))
25+
import Data.Lens.Iso (AnIso, AnIso', Iso, Iso', Optic, Exchange(..), Re(..), au, auf, cloneIso, curried, flipped, iso, re, uncurried, under, withIso)
26+
import Data.Lens.Lens (ALens, ALens', Lens, Lens', cloneLens, lens, lens', withLens)
27+
import Data.Lens.Prism (APrism, APrism', Prism, Prism', Review, Review', clonePrism, is, isn't, matching, nearly, only, prism, prism', review, withPrism)
28+
import Data.Lens.Traversal (Traversal, Traversal', element, elementsOf, failover, itraverseOf, sequenceOf, traverseOf, traversed)
29+
import Data.Lens.Types (class Wander, ALens, ALens', APrism, APrism', AnIso, AnIso', Fold, Fold', Getter, Getter', IndexedFold, IndexedFold', IndexedGetter, IndexedGetter', IndexedOptic, IndexedOptic', IndexedSetter, IndexedSetter', IndexedTraversal, IndexedTraversal', Iso, Iso', Lens, Lens', Optic, Optic', Prism, Prism', Review, Review', Setter, Setter', Traversal, Traversal', Exchange(..), Forget(..), Indexed(..), Market(..), Re(..), Shop(..), Tagged(..), wander)
30+
import Data.Lens.Setter (IndexedSetter, Setter, Setter', Indexed(..), addModifying, addOver, appendModifying, appendOver, assign, assignJust, conjModifying, conjOver, disjModifying, disjOver, divModifying, divOver, iover, modifying, mulModifying, mulOver, over, set, setJust, subModifying, subOver, (%=), (%~), (&&=), (&&~), (*=), (*~), (++=), (++~), (+=), (+~), (-=), (-~), (.=), (.~), (//=), (//~), (<>=), (<>~), (?=), (?~), (||=), (||~))
3131
import Data.Lens.Getter (Fold, Getter, IndexedFold, IndexedGetter, Optic, Indexed(..), iuse, iview, to, use, view, viewOn, (^.))
32-
import Data.Lens.Fold (Fold, FoldP, allOf, andOf, anyOf, elemOf, filtered, findOf, firstOf, foldMapOf, foldOf, folded, foldlOf, foldrOf, has, hasn't, iallOf, ianyOf, ifoldMapOf, ifoldlOf, ifoldrOf, itoListOf, itraverseOf_, lastOf, lengthOf, maximumOf, minimumOf, notElemOf, orOf, preview, previewOn, productOf, replicated, sequenceOf_, sumOf, toListOf, toListOfOn, unfolded, (^..), (^?))
32+
import Data.Lens.Fold (Fold, Fold', allOf, andOf, anyOf, elemOf, filtered, findOf, firstOf, foldMapOf, foldOf, folded, foldlOf, foldrOf, has, hasn't, iallOf, ianyOf, ifoldMapOf, ifoldlOf, ifoldrOf, itoListOf, itraverseOf_, lastOf, lengthOf, maximumOf, minimumOf, notElemOf, orOf, preview, previewOn, productOf, replicated, sequenceOf_, sumOf, toListOf, toListOfOn, unfolded, (^..), (^?))
3333
import Data.Lens.Common (_1, _2, _Just, _Left, _Nothing, _Right, first, left, right, second, united)

src/Data/Lens/At.purs

Lines changed: 7 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -5,25 +5,26 @@ module Data.Lens.At
55

66
import Prelude
77

8-
import Data.Identity (runIdentity, Identity(..))
8+
import Data.Identity (Identity(..))
99
import Data.Map as M
1010
import Data.Maybe (Maybe(..), maybe)
1111
import Data.Set as S
1212
import Data.StrMap as SM
13+
import Data.Newtype (unwrap)
1314

14-
import Data.Lens (LensP, lens)
15+
import Data.Lens (Lens', lens)
1516
import Data.Lens.Index (class Index)
1617

1718
class (Index m a b) <= At m a b where
18-
at :: a -> LensP m (Maybe b)
19+
at :: a -> Lens' m (Maybe b)
1920

2021
instance atIdentity :: At (Identity a) Unit a where
21-
at _ = lens (Just <<< runIdentity) (flip maybe Identity)
22+
at _ = lens (Just <<< unwrap) (flip maybe Identity)
2223

2324
instance atMaybe :: At (Maybe a) Unit a where
2425
at _ = lens id \_ -> id
2526

26-
instance atSet :: (Ord v) => At (S.Set v) v Unit where
27+
instance atSet :: Ord v => At (S.Set v) v Unit where
2728
at x = lens get (flip update)
2829
where
2930
get xs =
@@ -33,7 +34,7 @@ instance atSet :: (Ord v) => At (S.Set v) v Unit where
3334
update Nothing = S.delete x
3435
update (Just _) = S.insert x
3536

36-
instance atMap :: (Ord k) => At (M.Map k v) k v where
37+
instance atMap :: Ord k => At (M.Map k v) k v where
3738
at k =
3839
lens (M.lookup k) \m ->
3940
maybe (M.delete k m) \v -> M.insert k v m

src/Data/Lens/Fold.purs

Lines changed: 51 additions & 48 deletions
Original file line numberDiff line numberDiff line change
@@ -8,34 +8,36 @@ module Data.Lens.Fold
88
, folded, unfolded
99
, ifoldMapOf, ifoldrOf, ifoldlOf, iallOf, ianyOf, itoListOf, itraverseOf_
1010
, module ExportTypes
11-
) where
11+
)
12+
where
1213

1314
import Prelude
1415

1516
import Data.Either (Either(..), either)
1617
import Data.Foldable (class Foldable, foldMap)
1718
import Data.HeytingAlgebra (tt, ff)
18-
import Data.Lens.Internal.Forget (Forget (..), runForget)
19-
import Data.Lens.Types (Fold, FoldP) as ExportTypes
20-
import Data.Lens.Types (IndexedFold, Fold, OpticP, Indexed(..))
19+
import Data.Lens.Internal.Forget (Forget (..))
20+
import Data.Lens.Types (Fold, Fold') as ExportTypes
21+
import Data.Lens.Types (IndexedFold, Fold, Optic', Indexed(..))
2122
import Data.List (List(..), (:))
2223
import Data.Maybe (Maybe(..), maybe)
23-
import Data.Maybe.First (First(..), runFirst)
24-
import Data.Maybe.Last (Last(..), runLast)
24+
import Data.Maybe.First (First(..))
25+
import Data.Maybe.Last (Last(..))
2526
import Data.Monoid (class Monoid, mempty)
26-
import Data.Monoid.Additive (Additive(..), runAdditive)
27-
import Data.Monoid.Conj (Conj(..), runConj)
28-
import Data.Monoid.Disj (Disj(..), runDisj)
29-
import Data.Monoid.Dual (Dual(..), runDual)
30-
import Data.Monoid.Endo (Endo(..), runEndo)
31-
import Data.Monoid.Multiplicative (Multiplicative(..), runMultiplicative)
27+
import Data.Monoid.Additive (Additive(..))
28+
import Data.Monoid.Conj (Conj(..))
29+
import Data.Monoid.Disj (Disj(..))
30+
import Data.Monoid.Dual (Dual(..))
31+
import Data.Monoid.Endo (Endo(..))
32+
import Data.Monoid.Multiplicative (Multiplicative(..))
33+
import Data.Newtype (unwrap, under)
3234
import Data.Profunctor (dimap)
3335
import Data.Profunctor.Choice (class Choice, right)
3436
import Data.Tuple (Tuple(..), uncurry)
3537

3638
-- | Previews the first value of a fold, if there is any.
3739
preview :: forall s t a b. Fold (First a) s t a b -> s -> Maybe a
38-
preview p = runFirst <<< foldMapOf p (First <<< Just)
40+
preview p = unwrap <<< foldMapOf p (First <<< Just)
3941

4042
-- | Synonym for `preview`, flipped.
4143
previewOn :: forall s t a b. s -> Fold (First a) s t a b -> Maybe a
@@ -45,71 +47,71 @@ infixl 8 previewOn as ^?
4547

4648
-- | Folds all foci of a `Fold` to one. Note that this is the same as `view`.
4749
foldOf :: forall s t a b. Fold a s t a b -> s -> a
48-
foldOf p = runForget (p (Forget id))
50+
foldOf p = foldMapOf p id
4951

5052
-- | Maps and then folds all foci of a `Fold`.
5153
foldMapOf :: forall s t a b r. Fold r s t a b -> (a -> r) -> s -> r
52-
foldMapOf p f = runForget (p (Forget f))
54+
foldMapOf = under Forget
5355

5456
-- | Right fold over a `Fold`.
5557
foldrOf :: forall s t a b r. Fold (Endo r) s t a b -> (a -> r -> r) -> r -> s -> r
56-
foldrOf p f r = flip runEndo r <<< foldMapOf p (Endo <<< f)
58+
foldrOf p f r = flip unwrap r <<< foldMapOf p (Endo <<< f)
5759

5860
-- | Left fold over a `Fold`.
5961
foldlOf :: forall s t a b r. Fold (Dual (Endo r)) s t a b -> (r -> a -> r) -> r -> s -> r
60-
foldlOf p f r = flip runEndo r <<< runDual <<< foldMapOf p (Dual <<< Endo <<< flip f)
62+
foldlOf p f r = flip unwrap r <<< unwrap <<< foldMapOf p (Dual <<< Endo <<< flip f)
6163

6264
-- | Whether all foci of a `Fold` satisfy a predicate.
63-
allOf :: forall s t a b r. (BooleanAlgebra r) => Fold (Conj r) s t a b -> (a -> r) -> s -> r
64-
allOf p f = runConj <<< foldMapOf p (Conj <<< f)
65+
allOf :: forall s t a b r. HeytingAlgebra r => Fold (Conj r) s t a b -> (a -> r) -> s -> r
66+
allOf p f = unwrap <<< foldMapOf p (Conj <<< f)
6567

6668
-- | Whether any focus of a `Fold` satisfies a predicate.
67-
anyOf :: forall s t a b r. (BooleanAlgebra r) => Fold (Disj r) s t a b -> (a -> r) -> s -> r
68-
anyOf p f = runDisj <<< foldMapOf p (Disj <<< f)
69+
anyOf :: forall s t a b r. HeytingAlgebra r => Fold (Disj r) s t a b -> (a -> r) -> s -> r
70+
anyOf p f = unwrap <<< foldMapOf p (Disj <<< f)
6971

7072
-- | The conjunction of all foci of a `Fold`.
71-
andOf :: forall s t a b. (BooleanAlgebra a) => Fold (Conj a) s t a b -> s -> a
73+
andOf :: forall s t a b. HeytingAlgebra a => Fold (Conj a) s t a b -> s -> a
7274
andOf p = allOf p id
7375

7476
-- | The disjunction of all foci of a `Fold`.
75-
orOf :: forall s t a b. (BooleanAlgebra a) => Fold (Disj a) s t a b -> s -> a
77+
orOf :: forall s t a b. HeytingAlgebra a => Fold (Disj a) s t a b -> s -> a
7678
orOf p = anyOf p id
7779

7880
-- | Whether a `Fold` contains a given element.
79-
elemOf :: forall s t a b. (Eq a) => Fold (Disj Boolean) s t a b -> a -> s -> Boolean
81+
elemOf :: forall s t a b. Eq a => Fold (Disj Boolean) s t a b -> a -> s -> Boolean
8082
elemOf p a = anyOf p (_ == a)
8183

8284
-- | Whether a `Fold` not contains a given element.
83-
notElemOf :: forall s t a b. (Eq a) => Fold (Conj Boolean) s t a b -> a -> s -> Boolean
85+
notElemOf :: forall s t a b. Eq a => Fold (Conj Boolean) s t a b -> a -> s -> Boolean
8486
notElemOf p a = allOf p (_ /= a)
8587

8688
-- | The sum of all foci of a `Fold`.
87-
sumOf :: forall s t a b. (Semiring a) => Fold (Additive a) s t a b -> s -> a
88-
sumOf p = runAdditive <<< foldMapOf p Additive
89+
sumOf :: forall s t a b. Semiring a => Fold (Additive a) s t a b -> s -> a
90+
sumOf p = unwrap <<< foldMapOf p Additive
8991

9092
-- | The product of all foci of a `Fold`.
91-
productOf :: forall s t a b. (Semiring a) => Fold (Multiplicative a) s t a b -> s -> a
92-
productOf p = runMultiplicative <<< foldMapOf p Multiplicative
93+
productOf :: forall s t a b. Semiring a => Fold (Multiplicative a) s t a b -> s -> a
94+
productOf p = unwrap <<< foldMapOf p Multiplicative
9395

9496
-- | The number of foci of a `Fold`.
9597
lengthOf :: forall s t a b. Fold (Additive Int) s t a b -> s -> Int
96-
lengthOf p = runAdditive <<< foldMapOf p (const $ Additive 1)
98+
lengthOf p = unwrap <<< foldMapOf p (const $ Additive 1)
9799

98100
-- | The first focus of a `Fold`, if there is any. Synonym for `preview`.
99101
firstOf :: forall s t a b. Fold (First a) s t a b -> s -> Maybe a
100-
firstOf p = runFirst <<< foldMapOf p (First <<< Just)
102+
firstOf p = unwrap <<< foldMapOf p (First <<< Just)
101103

102104
-- | The last focus of a `Fold`, if there is any.
103105
lastOf :: forall s t a b. Fold (Last a) s t a b -> s -> Maybe a
104-
lastOf p = runLast <<< foldMapOf p (Last <<< Just)
106+
lastOf p = unwrap <<< foldMapOf p (Last <<< Just)
105107

106108
-- | The maximum of all foci of a `Fold`, if there is any.
107-
maximumOf :: forall s t a b. (Ord a) => Fold (Endo (Maybe a)) s t a b -> s -> Maybe a
109+
maximumOf :: forall s t a b. Ord a => Fold (Endo (Maybe a)) s t a b -> s -> Maybe a
108110
maximumOf p = foldrOf p (\a -> Just <<< maybe a (max a)) Nothing where
109111
max a b = if a > b then a else b
110112

111113
-- | The minimum of all foci of a `Fold`, if there is any.
112-
minimumOf :: forall s t a b. (Ord a) => Fold (Endo (Maybe a)) s t a b -> s -> Maybe a
114+
minimumOf :: forall s t a b. Ord a => Fold (Endo (Maybe a)) s t a b -> s -> Maybe a
113115
minimumOf p = foldrOf p (\a -> Just <<< maybe a (min a)) Nothing where
114116
min a b = if a < b then a else b
115117

@@ -125,7 +127,7 @@ sequenceOf_
125127
=> Fold (Endo (f Unit)) s t (f a) b
126128
-> s
127129
-> f Unit
128-
sequenceOf_ p = flip runEndo (pure unit) <<< foldMapOf p \f -> Endo (f *> _)
130+
sequenceOf_ p = flip unwrap (pure unit) <<< foldMapOf p \f -> Endo (f *> _)
129131

130132
-- | Traverse the foci of a `Fold`, discarding the results.
131133
traverseOf_
@@ -149,29 +151,30 @@ infixl 8 toListOfOn as ^..
149151

150152
-- | Determines whether a `Fold` has at least one focus.
151153
has :: forall s t a b r. HeytingAlgebra r => Fold (Disj r) s t a b -> s -> r
152-
has p = runDisj <<< foldMapOf p (const (Disj tt))
154+
has p = unwrap <<< foldMapOf p (const (Disj tt))
153155

154156
-- | Determines whether a `Fold` does not have a focus.
155157
hasn't :: forall s t a b r. HeytingAlgebra r => Fold (Conj r) s t a b -> s -> r
156-
hasn't p = runConj <<< foldMapOf p (const (Conj ff))
158+
hasn't p = unwrap <<< foldMapOf p (const (Conj ff))
157159

158160
-- | Filters on a predicate.
159-
filtered :: forall p a. (Choice p) => (a -> Boolean) -> OpticP p a a
161+
filtered :: forall p a. Choice p => (a -> Boolean) -> Optic' p a a
160162
filtered f =
161163
right >>>
162164
dimap
163165
(\x -> if f x then Right x else Left x)
164166
(either id id)
165167

166168
-- | Replicates the elements of a fold.
167-
replicated :: forall a b t r. (Monoid r) => Int -> Fold r a b a t
168-
replicated n = Forget <<< go n <<< runForget where
169+
replicated :: forall a b t r. Monoid r => Int -> Fold r a b a t
170+
replicated i (Forget a) = Forget (go i a)
171+
where
169172
go 0 x = mempty
170173
go n x = x <> go (n - 1) x
171174

172175
-- | Folds over a `Foldable` container.
173176
folded :: forall g a b t r. (Monoid r, Foldable g) => Fold r (g a) b a t
174-
folded = Forget <<< foldMap <<< runForget
177+
folded (Forget a) = Forget (foldMap a)
175178

176179
-- | Builds a `Fold` using an unfold.
177180
unfolded
@@ -181,7 +184,7 @@ unfolded
181184
-> Fold r s t a b
182185
unfolded f p = Forget go
183186
where
184-
go = maybe mempty (\(Tuple a sn) -> runForget p a <> go sn) <<< f
187+
go = maybe mempty (\(Tuple a sn) -> unwrap p a <> go sn) <<< f
185188

186189
-- | Fold map over an `IndexedFold`.
187190
ifoldMapOf
@@ -190,7 +193,7 @@ ifoldMapOf
190193
-> (i -> a -> r)
191194
-> s
192195
-> r
193-
ifoldMapOf p f = runForget $ p $ Indexed $ Forget (uncurry f)
196+
ifoldMapOf p f = unwrap $ p $ Indexed $ Forget (uncurry f)
194197

195198
-- | Right fold over an `IndexedFold`.
196199
ifoldrOf
@@ -200,7 +203,7 @@ ifoldrOf
200203
-> r
201204
-> s
202205
-> r
203-
ifoldrOf p f r = flip runEndo r <<< ifoldMapOf p (\i -> Endo <<< f i)
206+
ifoldrOf p f r = flip unwrap r <<< ifoldMapOf p (\i -> Endo <<< f i)
204207

205208
-- | Left fold over an `IndexedFold`.
206209
ifoldlOf
@@ -211,8 +214,8 @@ ifoldlOf
211214
-> s
212215
-> r
213216
ifoldlOf p f r =
214-
flip runEndo r
215-
<<< runDual
217+
flip unwrap r
218+
<<< unwrap
216219
<<< ifoldMapOf p (\i -> Dual <<< Endo <<< flip (f i))
217220

218221
-- | Whether all foci of an `IndexedFold` satisfy a predicate.
@@ -223,7 +226,7 @@ iallOf
223226
-> (i -> a -> r)
224227
-> s
225228
-> r
226-
iallOf p f = runConj <<< ifoldMapOf p (\i -> Conj <<< f i)
229+
iallOf p f = unwrap <<< ifoldMapOf p (\i -> Conj <<< f i)
227230

228231
-- | Whether any focus of an `IndexedFold` satisfies a predicate.
229232
ianyOf
@@ -233,7 +236,7 @@ ianyOf
233236
-> (i -> a -> r)
234237
-> s
235238
-> r
236-
ianyOf p f = runDisj <<< ifoldMapOf p (\i -> Disj <<< f i)
239+
ianyOf p f = unwrap <<< ifoldMapOf p (\i -> Disj <<< f i)
237240

238241
-- | Find the first focus of an `IndexedFold` that satisfies a predicate, if
239242
-- | there is any.

src/Data/Lens/Getter.purs

Lines changed: 8 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -9,34 +9,36 @@ import Prelude
99

1010
import Control.Monad.State.Class (class MonadState, gets)
1111

12-
import Data.Lens.Internal.Forget (Forget(..), runForget)
12+
import Data.Lens.Internal.Forget (Forget(..))
1313
import Data.Lens.Types (Getter, Fold, Optic, IndexedGetter, Indexed(..), IndexedFold)
14+
import Data.Newtype (unwrap)
1415
import Data.Tuple (Tuple)
1516

1617
infixl 8 viewOn as ^.
1718

1819
-- | View the focus of a `Getter`.
1920
view :: forall s t a b. Getter s t a b -> s -> a
20-
view l = runForget (l (Forget id))
21+
view l = unwrap (l (Forget id))
2122

2223
-- | View the focus of a `Getter` and its index.
2324
iview :: forall i s t a b. IndexedFold (Tuple i a) i s t a b -> s -> Tuple i a
24-
iview l = runForget (l (Indexed $ Forget id))
25+
iview l = unwrap (l (Indexed $ Forget id))
2526

2627
-- | Synonym for `view`, flipped.
2728
viewOn :: forall s t a b. s -> Getter s t a b -> a
2829
viewOn s l = view l s
2930

3031
-- | Convert a function into a getter.
3132
to :: forall r s t a b. (s -> a) -> Fold r s t a b
32-
to f p = Forget (runForget p <<< f)
33+
to f p = Forget (unwrap p <<< f)
3334

3435
-- | View the focus of a `Getter` in the state of a monad.
35-
use :: forall s t a b m. (MonadState s m) => Getter s t a b -> m a
36+
use :: forall s t a b m. MonadState s m => Getter s t a b -> m a
3637
use p = gets (_ ^. p)
3738

3839
-- | View the focus of a `Getter` and its index in the state of a monad.
3940
iuse
40-
:: forall i s t a b m. (MonadState s m)
41+
:: forall i s t a b m
42+
. MonadState s m
4143
=> IndexedFold (Tuple i a) i s t a b -> m (Tuple i a)
4244
iuse p = gets (iview p)

0 commit comments

Comments
 (0)