{-# LANGUAGE RankNTypes #-} module Chiasma.Ui.Lens.Ident( matchIdent, matchIdentL, matchIdentP, ) where import Control.Lens (Traversal', Prism', filtered, each, prism) import Chiasma.Data.Ident (Ident, Identifiable(..), sameIdent) matchIdent :: Identifiable a => Ident -> Traversal' a a matchIdent :: Ident -> Traversal' a a matchIdent = (a -> Bool) -> Optic' (->) f a a forall (p :: * -> * -> *) (f :: * -> *) a. (Choice p, Applicative f) => (a -> Bool) -> Optic' p f a a filtered ((a -> Bool) -> Optic' (->) f a a) -> (Ident -> a -> Bool) -> Ident -> Optic' (->) f a a forall b c a. (b -> c) -> (a -> b) -> a -> c . Ident -> a -> Bool forall a b. (Identifiable a, Identifiable b) => a -> b -> Bool sameIdent matchIdentL :: Identifiable a => Ident -> Traversal' [a] a matchIdentL :: Ident -> Traversal' [a] a matchIdentL Ident ident = (a -> f a) -> [a] -> f [a] forall s t a b. Each s t a b => Traversal s t a b each ((a -> f a) -> [a] -> f [a]) -> ((a -> f a) -> a -> f a) -> (a -> f a) -> [a] -> f [a] forall b c a. (b -> c) -> (a -> b) -> a -> c . Ident -> Traversal' a a forall a. Identifiable a => Ident -> Traversal' a a matchIdent Ident ident identEither :: Identifiable a => Ident -> a -> Either a a identEither :: Ident -> a -> Either a a identEither Ident target a a = if Ident -> a -> Bool forall a b. (Identifiable a, Identifiable b) => a -> b -> Bool sameIdent Ident target a a then a -> Either a a forall a b. b -> Either a b Right a a else a -> Either a a forall a b. a -> Either a b Left a a matchIdentP :: Identifiable a => Ident -> Prism' a a matchIdentP :: Ident -> Prism' a a matchIdentP Ident ident = (a -> a) -> (a -> Either a a) -> Prism' a a forall b t s a. (b -> t) -> (s -> Either t a) -> Prism s t a b prism a -> a forall a. a -> a id (Ident -> a -> Either a a forall a. Identifiable a => Ident -> a -> Either a a identEither Ident ident)