@@ -13,38 +13,49 @@ 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 Control.Arrow as NonLinear
3843import qualified Data.Bifunctor.Linear as Bifunctor
3944import Data.Bifunctor.Linear (SymmetricMonoidal )
4045import Data.Monoid
46+ import Data.Functor.Const
47+ import Data.Functor.Linear
4148import Data.Profunctor.Linear
4249import Data.Functor.Linear
4350import qualified Data.Profunctor.Kleisli.Linear as Linear
4451import Data.Void
45- import Prelude.Linear
52+ import Prelude.Linear hiding ((<$>) )
53+ -- ^ XXX: not entirely sure why the hiding is necessary here...
4654import qualified Prelude as P
4755
56+ -- TODO: documentation in this module
57+ -- Put the functions in some sensible order: possibly split into separate
58+ -- Lens/Prism/Traversal/Iso modules
4859newtype Optic_ arr a b s t = Optical (a `arr ` b -> s `arr ` t )
4960
5061type Optic c a b s t =
@@ -56,8 +67,12 @@ type Lens a b s t = Optic (Strong (,) ()) a b s t
5667type Lens' a s = Lens a a s s
5768type Prism a b s t = Optic (Strong Either Void ) a b s t
5869type Prism' a s = Prism a a s s
59- type Traversal a b s t = Optic Wandering a b s t
60- type Traversal' a s = Traversal a a s s
70+ type PTraversal a b s t = Optic PWandering a b s t
71+ type PTraversal' a s = PTraversal a a s s
72+ type DTraversal a b s t = Optic DWandering a b s t
73+ type DTraversal' a s = DTraversal a a s s
74+ -- XXX: these will unify into
75+ -- type Traversal (p :: Multiplicity) a b s t = Optic (Wandering p) a b s t
6176
6277swap :: SymmetricMonoidal m u => Iso (a `m ` b ) (c `m ` d ) (b `m ` a ) (d `m ` c )
6378swap = iso Bifunctor. swap Bifunctor. swap
@@ -68,6 +83,10 @@ assoc = iso Bifunctor.lassoc Bifunctor.rassoc
6883(.>) :: Optic_ arr a b s t -> Optic_ arr x y a b -> Optic_ arr x y s t
6984Optical f .> Optical g = Optical (f P. . g)
7085
86+ -- c is the complement (probably)
87+ lens :: (s ->. (c ,a )) -> ((c ,b ) ->. t ) -> Lens a b s t
88+ lens sca cbt = Optical $ \ f -> dimap sca cbt (second f)
89+
7190prism :: (b ->. t ) -> (s ->. Either t a ) -> Prism a b s t
7291prism b s = Optical $ \ f -> dimap s (either id id ) (second (rmap b f))
7392
@@ -77,6 +96,37 @@ _1 = Optical first
7796_2 :: Lens a b (c ,a ) (c ,b )
7897_2 = Optical second
7998
99+ -- XXX: these will unify to
100+ -- > both :: forall (p :: Multiplicity). Traversal p a b (a,a) (b,b)
101+ both' :: PTraversal a b (a ,a ) (b ,b )
102+ both' = _Pairing .> ptraversed
103+
104+ both :: DTraversal a b (a ,a ) (b ,b )
105+ both = _Pairing .> dtraversed
106+
107+ -- XXX: these are a special case of Bitraversable, but just the simple case
108+ -- is included here for now
109+ _Pairing :: Iso (Pair a ) (Pair b ) (a ,a ) (b ,b )
110+ _Pairing = iso Paired unpair
111+
112+ newtype Pair a = Paired (a ,a )
113+ unpair :: Pair a ->. (a ,a )
114+ unpair (Paired x) = x
115+
116+ instance P. Functor Pair where
117+ fmap f (Paired (x,y)) = Paired (f x, f y)
118+ instance Functor Pair where
119+ fmap f (Paired (x,y)) = Paired (f x, f y)
120+ instance Foldable Pair where
121+ foldMap f (Paired (x,y)) = f x P. <> f y
122+ instance P. Traversable Pair where
123+ traverse f (Paired (x,y)) = Paired P. <$> ((,) P. <$> f x P. <*> f y)
124+ instance Traversable Pair where
125+ traverse f (Paired (x,y)) = Paired <$> ((,) <$> f x <*> f y)
126+
127+ toListOf :: Optic_ (NonLinear. Kleisli (Const [a ])) a b s t -> s -> [a ]
128+ toListOf l = gets l (\ a -> [a])
129+
80130_Left :: Prism a b (Either a c ) (Either b c )
81131_Left = Optical first
82132
@@ -89,8 +139,11 @@ _Just = prism Just (maybe (Left Nothing) Right)
89139_Nothing :: Prism' () (Maybe a )
90140_Nothing = prism (\ () -> Nothing ) Left
91141
92- traversed :: Traversable t => Traversal a b (t a ) (t b )
93- traversed = Optical wander
142+ ptraversed :: P. Traversable t => PTraversal a b (t a ) (t b )
143+ ptraversed = Optical pwander
144+
145+ dtraversed :: Traversable t => DTraversal a b (t a ) (t b )
146+ dtraversed = Optical dwander
94147
95148over :: Optic_ LinearArrow a b s t -> (a ->. b ) -> s ->. t
96149over (Optical l) f = getLA (l (LA f))
@@ -104,6 +157,18 @@ get l = gets l P.id
104157gets :: Optic_ (NonLinear. Kleisli (Const r )) a b s t -> (a -> r ) -> s -> r
105158gets (Optical l) f s = getConst' (NonLinear. runKleisli (l (NonLinear. Kleisli (Const P. . f))) s)
106159
160+ preview :: Optic_ (NonLinear. Kleisli (Const (Maybe (First a )))) a b s t -> s -> Maybe a
161+ preview (Optical l) s = getFirst P. <$> (getConst (NonLinear. runKleisli (l (NonLinear. Kleisli (\ a -> Const (Just (First a))))) s))
162+
163+ get' :: Optic_ (Linear. Kleisli (Const (Top , a ))) a b s t -> s ->. (Top , a )
164+ get' l = gets' l id
165+
166+ gets' :: Optic_ (Linear. Kleisli (Const (Top , r ))) a b s t -> (a ->. r ) -> s ->. (Top , r )
167+ gets' (Optical l) f s = getConst' (Linear. runKleisli (l (Linear. Kleisli (\ a -> Const (mempty , f a)))) s)
168+
169+ set' :: Optic_ (Linear. Kleisli (MyFunctor a b )) a b s t -> s ->. b ->. (a , t )
170+ set' (Optical l) = runMyFunctor . Linear. runKleisli (l (Linear. Kleisli (\ a -> MyFunctor (\ b -> (a,b)))))
171+
107172set :: Optic_ (-> ) a b s t -> b -> s -> t
108173set (Optical l) x = l (const x)
109174
0 commit comments