@@ -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
4241import qualified Control.Arrow as NonLinear
4342import qualified Data.Bifunctor.Linear as Bifunctor
4443import qualified Control.Monad.Linear as Control
44+ import Data.Functor.Linear.Internal.Traversable
4545import Data.Bifunctor.Linear (SymmetricMonoidal )
4646import Data.Monoid.Linear
4747import Data.Functor.Const
@@ -66,12 +66,8 @@ type Lens a b s t = Optic (Strong (,) ()) a b s t
6666type Lens' a s = Lens a a s s
6767type Prism a b s t = Optic (Strong Either Void ) a b s t
6868type 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
7672swap :: SymmetricMonoidal m u => Iso (a `m ` b ) (c `m ` d ) (b `m ` a ) (d `m ` c )
7773swap = 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)
119110instance 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)
125112instance 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-
149130over :: Optic_ LinearArrow a b s t -> (a ->. b ) -> s ->. t
150131over (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
168149set'' (Optical l) b s = Control. runReader (NonLinear. runKleisli (l (NonLinear. Kleisli (const (Control. reader id )))) s) b
169150
170151set :: 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
173154match :: Optic_ (Market a b ) a b s t -> s ->. Either t a
174155match (Optical l) = snd (runMarket (l (Market id Right )))
@@ -203,3 +184,23 @@ withIso (Optical l) f = f fro to
203184withPrism :: Optic_ (Market a b ) a b s t -> ((b ->. t ) -> (s ->. Either t a ) -> r ) -> r
204185withPrism (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))
0 commit comments