Skip to content

Commit b7c4c3f

Browse files
committed
Batch traversals
1 parent d8c2e33 commit b7c4c3f

File tree

4 files changed

+80
-55
lines changed

4 files changed

+80
-55
lines changed

src/Control/Optics/Linear/Internal.hs

+30-29
Original file line numberDiff line numberDiff line change
@@ -13,17 +13,16 @@ module Control.Optics.Linear.Internal
1313
, Iso, Iso'
1414
, Lens, Lens'
1515
, Prism, Prism'
16-
, PTraversal, PTraversal'
17-
, DTraversal, DTraversal'
16+
, Traversal, Traversal'
1817
-- * Composing optics
1918
, (.>)
2019
-- * Common optics
2120
, swap, assoc
2221
, _1, _2
2322
, _Left, _Right
2423
, _Just, _Nothing
25-
, ptraversed, dtraversed
26-
, both, both'
24+
, traversed
25+
, both
2726
-- * Using optics
2827
, get, set, gets
2928
, set', set''
@@ -32,8 +31,8 @@ module Control.Optics.Linear.Internal
3231
, over, over'
3332
, traverseOf, traverseOf'
3433
, lengthOf
35-
, withIso, withLens, withPrism
3634
, toListOf
35+
, withIso, withLens, withPrism, withTraversal
3736
-- * Constructing optics
3837
, iso, prism, lens
3938
)
@@ -42,6 +41,7 @@ module Control.Optics.Linear.Internal
4241
import qualified Control.Arrow as NonLinear
4342
import qualified Data.Bifunctor.Linear as Bifunctor
4443
import qualified Control.Monad.Linear as Control
44+
import Data.Functor.Linear.Internal.Traversable
4545
import Data.Bifunctor.Linear (SymmetricMonoidal)
4646
import Data.Monoid.Linear
4747
import Data.Functor.Const
@@ -66,12 +66,8 @@ type Lens a b s t = Optic (Strong (,) ()) a b s t
6666
type Lens' a s = Lens a a s s
6767
type Prism a b s t = Optic (Strong Either Void) a b s t
6868
type Prism' a s = Prism a a s s
69-
type PTraversal a b s t = Optic PWandering a b s t
70-
type PTraversal' a s = PTraversal a a s s
71-
type DTraversal a b s t = Optic DWandering a b s t
72-
type DTraversal' a s = DTraversal a a s s
73-
-- XXX: these will unify into
74-
-- type Traversal (p :: Multiplicity) a b s t = Optic (Wandering p) a b s t
69+
type Traversal a b s t = Optic Traversing a b s t
70+
type Traversal' a s = Traversal a a s s
7571

7672
swap :: SymmetricMonoidal m u => Iso (a `m` b) (c `m` d) (b `m` a) (d `m` c)
7773
swap = iso Bifunctor.swap Bifunctor.swap
@@ -97,13 +93,8 @@ _1 = Optical first
9793
_2 :: Lens a b (c,a) (c,b)
9894
_2 = Optical second
9995

100-
-- XXX: these will unify to
101-
-- > both :: forall (p :: Multiplicity). Traversal p a b (a,a) (b,b)
102-
both' :: PTraversal a b (a,a) (b,b)
103-
both' = _Pairing .> ptraversed
104-
105-
both :: DTraversal a b (a,a) (b,b)
106-
both = _Pairing .> dtraversed
96+
both :: Traversal a b (a,a) (b,b)
97+
both = _Pairing .> traversed
10798

10899
-- XXX: these are a special case of Bitraversable, but just the simple case
109100
-- is included here for now
@@ -118,10 +109,6 @@ instance P.Functor Pair where
118109
fmap f (Paired (x,y)) = Paired (f x, f y)
119110
instance Functor Pair where
120111
fmap f (Paired (x,y)) = Paired (f x, f y)
121-
instance Foldable Pair where
122-
foldMap f (Paired (x,y)) = f x P.<> f y
123-
instance P.Traversable Pair where
124-
traverse f (Paired (x,y)) = Paired P.<$> ((,) P.<$> f x P.<*> f y)
125112
instance Traversable Pair where
126113
traverse f (Paired (x,y)) = Paired <$> ((,) <$> f x <*> f y)
127114

@@ -140,12 +127,6 @@ _Just = prism Just (maybe (Left Nothing) Right)
140127
_Nothing :: Prism' () (Maybe a)
141128
_Nothing = prism (\() -> Nothing) Left
142129

143-
ptraversed :: P.Traversable t => PTraversal a b (t a) (t b)
144-
ptraversed = Optical pwander
145-
146-
dtraversed :: Traversable t => DTraversal a b (t a) (t b)
147-
dtraversed = Optical dwander
148-
149130
over :: Optic_ LinearArrow a b s t -> (a ->. b) -> s ->. t
150131
over (Optical l) f = getLA (l (LA f))
151132

@@ -168,7 +149,7 @@ set'' :: Optic_ (NonLinear.Kleisli (Control.Reader b)) a b s t -> b ->. s -> t
168149
set'' (Optical l) b s = Control.runReader (NonLinear.runKleisli (l (NonLinear.Kleisli (const (Control.reader id)))) s) b
169150

170151
set :: Optic_ (->) a b s t -> b -> s -> t
171-
set (Optical l) x = l (const x)
152+
set l b = over' l (const b)
172153

173154
match :: Optic_ (Market a b) a b s t -> s ->. Either t a
174155
match (Optical l) = snd (runMarket (l (Market id Right)))
@@ -203,3 +184,23 @@ withIso (Optical l) f = f fro to
203184
withPrism :: Optic_ (Market a b) a b s t -> ((b ->. t) -> (s ->. Either t a) -> r) -> r
204185
withPrism (Optical l) f = f b m
205186
where Market b m = l (Market id Right)
187+
188+
traversal :: (s ->. Batch a b t) -> Traversal a b s t
189+
traversal h = Optical (\k -> dimap h fuse (traverse' k))
190+
191+
traverse' :: (Strong Either Void arr, Monoidal (,) () arr) => a `arr` b -> Batch a c t `arr` Batch b c t
192+
traverse' k = dimap out inn (second (traverse' k *** k))
193+
194+
out :: Batch a b t ->. Either t (Batch a b (b ->. t), a)
195+
out (P t) = Left t
196+
out (l :*: x) = Right (l,x)
197+
198+
inn :: Either t (Batch a b (b ->. t), a) ->. Batch a b t
199+
inn (Left t) = P t
200+
inn (Right (l,x)) = l :*: x
201+
202+
traversed :: Traversable t => Traversal a b (t a) (t b)
203+
traversed = traversal (traverse batch)
204+
205+
withTraversal :: Optic_ (Linear.Kleisli (Batch a b)) a b s t -> s ->. Batch a b t
206+
withTraversal (Optical l) = Linear.runKleisli (l (Linear.Kleisli batch))

src/Data/Functor/Linear/Internal/Traversable.hs

+27
Original file line numberDiff line numberDiff line change
@@ -14,6 +14,7 @@ module Data.Functor.Linear.Internal.Traversable
1414
Traversable(..)
1515
, mapM, sequenceA, for, forM
1616
, mapAccumL, mapAccumR
17+
, batch, runWith, Batch(..), fuse
1718
) where
1819

1920
import qualified Control.Monad.Linear.Internal as Control
@@ -79,6 +80,32 @@ instance Control.Applicative (StateR s) where
7980
where go :: (a, (a ->. b, s)) ->. (b, s)
8081
go (a, (h, s'')) = (h a, s'')
8182

83+
data Batch a b c = P c | Batch a b (b ->. c) :*: a
84+
deriving (Data.Functor, Data.Applicative) via Control.Data (Batch a b)
85+
instance Control.Functor (Batch a b) where
86+
fmap f (P c) = P (f c)
87+
fmap f (u :*: a) = Control.fmap (f.) u :*: a
88+
89+
instance Control.Applicative (Batch a b) where
90+
pure = P
91+
P f <*> P x = P (f x)
92+
(u :*: a) <*> P x = ((P $ help x) Control.<*> u) :*: a
93+
u <*> (v :*: a) = (P (.) Control.<*> u Control.<*> v) :*: a
94+
95+
help :: d ->. ((b ->. d ->. e) ->. b ->. e)
96+
help d bde b = bde b d
97+
98+
batch :: a ->. Batch a b b
99+
batch x = P id :*: x
100+
101+
runWith :: Control.Applicative f => (a ->. f b) -> Batch a b c ->. f c
102+
runWith _ (P x) = Control.pure x
103+
runWith f (u :*: x) = runWith f u Control.<*> f x
104+
105+
fuse :: Batch b b t ->. t
106+
fuse (P i) = i
107+
fuse (u :*: x) = fuse u x
108+
82109
------------------------
83110
-- Standard instances --
84111
------------------------

src/Data/Profunctor/Kleisli/Linear.hs

+5-2
Original file line numberDiff line numberDiff line change
@@ -41,8 +41,11 @@ instance Control.Applicative f => Strong Either Void (Kleisli f) where
4141
first (Kleisli f) = Kleisli (either (Data.fmap Left . f) (Control.pure . Right))
4242
second (Kleisli g) = Kleisli (either (Control.pure . Left) (Data.fmap Right . g))
4343

44-
instance Control.Applicative f => DWandering (Kleisli f) where
45-
dwander (Kleisli f) = Kleisli (Data.traverse f)
44+
instance Control.Applicative f => Monoidal (,) () (Kleisli f) where
45+
Kleisli f *** Kleisli g = Kleisli $ \(x,y) -> (,) Control.<$> f x Control.<*> g y
46+
unit = Kleisli Control.pure
47+
48+
instance Control.Applicative f => Traversing (Kleisli f)
4649

4750
-- | Linear co-Kleisli arrows for the comonad `w`. These arrows are still
4851
-- useful in the case where `w` is not a comonad however, and some

src/Data/Profunctor/Linear.hs

+18-24
Original file line numberDiff line numberDiff line change
@@ -1,12 +1,9 @@
1-
{-# LANGUAGE GADTs #-}
21
{-# LANGUAGE FlexibleContexts #-}
32
{-# LANGUAGE FlexibleInstances #-}
4-
{-# LANGUAGE KindSignatures #-}
53
{-# LANGUAGE LambdaCase #-}
64
{-# LANGUAGE LinearTypes #-}
75
{-# LANGUAGE MultiParamTypeClasses #-}
86
{-# LANGUAGE NoImplicitPrelude #-}
9-
{-# LANGUAGE RankNTypes #-}
107
{-# LANGUAGE TupleSections #-}
118
{-# LANGUAGE TypeOperators #-}
129

@@ -16,8 +13,7 @@ module Data.Profunctor.Linear
1613
( Profunctor(..)
1714
, Monoidal(..)
1815
, Strong(..)
19-
, PWandering(..)
20-
, DWandering(..)
16+
, Traversing
2117
, LinearArrow(..), getLA
2218
, Exchange(..)
2319
, Market(..), runMarket
@@ -35,7 +31,7 @@ import Control.Arrow (Kleisli(..))
3531

3632
-- TODO: write laws
3733

38-
class Profunctor (arr :: * -> * -> *) where
34+
class Profunctor arr where
3935
{-# MINIMAL dimap | lmap, rmap #-}
4036

4137
dimap :: (s ->. a) -> (b ->. t) -> a `arr` b -> s `arr` t
@@ -65,17 +61,7 @@ class (SymmetricMonoidal m u, Profunctor arr) => Strong m u arr where
6561
second arr = dimap swap swap (first arr)
6662
{-# INLINE second #-}
6763

68-
-- XXX: Just as Prelude.Functor/Data.Functor will combine into
69-
-- > `class Functor (p :: Multiplicity) f`
70-
-- so will Traversable, and then we would instead write
71-
-- > class (...) => Wandering (p :: Multiplicity) arr where
72-
-- > wander :: Traversable p f => a `arr` b -> f a `arr` f b
73-
-- For now, however, we cannot do this, so we use two classes instead:
74-
-- PreludeWandering and DataWandering
75-
class (Strong (,) () arr, Strong Either Void arr) => PWandering arr where
76-
pwander :: Prelude.Traversable f => a `arr` b -> f a `arr` f b
77-
class (Strong (,) () arr, Strong Either Void arr) => DWandering arr where
78-
dwander :: Data.Traversable f => a `arr` b -> f a `arr` f b
64+
class (Strong (,) () arr, Strong Either Void arr, Monoidal (,) () arr) => Traversing arr where
7965

8066
---------------
8167
-- Instances --
@@ -97,8 +83,11 @@ instance Strong Either Void LinearArrow where
9783
first (LA f) = LA $ either (Left . f) Right
9884
second (LA g) = LA $ either Left (Right . g)
9985

100-
instance DWandering LinearArrow where
101-
dwander (LA f) = LA (Data.fmap f)
86+
instance Monoidal (,) () LinearArrow where
87+
LA f *** LA g = LA $ \(a,x) -> (f a, g x)
88+
unit = LA id
89+
90+
instance Traversing LinearArrow
10291

10392
instance Profunctor (->) where
10493
dimap f g h x = g (h (f x))
@@ -107,8 +96,10 @@ instance Strong (,) () (->) where
10796
instance Strong Either Void (->) where
10897
first f (Left x) = Left (f x)
10998
first _ (Right y) = Right y
110-
instance PWandering (->) where
111-
pwander = Prelude.fmap
99+
instance Monoidal (,) () (->) where
100+
(f *** g) (a,x) = (f a, g x)
101+
unit () = ()
102+
instance Traversing (->)
112103

113104
data Exchange a b s t = Exchange (s ->. a) (b ->. t)
114105
instance Profunctor (Exchange a b) where
@@ -126,6 +117,12 @@ instance Prelude.Applicative f => Strong Either Void (Kleisli f) where
126117
Left x -> Prelude.fmap Left (f x)
127118
Right y -> Prelude.pure (Right y)
128119

120+
instance Prelude.Applicative f => Monoidal (,) () (Kleisli f) where
121+
Kleisli f *** Kleisli g = Kleisli (\(x,y) -> (,) Prelude.<$> f x Prelude.<*> g y)
122+
unit = Kleisli Prelude.pure
123+
124+
instance Prelude.Applicative f => Traversing (Kleisli f) where
125+
129126
data Market a b s t = Market (b ->. t) (s ->. Either t a)
130127
runMarket :: Market a b s t ->. (b ->. t, s ->. Either t a)
131128
runMarket (Market f g) = (f, g)
@@ -136,9 +133,6 @@ instance Profunctor (Market a b) where
136133
instance Strong Either Void (Market a b) where
137134
first (Market f g) = Market (Left . f) (either (either (Left . Left) Right . g) (Left . Right))
138135

139-
instance Prelude.Applicative f => PWandering (Kleisli f) where
140-
pwander (Kleisli f) = Kleisli (Prelude.traverse f)
141-
142136
-- TODO: pick a more sensible name for this
143137
newtype MyFunctor a b t = MyFunctor (b ->. (a, t))
144138
runMyFunctor :: MyFunctor a b t ->. b ->. (a, t)

0 commit comments

Comments
 (0)