@@ -13,39 +13,48 @@ module Control.Optics.Linear.Internal
13
13
, Iso , Iso'
14
14
, Lens , Lens'
15
15
, Prism , Prism'
16
- , Traversal , Traversal'
16
+ , PTraversal , PTraversal'
17
+ , DTraversal , DTraversal'
17
18
-- * Composing optics
18
19
, (.>)
19
20
-- * Common optics
20
21
, swap , assoc
21
22
, _1 , _2
22
23
, _Left , _Right
23
24
, _Just , _Nothing
24
- , traversed
25
+ , ptraversed , dtraversed
26
+ , both , both'
27
+ , get' , gets' , set'
25
28
-- * Using optics
26
29
, get , set , gets
27
30
, match , match' , build
31
+ , preview
28
32
, over , over'
29
33
, traverseOf , traverseOf'
30
34
, lengthOf
31
35
, withIso
36
+ , toListOf
32
37
-- * Constructing optics
33
- , iso , prism
38
+ , iso , prism , lens
34
39
)
35
40
where
36
41
37
42
import qualified Data.Bifunctor.Linear as Bifunctor
38
43
import Data.Bifunctor.Linear (SymmetricMonoidal )
39
44
import Data.Functor.Const
40
45
import Data.Functor.Linear
41
- import Data.Monoid
46
+ import Data.Semigroup.Linear
42
47
import Data.Profunctor.Linear
43
48
import qualified Data.Profunctor.Kleisli.Linear as L
44
49
import qualified Data.Profunctor.Kleisli.NonLinear as NL
45
50
import Data.Void
46
- import Prelude.Linear
51
+ import Prelude.Linear hiding ((<$>) )
52
+ -- ^ XXX: not entirely sure why the hiding is necessary here...
47
53
import qualified Prelude as P
48
54
55
+ -- TODO: documentation in this module
56
+ -- Put the functions in some sensible order: possibly split into separate
57
+ -- Lens/Prism/Traversal/Iso modules
49
58
newtype Optic_ arr a b s t = Optical (a `arr ` b -> s `arr ` t )
50
59
51
60
type Optic c a b s t =
@@ -57,8 +66,12 @@ type Lens a b s t = Optic (Strong (,) ()) a b s t
57
66
type Lens' a s = Lens a a s s
58
67
type Prism a b s t = Optic (Strong Either Void ) a b s t
59
68
type 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
62
75
63
76
swap :: SymmetricMonoidal m u => Iso (a `m ` b ) (c `m ` d ) (b `m ` a ) (d `m ` c )
64
77
swap = iso Bifunctor. swap Bifunctor. swap
@@ -69,6 +82,10 @@ assoc = iso Bifunctor.lassoc Bifunctor.rassoc
69
82
(.>) :: Optic_ arr a b s t -> Optic_ arr x y a b -> Optic_ arr x y s t
70
83
Optical f .> Optical g = Optical (f P. . g)
71
84
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
+
72
89
prism :: (b ->. t ) -> (s ->. Either t a ) -> Prism a b s t
73
90
prism b s = Optical $ \ f -> dimap s (either id id ) (second (rmap b f))
74
91
@@ -78,6 +95,37 @@ _1 = Optical first
78
95
_2 :: Lens a b (c ,a ) (c ,b )
79
96
_2 = Optical second
80
97
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_ (NL. Kleisli (Const [a ])) a b s t -> s -> [a ]
127
+ toListOf l = gets l (\ a -> [a])
128
+
81
129
_Left :: Prism a b (Either a c ) (Either b c )
82
130
_Left = Optical first
83
131
@@ -90,8 +138,11 @@ _Just = prism Just (maybe (Left Nothing) Right)
90
138
_Nothing :: Prism' () (Maybe a )
91
139
_Nothing = prism (\ () -> Nothing ) Left
92
140
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
95
146
96
147
over :: Optic_ LinearArrow a b s t -> (a ->. b ) -> s ->. t
97
148
over (Optical l) f = getLA (l (LA f))
@@ -105,6 +156,18 @@ get l = gets l P.id
105
156
gets :: Optic_ (NL. Kleisli (Const r )) a b s t -> (a -> r ) -> s -> r
106
157
gets (Optical l) f s = getConst' (NL. runKleisli (l (NL. Kleisli (Const P. . f))) s)
107
158
159
+ preview :: Optic_ (NL. Kleisli (Const (Maybe (First a )))) a b s t -> s -> Maybe a
160
+ preview (Optical l) s = getFirst P. <$> (getConst (NL. runKleisli (l (NL. Kleisli (\ a -> Const (Just (First a))))) s))
161
+
162
+ get' :: Optic_ (L. Kleisli (Const (Top , a ))) a b s t -> s ->. (Top , a )
163
+ get' l = gets' l id
164
+
165
+ gets' :: Optic_ (L. Kleisli (Const (Top , r ))) a b s t -> (a ->. r ) -> s ->. (Top , r )
166
+ gets' (Optical l) f s = getConst' (L. runKleisli (l (L. Kleisli (\ a -> Const (mempty , f a)))) s)
167
+
168
+ set' :: Optic_ (L. Kleisli (MyFunctor a b )) a b s t -> s ->. b ->. (a , t )
169
+ set' (Optical l) = runMyFunctor . L. runKleisli (l (L. Kleisli (\ a -> MyFunctor (\ b -> (a,b)))))
170
+
108
171
set :: Optic_ (-> ) a b s t -> b -> s -> t
109
172
set (Optical l) x = l (const x)
110
173
@@ -113,7 +176,7 @@ match (Optical l) = withIso swap (\x _ -> x) . L.runKleisli (l (L.Kleisli Left))
113
176
114
177
-- will be redundant with multiplicity polymorphism
115
178
match' :: Optic_ (NL. Kleisli (Either a )) a b s t -> s -> Either t a
116
- match' (Optical l) = withIso swap (\ x _ -> forget x) P. . NL. runKleisli (l (NL. Kleisli Left ))
179
+ match' (Optical l) = withIso swap (\ x _ -> eta x) P. . NL. runKleisli (l (NL. Kleisli Left ))
117
180
118
181
build :: Optic_ (L. CoKleisli (Const b )) a b s t -> b ->. t
119
182
build (Optical l) x = L. runCoKleisli (l (L. CoKleisli getConst')) (Const x)
0 commit comments