@@ -13,39 +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'
27+ , get' , gets' , set'
2528 -- * Using optics
2629 , get , set , gets
2730 , match , match' , build
31+ , preview
2832 , over , over'
2933 , traverseOf , traverseOf'
3034 , lengthOf
3135 , withIso
36+ , toListOf
3237 -- * Constructing optics
33- , iso , prism
38+ , iso , prism , lens
3439 )
3540 where
3641
3742import qualified Data.Bifunctor.Linear as Bifunctor
3843import Data.Bifunctor.Linear (SymmetricMonoidal )
3944import Data.Functor.Const
4045import Data.Functor.Linear
41- import Data.Monoid
46+ import Data.Semigroup.Linear
4247import Data.Profunctor.Linear
4348import qualified Data.Profunctor.Kleisli.Linear as Linear
4449import qualified Data.Profunctor.Kleisli.NonLinear as NonLinear
4550import Data.Void
46- import Prelude.Linear
51+ import Prelude.Linear hiding ((<$>) )
52+ -- ^ XXX: not entirely sure why the hiding is necessary here...
4753import qualified Prelude as P
4854
55+ -- TODO: documentation in this module
56+ -- Put the functions in some sensible order: possibly split into separate
57+ -- Lens/Prism/Traversal/Iso modules
4958newtype Optic_ arr a b s t = Optical (a `arr ` b -> s `arr ` t )
5059
5160type Optic c a b s t =
@@ -57,8 +66,12 @@ type Lens a b s t = Optic (Strong (,) ()) a b s t
5766type Lens' a s = Lens a a s s
5867type Prism a b s t = Optic (Strong Either Void ) a b s t
5968type Prism' a s = Prism a a s s
60- type Traversal a b s t = Optic Wandering a b s t
61- 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
6275
6376swap :: SymmetricMonoidal m u => Iso (a `m ` b ) (c `m ` d ) (b `m ` a ) (d `m ` c )
6477swap = iso Bifunctor. swap Bifunctor. swap
@@ -69,6 +82,10 @@ assoc = iso Bifunctor.lassoc Bifunctor.rassoc
6982(.>) :: Optic_ arr a b s t -> Optic_ arr x y a b -> Optic_ arr x y s t
7083Optical f .> Optical g = Optical (f P. . g)
7184
85+ -- c is the complement (probably)
86+ lens :: (s ->. (c ,a )) -> ((c ,b ) ->. t ) -> Lens a b s t
87+ lens sca cbt = Optical $ \ f -> dimap sca cbt (second f)
88+
7289prism :: (b ->. t ) -> (s ->. Either t a ) -> Prism a b s t
7390prism b s = Optical $ \ f -> dimap s (either id id ) (second (rmap b f))
7491
@@ -78,6 +95,37 @@ _1 = Optical first
7895_2 :: Lens a b (c ,a ) (c ,b )
7996_2 = Optical second
8097
98+ -- XXX: these will unify to
99+ -- > both :: forall (p :: Multiplicity). Traversal p a b (a,a) (b,b)
100+ both' :: PTraversal a b (a ,a ) (b ,b )
101+ both' = _Pairing .> ptraversed
102+
103+ both :: DTraversal a b (a ,a ) (b ,b )
104+ both = _Pairing .> dtraversed
105+
106+ -- XXX: these are a special case of Bitraversable, but just the simple case
107+ -- is included here for now
108+ _Pairing :: Iso (Pair a ) (Pair b ) (a ,a ) (b ,b )
109+ _Pairing = iso Paired unpair
110+
111+ newtype Pair a = Paired (a ,a )
112+ unpair :: Pair a ->. (a ,a )
113+ unpair (Paired x) = x
114+
115+ instance P. Functor Pair where
116+ fmap f (Paired (x,y)) = Paired (f x, f y)
117+ instance Functor Pair where
118+ fmap f (Paired (x,y)) = Paired (f x, f y)
119+ instance Foldable Pair where
120+ foldMap f (Paired (x,y)) = f x P. <> f y
121+ instance P. Traversable Pair where
122+ traverse f (Paired (x,y)) = Paired P. <$> ((,) P. <$> f x P. <*> f y)
123+ instance Traversable Pair where
124+ traverse f (Paired (x,y)) = Paired <$> ((,) <$> f x <*> f y)
125+
126+ toListOf :: Optic_ (NonLinear. Kleisli (Const [a ])) a b s t -> s -> [a ]
127+ toListOf l = gets l (\ a -> [a])
128+
81129_Left :: Prism a b (Either a c ) (Either b c )
82130_Left = Optical first
83131
@@ -90,8 +138,11 @@ _Just = prism Just (maybe (Left Nothing) Right)
90138_Nothing :: Prism' () (Maybe a )
91139_Nothing = prism (\ () -> Nothing ) Left
92140
93- traversed :: Traversable t => Traversal a b (t a ) (t b )
94- traversed = Optical wander
141+ ptraversed :: P. Traversable t => PTraversal a b (t a ) (t b )
142+ ptraversed = Optical pwander
143+
144+ dtraversed :: Traversable t => DTraversal a b (t a ) (t b )
145+ dtraversed = Optical dwander
95146
96147over :: Optic_ LinearArrow a b s t -> (a ->. b ) -> s ->. t
97148over (Optical l) f = getLA (l (LA f))
@@ -105,6 +156,18 @@ get l = gets l P.id
105156gets :: Optic_ (NonLinear. Kleisli (Const r )) a b s t -> (a -> r ) -> s -> r
106157gets (Optical l) f s = getConst' (NonLinear. runKleisli (l (NonLinear. Kleisli (Const P. . f))) s)
107158
159+ preview :: Optic_ (NonLinear. Kleisli (Const (Maybe (First a )))) a b s t -> s -> Maybe a
160+ preview (Optical l) s = getFirst P. <$> (getConst (NonLinear. runKleisli (l (NonLinear. Kleisli (\ a -> Const (Just (First a))))) s))
161+
162+ get' :: Optic_ (Linear. Kleisli (Const (Top , a ))) a b s t -> s ->. (Top , a )
163+ get' l = gets' l id
164+
165+ gets' :: Optic_ (Linear. Kleisli (Const (Top , r ))) a b s t -> (a ->. r ) -> s ->. (Top , r )
166+ gets' (Optical l) f s = getConst' (Linear. runKleisli (l (Linear. Kleisli (\ a -> Const (mempty , f a)))) s)
167+
168+ set' :: Optic_ (Linear. Kleisli (MyFunctor a b )) a b s t -> s ->. b ->. (a , t )
169+ set' (Optical l) = runMyFunctor . Linear. runKleisli (l (Linear. Kleisli (\ a -> MyFunctor (\ b -> (a,b)))))
170+
108171set :: Optic_ (-> ) a b s t -> b -> s -> t
109172set (Optical l) x = l (const x)
110173
0 commit comments