module Iri.Optics.Basics where import Iri.Prelude type Lens s t a b = forall f. (Functor f) => (a -> f b) -> s -> f t type Lens' s a = Lens s s a a 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 type Traversal s t a b = forall f. (Applicative f) => (a -> f b) -> s -> f t type Traversal' s a = Traversal s s a a type Iso s t a b = forall p f. (Profunctor p, Functor f) => p a (f b) -> p s (f t) type Iso' s a = Iso s s a a {-# INLINE prism #-} 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 forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k). Category cat => cat b c -> cat a b -> cat 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' #-} prism' :: (a -> s) -> (s -> Maybe a) -> Prism' s a prism' :: forall a s. (a -> s) -> (s -> Maybe a) -> Prism' s a prism' a -> s as s -> Maybe a sma = (a -> s) -> (s -> Either s a) -> Prism s s a a forall b t s a. (b -> t) -> (s -> Either t a) -> Prism s t a b prism a -> s as (\s s -> Either s a -> (a -> Either s a) -> Maybe a -> Either s a forall b a. b -> (a -> b) -> Maybe a -> b maybe (s -> Either s a forall a b. a -> Either a b Left s s) a -> Either s a forall a b. b -> Either a b Right (s -> Maybe a sma s s)) {-# INLINE lens #-} lens :: (s -> a) -> (s -> b -> t) -> Lens s t a b lens :: forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b lens s -> a sa s -> b -> t sbt a -> f b afb s s = s -> b -> t sbt s s (b -> t) -> f b -> f t forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> a -> f b afb (s -> a sa s s)