{-# LANGUAGE Rank2Types #-} -- | This module contains lenses for common structures in Haskell. -- It also contains the lens combinators 'mergeL' and '***'. module Lens.Family2.Stock ( -- * Lens Combinators Stock.mergeL , (***) -- * Stock Lenses , fstL, sndL , funL , mapL, intMapL , setL, intSetL -- * Types , LensFamily, Lens ) where import Lens.Family2.Unchecked (LensFamily, Lens) import qualified Lens.Family.Stock as Stock import Lens.Family ((^.), (^=)) import qualified Data.Map as Map import qualified Data.IntMap as IntMap import qualified Data.Set as Set import qualified Data.IntSet as IntSet -- I suspect there is a more clever way to define this function. -- | Given two lens families, make a new lens on their product. (***) :: LensFamily a1 a1' b1 b1' -> LensFamily a2 a2' b2 b2' -> LensFamily (a1, a2) (a1', a2') (b1, b2) (b1', b2') (***) l1 l2 f (a1, a2) = (\(v'1, v'2) -> (l1 ^= v'1 $ a1, l2 ^= v'2 $ a2)) `fmap` f (a1 ^. l1, a2 ^. l2) -- | Lens on the first element of a pair. fstL :: LensFamily (a, b) (a', b) a a' fstL = Stock.fstL -- | Lens on the second element of a pair. sndL :: LensFamily (a, b) (a, b') b b' sndL = Stock.sndL -- | Lens on a given point of a function. funL :: (Eq k) => k -> Lens (k -> v) v funL = Stock.funL -- | Lens on a given point of a 'Map.Map'. mapL :: (Ord k) => k -> Lens (Map.Map k v) (Maybe v) mapL = Stock.mapL -- | Lens on a given point of a 'IntMap.IntMap'. intMapL :: Int -> Lens (IntMap.IntMap v) (Maybe v) intMapL = Stock.intMapL -- | Lens on a given point of a 'Set.Set'. setL :: (Ord k) => k -> Lens (Set.Set k) Bool setL = Stock.setL -- | Lens on a given point of a 'IntSet.IntSet'. intSetL :: Int -> Lens IntSet.IntSet Bool intSetL = Stock.intSetL