Skip to content

Commit 7c3b2e4

Browse files
committed
Add strict traversal operations
* Add `strictly` to turn a lazy (standard) traversal into a strict one that forces targets before installing them. * Add `over'`, `iover'`, `modifying'`, `imodifying'`, and corresponding operators `%!~`, `%!@~`, `%!=`, and `%!@=`. * Adjust documentation. Closes ekmett#1016
1 parent a901d6e commit 7c3b2e4

File tree

5 files changed

+238
-1
lines changed

5 files changed

+238
-1
lines changed

lens.cabal

+1
Original file line numberDiff line numberDiff line change
@@ -190,6 +190,7 @@ library
190190
indexed-traversable-instances >= 0.1 && < 0.2,
191191
kan-extensions >= 5 && < 6,
192192
mtl >= 2.2.1 && < 2.4,
193+
OneTuple >= 0.3 && < 0.4,
193194
parallel >= 3.2.1.0 && < 3.3,
194195
profunctors >= 5.5.2 && < 6,
195196
reflection >= 2.1 && < 3,

src/Control/Lens/Combinators.hs

+4
Original file line numberDiff line numberDiff line change
@@ -107,6 +107,7 @@ import Control.Lens hiding
107107
, (...)
108108
, (#)
109109
, (%~)
110+
, (%!~)
110111
, (.~)
111112
, (?~)
112113
, (<.~)
@@ -124,6 +125,7 @@ import Control.Lens hiding
124125
, (&&~)
125126
, (.=)
126127
, (%=)
128+
, (%!=)
127129
, (?=)
128130
, (+=)
129131
, (-=)
@@ -140,7 +142,9 @@ import Control.Lens hiding
140142
, (<>~)
141143
, (<>=)
142144
, (%@~)
145+
, (%!@~)
143146
, (%@=)
147+
, (%!@=)
144148
, (:>)
145149
, (:<)
146150
)

src/Control/Lens/Internal/Setter.hs

+9
Original file line numberDiff line numberDiff line change
@@ -49,6 +49,15 @@ instance Settable Identity where
4949
taintedDot = (Identity #.)
5050
{-# INLINE taintedDot #-}
5151

52+
-- CAUTION: While Data.Tuple.Solo may *look* a lot like Identity, and while we
53+
-- *could* give it a Settable instance, we probably do not want to do so. In
54+
-- particular, if we did, then Control.Lens.Traversal.over' would "work" with
55+
-- Setters. But ... it wouldn't *actually* work; the mapping would end up being
56+
-- lazy when it's supposed to be strict. Similarly, the BoxT applicative
57+
-- transformer must not be made Settable, because that would cause a similarly
58+
-- confusing problem with Control.Lens.Traversal.strictly. There is not, as
59+
-- yet, any compelling reason to write such an instance, so let's not.
60+
5261
-- | 'Control.Lens.Fold.backwards'
5362
instance Settable f => Settable (Backwards f) where
5463
untainted = untaintedDot forwards

src/Control/Lens/Setter.hs

+14
Original file line numberDiff line numberDiff line change
@@ -342,6 +342,13 @@ cloneIndexedSetter l pafb = taintedDot (runIdentity #. l (Indexed $ \i -> Identi
342342
-- >>> over _1 show (10,20)
343343
-- ("10",20)
344344
--
345+
--
346+
-- Like 'fmap', @over@ is normally lazy in the result(s) of calling the
347+
-- function, which can cause space leaks in lazy fields, or when using
348+
-- 'Control.Lens.At.ix' for value-lazy structures like 'Data.Sequence.Seq',
349+
-- 'Data.Map.Map', 'Data.IntMap.IntMap', or 'Data.Array.Array'. For a strict
350+
-- version, see `Control.Lens.Traversal.iover'`.
351+
--
345352
-- @
346353
-- 'over' :: 'Setter' s t a b -> (a -> b) -> s -> t
347354
-- 'over' :: 'ASetter' s t a b -> (a -> b) -> s -> t
@@ -1169,6 +1176,13 @@ ilocally l f = Reader.local (iover l f)
11691176
-- 'iover' l ≡ 'over' l '.' 'Indexed'
11701177
-- @
11711178
--
1179+
-- Like 'Data.Functor.WithIndex.imap', @iover@ is normally lazy in the
1180+
-- result(s) of calling the function, which can cause space leaks in lazy
1181+
-- fields, or when using 'Control.Lens.At.ix' for value-lazy structures like
1182+
-- 'Data.Sequence.Seq', 'Data.Map.Map', 'Data.IntMap.IntMap', or
1183+
-- 'Data.Array.Array'. For a strict version, see
1184+
-- `Control.Lens.Traversal.iover'`.
1185+
--
11721186
-- @
11731187
-- 'iover' :: 'IndexedSetter' i s t a b -> (i -> a -> b) -> s -> t
11741188
-- 'iover' :: 'IndexedLens' i s t a b -> (i -> a -> b) -> s -> t

src/Control/Lens/Traversal.hs

+210-1
Original file line numberDiff line numberDiff line change
@@ -1,11 +1,14 @@
11
{-# LANGUAGE CPP #-}
2+
{-# LANGUAGE BangPatterns #-}
3+
{-# LANGUAGE DeriveTraversable #-}
24
{-# LANGUAGE GADTs #-}
35
{-# LANGUAGE Rank2Types #-}
46
{-# LANGUAGE FlexibleContexts #-}
57
{-# LANGUAGE FlexibleInstances #-}
68
{-# LANGUAGE FunctionalDependencies #-}
79
{-# LANGUAGE ScopedTypeVariables #-}
810
{-# LANGUAGE Trustworthy #-}
11+
{-# LANGUAGE UndecidableInstances #-}
912
{-# LANGUAGE ConstraintKinds #-}
1013

1114
#include "lens-common.h"
@@ -113,6 +116,17 @@ module Control.Lens.Traversal
113116
, imapAccumROf
114117
, imapAccumLOf
115118

119+
-- ** Strict traversals
120+
, over'
121+
, (%!~)
122+
, iover'
123+
, (%!@~)
124+
, modifying'
125+
, (%!=)
126+
, imodifying'
127+
, (%!@=)
128+
, strictly
129+
116130
-- * Reflection
117131
, traverseBy
118132
, traverseByOf
@@ -145,6 +159,8 @@ import Control.Lens.Lens
145159
import Control.Lens.Setter (ASetter, AnIndexedSetter, isets, sets)
146160
import Control.Lens.Type
147161
import Control.Monad.Trans.State.Lazy
162+
import Control.Monad.State.Class (MonadState)
163+
import qualified Control.Monad.State.Class as MonadState
148164
import Data.Bitraversable
149165
import Data.CallStack
150166
import Data.Functor.Apply
@@ -162,10 +178,11 @@ import Data.Reflection
162178
import Data.Semigroup.Traversable
163179
import Data.Semigroup.Bitraversable
164180
import Data.Tuple (swap)
181+
import Data.Tuple.Solo (Solo (..), getSolo)
165182
import GHC.Magic (inline)
166183

167184
-- $setup
168-
-- >>> :set -XNoOverloadedStrings -XFlexibleContexts
185+
-- >>> :set -XNoOverloadedStrings -XFlexibleContexts -XRankNTypes
169186
-- >>> import Data.Char (toUpper)
170187
-- >>> import Control.Applicative
171188
-- >>> import Control.Lens
@@ -183,6 +200,9 @@ import GHC.Magic (inline)
183200
-- >>> let firstAndThird :: Traversal (a, x, a) (b, x, b) a b; firstAndThird = traversal go where { go :: Applicative f => (a -> f b) -> (a, x, a) -> f (b, x, b); go focus (a, x, a') = liftA3 (,,) (focus a) (pure x) (focus a') }
184201
-- >>> let selectNested :: Traversal (x, [a]) (x, [b]) a b; selectNested = traversal go where { go :: Applicative f => (a -> f b) -> (x, [a]) -> f (x, [b]); go focus (x, as) = liftA2 (,) (pure x) (traverse focus as) }
185202

203+
infixr 4 %!~, %!@~
204+
infix 4 %!=, %!@=
205+
186206
------------------------------------------------------------------------------
187207
-- Traversals
188208
------------------------------------------------------------------------------
@@ -1466,3 +1486,192 @@ traverseByOf l pur app f = reifyApplicative pur app (l (ReflectedApplicative #.
14661486
-- @
14671487
sequenceByOf :: Traversal s t (f b) b -> (forall x. x -> f x) -> (forall x y. f (x -> y) -> f x -> f y) -> s -> f t
14681488
sequenceByOf l pur app = reifyApplicative pur app (l ReflectedApplicative)
1489+
1490+
-- Note: Solo wrapping
1491+
--
1492+
-- We use Solo for strict application of (indexed) setters.
1493+
--
1494+
-- Credit for this idea goes to Eric Mertens; see
1495+
-- <https://github.com/glguy/irc-core/commit/2d5fc45b05f1>. It was reinvented
1496+
-- independently by David Feuer, who realized that an applicative transformer
1497+
-- version could be used to implement `strictly`.
1498+
--
1499+
-- Using Solo rather than Identity allows us, when applying a traversal to a
1500+
-- structure, to evaluate only the parts that we modify. If an optic focuses on
1501+
-- multiple targets, the Applicative instance of Solo (combined with applying
1502+
-- the Solo data constructor strictly) makes sure that we force evaluation of
1503+
-- all of them, but we leave anything else alone.
1504+
1505+
-- | A version of 'Control.Lens.Setter.over' that forces the result(s) of
1506+
-- applying the function. This can prevent space leaks when modifying lazy
1507+
-- fields. See also 'strictly'.
1508+
--
1509+
-- @
1510+
-- over' :: 'Lens' s t a b -> (a -> b) -> s -> t
1511+
-- over' :: 'Traversal' s t a b -> (a -> b) -> s -> t
1512+
-- @
1513+
--
1514+
-- >>> length $ over traverse id [undefined, undefined]
1515+
-- 2
1516+
--
1517+
-- >>> over' traverse id [1, undefined :: Int]
1518+
-- *** Exception: Prelude.undefined
1519+
-- ...
1520+
over' :: LensLike Solo s t a b -> (a -> b) -> s -> t
1521+
-- See [Note: Solo wrapping]
1522+
over' l f = getSolo . l (\old -> Solo $! f old)
1523+
{-# INLINE over' #-}
1524+
1525+
-- | Traverse targets strictly. This is the operator version of 'over''.
1526+
(%!~) :: LensLike Solo s t a b -> (a -> b) -> s -> t
1527+
(%!~) = over'
1528+
{-# INLINE (%!~) #-}
1529+
1530+
-- $
1531+
-- >>> :{
1532+
-- let lover' :: Lens s t a b -> (a -> b) -> s -> t
1533+
-- lover' l = over' l
1534+
-- tover' :: Traversal s t a b -> (a -> b) -> s -> t
1535+
-- tover' l = over' l
1536+
-- :}
1537+
--
1538+
-- >>> :{
1539+
-- let sover' :: Setter s t a b -> (a -> b) -> s -> t
1540+
-- sover' l = over' l
1541+
-- :}
1542+
-- ...
1543+
-- ...error...
1544+
-- ...
1545+
1546+
-- | A version of 'Control.Lens.Setter.iover' that forces the result(s) of
1547+
-- applying the function. Alternatively, an indexed version of `over'`.
1548+
-- See also 'strictly'.
1549+
--
1550+
-- @
1551+
-- iover' :: IndexedLens i s t a b -> (i -> a -> b) -> s -> t
1552+
-- iover' :: IndexedTraversal i s t a b -> (i -> a -> b) -> s -> t
1553+
-- @
1554+
iover' :: Over (Indexed i) Solo s t a b -> (i -> a -> b) -> s -> t
1555+
-- See [Note: Solo wrapping]
1556+
iover' l f = getSolo . l (Indexed $ \i a -> Solo $! f i a)
1557+
{-# INLINE iover' #-}
1558+
1559+
-- | Traverse targets strictly with indices. This is the operator version of
1560+
-- 'iover''.
1561+
(%!@~) :: Over (Indexed i) Solo s t a b -> (i -> a -> b) -> s -> t
1562+
(%!@~) = iover'
1563+
{-# INLINE (%!@~) #-}
1564+
1565+
-- | Modify the state strictly. This is stricter than
1566+
-- @Control.Lens.Setter.modifying@ in two ways: it forces the new value of the
1567+
-- state, and it forces the new value of the target within the state.
1568+
modifying' :: MonadState s m => LensLike Solo s s a b -> (a -> b) -> m ()
1569+
-- See [Note: Solo wrapping]
1570+
modifying' l f = do
1571+
s <- MonadState.get
1572+
let !(Solo !t) = l (\old -> Solo $! f old) s
1573+
MonadState.put t
1574+
{-# INLINE modifying' #-}
1575+
1576+
-- | Modify the state strictly. This is an operator version of
1577+
-- 'modifying''.
1578+
(%!=) :: MonadState s m => LensLike Solo s s a b -> (a -> b) -> m ()
1579+
(%!=) = modifying'
1580+
{-# INLINE (%!=) #-}
1581+
1582+
-- | Modify the state strictly with an index. This is stricter than
1583+
-- @Control.Lens.Setter.imodifying@ in two ways: it forces the new value of the
1584+
-- state, and it forces the new value of the target within the state.
1585+
imodifying' :: MonadState s m => Over (Indexed i) Solo s s a b -> (i -> a -> b) -> m ()
1586+
-- See [Note: Solo wrapping]
1587+
imodifying' l f = do
1588+
s <- MonadState.get
1589+
let !(Solo !t) = l (Indexed $ \i old -> Solo $! f i old) s
1590+
MonadState.put t
1591+
{-# INLINE imodifying' #-}
1592+
1593+
-- | Modify the state strictly. This is an operator version of
1594+
-- 'imodifying''.
1595+
(%!@=) :: MonadState s m => Over (Indexed i) Solo s s a b -> (i -> a -> b) -> m ()
1596+
(%!@=) = imodifying'
1597+
{-# INLINE (%!@=) #-}
1598+
1599+
-- $
1600+
-- >>> :{
1601+
-- let liover' :: IndexedLens i s t a b -> (i -> a -> b) -> s -> t
1602+
-- liover' l = iover' l
1603+
-- tiover' :: IndexedTraversal i s t a b -> (i -> a -> b) -> s -> t
1604+
-- tiover' l = iover' l
1605+
-- :}
1606+
1607+
-- | Use an optic /strictly/. @strictly l f s@ will force the results of /all/
1608+
-- the targets of @l@ before producing a new value. It does not affect folds or
1609+
-- getters. Note that producing an optic using 'strictly' will not necessarily
1610+
-- produce one as efficient as what could be written by hand, although it will
1611+
-- do so in simple enough situations. Efficiency issues are most likely when
1612+
-- working over a large structure in a functor other than the usual 'Identity'.
1613+
--
1614+
-- @
1615+
-- 'over'' l = 'Control.Lens.Setter.over' (strictly l)
1616+
-- 'iover'' l = 'Control.Lens.Setter.iover' (strictly l)
1617+
-- @
1618+
--
1619+
-- @
1620+
-- strictly :: 'Traversal' s t a b -> 'Traversal' s t a b
1621+
-- strictly :: 'IndexedTraversal' i s t a b -> 'IndexedTraversal' i s t a b
1622+
-- @
1623+
strictly :: (Functor f, Profunctor p, Profunctor q) => Optical p q (BoxT f) s t a b -> Optical p q f s t a b
1624+
-- See [Note: Solo wrapping]
1625+
strictly l f = rmap (fmap getSolo .# runBoxT) $ l (rmap (BoxT #. fmap (Solo $!)) f)
1626+
{-# INLINE strictly #-}
1627+
1628+
-- $
1629+
-- >>> :{
1630+
-- let tstrictly :: Traversal s t a b -> Traversal s t a b
1631+
-- tstrictly l = strictly l
1632+
-- itstrictly :: AnIndexedTraversal i s t a b -> IndexedTraversal i s t a b
1633+
-- itstrictly l = strictly (cloneIndexedTraversal l)
1634+
-- lstrictly :: Lens s t a b -> Lens s t a b
1635+
-- lstrictly l = strictly l
1636+
-- ilstrictly :: AnIndexedLens i s t a b -> IndexedLens i s t a b
1637+
-- ilstrictly l = strictly (cloneIndexedLens l)
1638+
-- fstrictly :: Fold s a -> Fold s a
1639+
-- fstrictly l = strictly l
1640+
-- :}
1641+
--
1642+
-- >>> :{
1643+
-- let sstrictly :: Setter s t a b -> Setter s t a b
1644+
-- sstrictly l = strictly l
1645+
-- :}
1646+
-- ...
1647+
-- ...Settable ...BoxT...
1648+
-- ...
1649+
1650+
-- | A very simple applicative transformer that gives us more control over when
1651+
-- things get forced. Note: this type /should not/ be made an instance of
1652+
-- @Settable@, because then users could accidentally use 'strictly' with a
1653+
-- 'Setter', which will not work at all. There is no way to strictify a
1654+
-- 'Setter'.
1655+
newtype BoxT f a = BoxT
1656+
{ runBoxT :: f (Solo a) }
1657+
deriving (Functor, Foldable, Traversable)
1658+
1659+
-- The Contravariant instance allows `strictly` to be used on a getter or fold.
1660+
-- It's not at all obvious that this is *useful* (since `strictly` doesn't
1661+
-- change these at all), but it's also not obviously *harmful*.
1662+
instance Contravariant f => Contravariant (BoxT f) where
1663+
contramap f (BoxT m) = BoxT $ contramap (fmap f) m
1664+
instance Apply f => Apply (BoxT f) where
1665+
liftF2 f (BoxT m) (BoxT n) = BoxT (liftF2 (liftA2 f) m n)
1666+
{-# INLINE liftF2 #-}
1667+
instance Applicative f => Applicative (BoxT f) where
1668+
pure = BoxT . pure . Solo
1669+
{-# INLINE pure #-}
1670+
BoxT m <*> BoxT n = BoxT (liftA2 (<*>) m n)
1671+
{-# INLINE (<*>) #-}
1672+
#if MIN_VERSION_base(4,10,0)
1673+
liftA2 f (BoxT m) (BoxT n) = BoxT (liftA2 (liftA2 f) m n)
1674+
{-# INLINE liftA2 #-}
1675+
#endif
1676+
-- Caution: We *can't* implement *> or <* in terms of the underlying *> and
1677+
-- <*. We need to force the Solos, not discard them.

0 commit comments

Comments
 (0)