Skip to content

Commit d8c2e33

Browse files
committed
A plethora of optics
1 parent dd65d13 commit d8c2e33

File tree

6 files changed

+125
-24
lines changed

6 files changed

+125
-24
lines changed

src/Control/Optics/Linear/Internal.hs

Lines changed: 73 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -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

3742
import qualified Control.Arrow as NonLinear
3843
import qualified Data.Bifunctor.Linear as Bifunctor
44+
import qualified Control.Monad.Linear as Control
3945
import Data.Bifunctor.Linear (SymmetricMonoidal)
40-
import Data.Profunctor.Linear
46+
import Data.Monoid.Linear
47+
import Data.Functor.Const
4148
import Data.Functor.Linear
49+
import Data.Profunctor.Linear
4250
import qualified Data.Profunctor.Kleisli.Linear as Linear
4351
import Data.Void
4452
import Prelude.Linear
4553
import 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
4758
newtype Optic_ arr a b s t = Optical (a `arr` b -> s `arr` t)
4859

4960
type Optic c a b s t =
@@ -55,8 +66,12 @@ type Lens a b s t = Optic (Strong (,) ()) a b s t
5566
type Lens' a s = Lens a a s s
5667
type Prism a b s t = Optic (Strong Either Void) a b s t
5768
type 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

6176
swap :: SymmetricMonoidal m u => Iso (a `m` b) (c `m` d) (b `m` a) (d `m` c)
6277
swap = 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
6883
Optical 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+
7091
prism :: (b ->. t) -> (s ->. Either t a) -> Prism a b s t
7192
prism 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

94149
over :: Optic_ LinearArrow a b s t -> (a ->. b) -> s ->. t
95150
over (Optical l) f = getLA (l (LA f))
@@ -103,6 +158,15 @@ get l = gets l P.id
103158
gets :: Optic_ (NonLinear.Kleisli (Const r)) a b s t -> (a -> r) -> s -> r
104159
gets (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+
106170
set :: Optic_ (->) a b s t -> b -> s -> t
107171
set (Optical l) x = l (const x)
108172

src/Data/Profunctor/Kleisli/Linear.hs

Lines changed: 2 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -41,22 +41,14 @@ instance Control.Applicative f => Strong Either Void (Kleisli f) where
4141
first (Kleisli f) = Kleisli (either (Data.fmap Left . f) (Control.pure . Right))
4242
second (Kleisli g) = Kleisli (either (Control.pure . Left) (Data.fmap Right . g))
4343

44-
instance Control.Applicative f => Wandering (Kleisli f) where
45-
wander (Kleisli f) = Kleisli (Data.traverse f)
44+
instance Control.Applicative f => DWandering (Kleisli f) where
45+
dwander (Kleisli f) = Kleisli (Data.traverse f)
4646

4747
-- | Linear co-Kleisli arrows for the comonad `w`. These arrows are still
4848
-- useful in the case where `w` is not a comonad however, and some
4949
-- profunctorial properties still hold in this weaker setting.
5050
-- However stronger requirements on `f` are needed for profunctorial
5151
-- strength, so we have fewer instances.
52-
--
53-
-- Category theoretic remark: duality doesn't work in the obvious way, since
54-
-- (,) isn't the categorical product. Instead, we have a product (&), called
55-
-- "With", defined by
56-
-- > type With a b = forall r. Either (a ->. r) (b ->. r) ->. r
57-
-- which satisfies the universal property of the product of `a` and `b`.
58-
-- CoKleisli arrows are strong with respect to this monoidal structure,
59-
-- although this might not be useful...
6052
newtype CoKleisli w a b = CoKleisli { runCoKleisli :: w a ->. b }
6153

6254
instance Data.Functor f => Profunctor (CoKleisli f) where

src/Data/Profunctor/Linear.hs

Lines changed: 47 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,23 +1,32 @@
1+
{-# LANGUAGE GADTs #-}
12
{-# LANGUAGE FlexibleContexts #-}
3+
{-# LANGUAGE FlexibleInstances #-}
24
{-# LANGUAGE KindSignatures #-}
35
{-# LANGUAGE LambdaCase #-}
46
{-# LANGUAGE LinearTypes #-}
57
{-# LANGUAGE MultiParamTypeClasses #-}
68
{-# LANGUAGE NoImplicitPrelude #-}
9+
{-# LANGUAGE RankNTypes #-}
710
{-# LANGUAGE TupleSections #-}
811
{-# LANGUAGE TypeOperators #-}
912

13+
{-# OPTIONS_GHC -fno-warn-orphans #-}
14+
1015
module Data.Profunctor.Linear
1116
( Profunctor(..)
1217
, Monoidal(..)
1318
, Strong(..)
14-
, Wandering(..)
19+
, PWandering(..)
20+
, DWandering(..)
1521
, LinearArrow(..), getLA
1622
, Exchange(..)
1723
, Market(..), runMarket
24+
, MyFunctor(..), runMyFunctor
25+
, OtherFunctor(..), runOtherFunctor
1826
) where
1927

2028
import qualified Data.Functor.Linear as Data
29+
import qualified Control.Monad.Linear as Control
2130
import Data.Bifunctor.Linear hiding (first, second)
2231
import Prelude.Linear
2332
import Data.Void
@@ -56,8 +65,17 @@ class (SymmetricMonoidal m u, Profunctor arr) => Strong m u arr where
5665
second arr = dimap swap swap (first arr)
5766
{-# INLINE second #-}
5867

59-
class (Strong (,) () arr, Strong Either Void arr) => Wandering arr where
60-
wander :: Data.Traversable f => a `arr` b -> f a `arr` f b
68+
-- XXX: Just as Prelude.Functor/Data.Functor will combine into
69+
-- > `class Functor (p :: Multiplicity) f`
70+
-- so will Traversable, and then we would instead write
71+
-- > class (...) => Wandering (p :: Multiplicity) arr where
72+
-- > wander :: Traversable p f => a `arr` b -> f a `arr` f b
73+
-- For now, however, we cannot do this, so we use two classes instead:
74+
-- PreludeWandering and DataWandering
75+
class (Strong (,) () arr, Strong Either Void arr) => PWandering arr where
76+
pwander :: Prelude.Traversable f => a `arr` b -> f a `arr` f b
77+
class (Strong (,) () arr, Strong Either Void arr) => DWandering arr where
78+
dwander :: Data.Traversable f => a `arr` b -> f a `arr` f b
6179

6280
---------------
6381
-- Instances --
@@ -79,13 +97,18 @@ instance Strong Either Void LinearArrow where
7997
first (LA f) = LA $ either (Left . f) Right
8098
second (LA g) = LA $ either Left (Right . g)
8199

100+
instance DWandering LinearArrow where
101+
dwander (LA f) = LA (Data.fmap f)
102+
82103
instance Profunctor (->) where
83104
dimap f g h x = g (h (f x))
84105
instance Strong (,) () (->) where
85106
first f (x, y) = (f x, y)
86107
instance Strong Either Void (->) where
87108
first f (Left x) = Left (f x)
88109
first _ (Right y) = Right y
110+
instance PWandering (->) where
111+
pwander = Prelude.fmap
89112

90113
data Exchange a b s t = Exchange (s ->. a) (b ->. t)
91114
instance Profunctor (Exchange a b) where
@@ -112,3 +135,24 @@ instance Profunctor (Market a b) where
112135

113136
instance Strong Either Void (Market a b) where
114137
first (Market f g) = Market (Left . f) (either (either (Left . Left) Right . g) (Left . Right))
138+
139+
instance Prelude.Applicative f => PWandering (Kleisli f) where
140+
pwander (Kleisli f) = Kleisli (Prelude.traverse f)
141+
142+
-- TODO: pick a more sensible name for this
143+
newtype MyFunctor a b t = MyFunctor (b ->. (a, t))
144+
runMyFunctor :: MyFunctor a b t ->. b ->. (a, t)
145+
runMyFunctor (MyFunctor f) = f
146+
147+
instance Data.Functor (MyFunctor a b) where
148+
fmap f (MyFunctor g) = MyFunctor (getLA (second (LA f)) . g)
149+
instance Control.Functor (MyFunctor a b) where
150+
fmap f (MyFunctor g) = MyFunctor (Control.fmap f . g)
151+
152+
newtype OtherFunctor a b t = OtherFunctor (a, b ->. t)
153+
runOtherFunctor :: OtherFunctor a b t ->. (a, b ->. t)
154+
runOtherFunctor (OtherFunctor f) = f
155+
instance Data.Functor (OtherFunctor a b) where
156+
fmap f (OtherFunctor (a,g)) = OtherFunctor (a,f . g)
157+
instance Control.Functor (OtherFunctor a b) where
158+
fmap f (OtherFunctor (a,g)) = OtherFunctor (a,f . g)

src/Foreign/Marshal/Pure.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -60,7 +60,7 @@ import Foreign.Marshal.Utils
6060
import Foreign.Ptr
6161
import Foreign.Storable
6262
import Foreign.Storable.Tuple ()
63-
import Prelude (($), return, (<*>))
63+
import Prelude (($), return, (<*>), (<$>))
6464
import Prelude.Linear hiding (($))
6565
import System.IO.Unsafe
6666
import qualified Unsafe.Linear as Unsafe

src/Prelude/Linear.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -53,7 +53,7 @@ import Prelude hiding
5353
, foldr
5454
, maybe
5555
, (.)
56-
, Functor(..)
56+
, Functor(..), (<$>)
5757
, Applicative(..)
5858
, Monad(..)
5959
, Traversable(..)

src/System/IO/Linear.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -41,6 +41,7 @@ import qualified Control.Monad.Linear as Control
4141
import qualified Data.Functor.Linear as Data
4242
import GHC.Exts (State#, RealWorld)
4343
import Prelude.Linear hiding (IO)
44+
import Prelude ((<$>))
4445
import qualified Unsafe.Linear as Unsafe
4546
import qualified System.IO as System
4647

0 commit comments

Comments
 (0)