{-# LANGUAGE RankNTypes #-} module Control.Foldl.Optics where import Data.Profunctor type Prism s t a b = forall p f. (Choice p, Applicative f) => p a (f b) -> p s (f t) type Prism' s a = Prism s s a a prism :: (b -> t) -> (s -> Either t a) -> Prism s t a b prism :: forall b t s a. (b -> t) -> (s -> Either t a) -> Prism s t a b prism b -> t bt s -> Either t a seta = (s -> Either t a) -> (Either t (f b) -> f t) -> p (Either t a) (Either t (f b)) -> p s (f t) forall a b c d. (a -> b) -> (c -> d) -> p b c -> p a d forall (p :: * -> * -> *) a b c d. Profunctor p => (a -> b) -> (c -> d) -> p b c -> p a d dimap s -> Either t a seta ((t -> f t) -> (f b -> f t) -> Either t (f b) -> f t forall a c b. (a -> c) -> (b -> c) -> Either a b -> c either t -> f t forall a. a -> f a forall (f :: * -> *) a. Applicative f => a -> f a pure ((b -> t) -> f b -> f t forall a b. (a -> b) -> f a -> f b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap b -> t bt)) (p (Either t a) (Either t (f b)) -> p s (f t)) -> (p a (f b) -> p (Either t a) (Either t (f b))) -> p a (f b) -> p s (f t) forall b c a. (b -> c) -> (a -> b) -> a -> c . p a (f b) -> p (Either t a) (Either t (f b)) forall a b c. p a b -> p (Either c a) (Either c b) forall (p :: * -> * -> *) a b c. Choice p => p a b -> p (Either c a) (Either c b) right' {-# INLINE prism #-} _Left :: Prism (Either a c) (Either b c) a b _Left :: forall a c b (p :: * -> * -> *) (f :: * -> *). (Choice p, Applicative f) => p a (f b) -> p (Either a c) (f (Either b c)) _Left = (b -> Either b c) -> (Either a c -> Either (Either b c) a) -> forall {p :: * -> * -> *} {f :: * -> *}. (Choice p, Applicative f) => p a (f b) -> p (Either a c) (f (Either b c)) forall b t s a. (b -> t) -> (s -> Either t a) -> Prism s t a b prism b -> Either b c forall a b. a -> Either a b Left ((Either a c -> Either (Either b c) a) -> forall {p :: * -> * -> *} {f :: * -> *}. (Choice p, Applicative f) => p a (f b) -> p (Either a c) (f (Either b c))) -> (Either a c -> Either (Either b c) a) -> forall {p :: * -> * -> *} {f :: * -> *}. (Choice p, Applicative f) => p a (f b) -> p (Either a c) (f (Either b c)) forall a b. (a -> b) -> a -> b $ (a -> Either (Either b c) a) -> (c -> Either (Either b c) a) -> Either a c -> Either (Either b c) a forall a c b. (a -> c) -> (b -> c) -> Either a b -> c either a -> Either (Either b c) a forall a b. b -> Either a b Right (Either b c -> Either (Either b c) a forall a b. a -> Either a b Left (Either b c -> Either (Either b c) a) -> (c -> Either b c) -> c -> Either (Either b c) a forall b c a. (b -> c) -> (a -> b) -> a -> c . c -> Either b c forall a b. b -> Either a b Right) {-# INLINE _Left #-} _Right :: Prism (Either c a) (Either c b) a b _Right :: forall c a b (p :: * -> * -> *) (f :: * -> *). (Choice p, Applicative f) => p a (f b) -> p (Either c a) (f (Either c b)) _Right = (b -> Either c b) -> (Either c a -> Either (Either c b) a) -> forall {p :: * -> * -> *} {f :: * -> *}. (Choice p, Applicative f) => p a (f b) -> p (Either c a) (f (Either c b)) forall b t s a. (b -> t) -> (s -> Either t a) -> Prism s t a b prism b -> Either c b forall a b. b -> Either a b Right ((Either c a -> Either (Either c b) a) -> forall {p :: * -> * -> *} {f :: * -> *}. (Choice p, Applicative f) => p a (f b) -> p (Either c a) (f (Either c b))) -> (Either c a -> Either (Either c b) a) -> forall {p :: * -> * -> *} {f :: * -> *}. (Choice p, Applicative f) => p a (f b) -> p (Either c a) (f (Either c b)) forall a b. (a -> b) -> a -> b $ (c -> Either (Either c b) a) -> (a -> Either (Either c b) a) -> Either c a -> Either (Either c b) a forall a c b. (a -> c) -> (b -> c) -> Either a b -> c either (Either c b -> Either (Either c b) a forall a b. a -> Either a b Left (Either c b -> Either (Either c b) a) -> (c -> Either c b) -> c -> Either (Either c b) a forall b c a. (b -> c) -> (a -> b) -> a -> c . c -> Either c b forall a b. a -> Either a b Left) a -> Either (Either c b) a forall a b. b -> Either a b Right {-# INLINE _Right #-}