@@ -13,37 +13,48 @@ module Control.Optics.Linear.Internal
1313 , Iso , Iso'
1414 , Lens , Lens'
1515 , Prism , Prism'
16- , Traversal , Traversal'
16+ , PTraversal , PTraversal'
17+ , DTraversal , DTraversal'
1718 -- * Composing optics
1819 , (.>)
1920 -- * Common optics
2021 , swap , assoc
2122 , _1 , _2
2223 , _Left , _Right
2324 , _Just , _Nothing
24- , traversed
25+ , ptraversed , dtraversed
26+ , both , both'
2527 -- * Using optics
2628 , get , set , gets
29+ , set' , set''
2730 , match , build
31+ , preview
2832 , over , over'
2933 , traverseOf , traverseOf'
3034 , lengthOf
31- , withIso , withPrism
35+ , withIso , withLens , withPrism
36+ , toListOf
3237 -- * Constructing optics
33- , iso , prism
38+ , iso , prism , lens
3439 )
3540 where
3641
3742import qualified Control.Arrow as NonLinear
3843import qualified Data.Bifunctor.Linear as Bifunctor
44+ import qualified Control.Monad.Linear as Control
3945import Data.Bifunctor.Linear (SymmetricMonoidal )
40- import Data.Profunctor.Linear
46+ import Data.Monoid.Linear
47+ import Data.Functor.Const
4148import Data.Functor.Linear
49+ import Data.Profunctor.Linear
4250import qualified Data.Profunctor.Kleisli.Linear as Linear
4351import Data.Void
4452import Prelude.Linear
4553import qualified Prelude as P
4654
55+ -- TODO: documentation in this module
56+ -- Put the functions in some sensible order: possibly split into separate
57+ -- Lens/Prism/Traversal/Iso modules
4758newtype Optic_ arr a b s t = Optical (a `arr ` b -> s `arr ` t )
4859
4960type Optic c a b s t =
@@ -55,8 +66,12 @@ type Lens a b s t = Optic (Strong (,) ()) a b s t
5566type Lens' a s = Lens a a s s
5667type Prism a b s t = Optic (Strong Either Void ) a b s t
5768type Prism' a s = Prism a a s s
58- type Traversal a b s t = Optic Wandering a b s t
59- type Traversal' a s = Traversal 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
6075
6176swap :: SymmetricMonoidal m u => Iso (a `m ` b ) (c `m ` d ) (b `m ` a ) (d `m ` c )
6277swap = iso Bifunctor. swap Bifunctor. swap
@@ -67,6 +82,12 @@ assoc = iso Bifunctor.lassoc Bifunctor.rassoc
6782(.>) :: Optic_ arr a b s t -> Optic_ arr x y a b -> Optic_ arr x y s t
6883Optical f .> Optical g = Optical (f P. . g)
6984
85+ lens :: (s ->. (a , b ->. t )) -> Lens a b s t
86+ lens k = Optical $ \ f -> dimap k (\ (x,g) -> g $ x) (first f)
87+
88+ withLens :: Optic_ (Linear. Kleisli (OtherFunctor a b )) a b s t -> s ->. (a , b ->. t )
89+ withLens (Optical l) s = runOtherFunctor (Linear. runKleisli (l (Linear. Kleisli (\ a -> OtherFunctor (a, id )))) s)
90+
7091prism :: (b ->. t ) -> (s ->. Either t a ) -> Prism a b s t
7192prism b s = Optical $ \ f -> dimap s (either id id ) (second (rmap b f))
7293
@@ -76,6 +97,37 @@ _1 = Optical first
7697_2 :: Lens a b (c ,a ) (c ,b )
7798_2 = Optical second
7899
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
107+
108+ -- XXX: these are a special case of Bitraversable, but just the simple case
109+ -- is included here for now
110+ _Pairing :: Iso (Pair a ) (Pair b ) (a ,a ) (b ,b )
111+ _Pairing = iso Paired unpair
112+
113+ newtype Pair a = Paired (a ,a )
114+ unpair :: Pair a ->. (a ,a )
115+ unpair (Paired x) = x
116+
117+ instance P. Functor Pair where
118+ fmap f (Paired (x,y)) = Paired (f x, f y)
119+ instance Functor Pair where
120+ 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)
125+ instance Traversable Pair where
126+ traverse f (Paired (x,y)) = Paired <$> ((,) <$> f x <*> f y)
127+
128+ toListOf :: Optic_ (NonLinear. Kleisli (Const [a ])) a b s t -> s -> [a ]
129+ toListOf l = gets l (\ a -> [a])
130+
79131_Left :: Prism a b (Either a c ) (Either b c )
80132_Left = Optical first
81133
@@ -88,8 +140,11 @@ _Just = prism Just (maybe (Left Nothing) Right)
88140_Nothing :: Prism' () (Maybe a )
89141_Nothing = prism (\ () -> Nothing ) Left
90142
91- traversed :: Traversable t => Traversal a b (t a ) (t b )
92- traversed = Optical wander
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
93148
94149over :: Optic_ LinearArrow a b s t -> (a ->. b ) -> s ->. t
95150over (Optical l) f = getLA (l (LA f))
@@ -103,6 +158,15 @@ get l = gets l P.id
103158gets :: Optic_ (NonLinear. Kleisli (Const r )) a b s t -> (a -> r ) -> s -> r
104159gets (Optical l) f s = getConst' (NonLinear. runKleisli (l (NonLinear. Kleisli (Const P. . f))) s)
105160
161+ preview :: Optic_ (NonLinear. Kleisli (Const (Maybe (First a )))) a b s t -> s -> Maybe a
162+ preview l s = P. fmap getFirst (gets l (\ a -> Just (First a)) s)
163+
164+ set' :: Optic_ (Linear. Kleisli (MyFunctor a b )) a b s t -> s ->. b ->. (a , t )
165+ set' (Optical l) s = runMyFunctor (Linear. runKleisli (l (Linear. Kleisli (\ a -> MyFunctor (\ b -> (a,b))))) s)
166+
167+ set'' :: Optic_ (NonLinear. Kleisli (Control. Reader b )) a b s t -> b ->. s -> t
168+ set'' (Optical l) b s = Control. runReader (NonLinear. runKleisli (l (NonLinear. Kleisli (const (Control. reader id )))) s) b
169+
106170set :: Optic_ (-> ) a b s t -> b -> s -> t
107171set (Optical l) x = l (const x)
108172
0 commit comments