{-# LANGUAGE LiberalTypeSynonyms #-} ------------------------------------------------------------------------------- -- | -- Module : Data.Either.Lens -- Copyright : (C) 2012 Edward Kmett -- License : BSD-style (see the file LICENSE) -- Maintainer : Edward Kmett -- Stability : provisional -- Portability : portable -- -- Lenses for working with sums ------------------------------------------------------------------------------ module Data.Either.Lens ( traverseLeft , traverseRight ) where import Control.Applicative import Control.Lens -- | A traversal for tweaking the left-hand value of an 'Either': -- -- @traverseLeft :: 'Applicative' f => (a -> f b) -> 'Either' a c -> f ('Either' b c)@ traverseLeft :: Traversal (Either a c) (Either b c) a b traverseLeft f (Left a) = Left <$> f a traverseLeft _ (Right c) = pure $ Right c {-# INLINE traverseLeft #-} -- | traverse the right-hand value of an 'Either': -- -- @'traverseRight' = 'Data.Traversable.traverse'@ -- -- Unfortunately the instance for -- @'Data.Traversable.Traversable' ('Either' c)@ is still missing from base, -- so this can't just be 'Data.Traversable.traverse' -- -- @traverseRight :: 'Applicative' f => (a -> f b) -> 'Either' c a -> f ('Either' c a)@ traverseRight :: Traversal (Either c a) (Either c b) a b traverseRight _ (Left c) = pure $ Left c traverseRight f (Right a) = Right <$> f a {-# INLINE traverseRight #-}