-- | This is the main module for end-users of lens-families-core. -- If you are not building your own lenses or traversals, but just using functional references made by others, this is the only module you need. module Lens.Family ( -- * Lenses -- -- | This module provides '^.' for accessing fields and '.~' and '%~' for setting and modifying fields. -- Lenses are composed with `Prelude..` from the @Prelude@ and `Prelude.id` is the identity lens. -- -- Lens composition in this library enjoys the following identities. -- -- * @x^.l1.l2 === x^.l1^.l2@ -- -- * @l1.l2 %~ f === l1 %~ l2 %~ f@ -- -- The identity lens behaves as follows. -- -- * @x^.id === x@ -- -- * @id %~ f === f@ -- -- The '&' operator, allows for a convenient way to sequence record updating: -- -- @record & l1 .~ value1 & l2 .~ value2@ -- -- Lenses are implemented in van Laarhoven style. -- Lenses have type @'Functor' f => (b -> f b) -> a -> f a@ and lens families have type @'Functor' f => (b i -> f (b j)) -> a i -> f (a j)@. -- -- Keep in mind that lenses and lens families can be used directly for functorial updates. -- For example, @_2 id@ gives you strength. -- -- > _2 id :: Functor f => (a, f b) -> f (a, b) -- -- Here is an example of code that uses the 'Maybe' functor to preserves sharing during update when possible. -- -- > -- | 'sharedUpdate' returns the *identical* object if the update doesn't change anything. -- > -- This is useful for preserving sharing. -- > sharedUpdate :: Eq b => LensLike' Maybe a b -> (b -> b) -> a -> a -- > sharedUpdate l f a = fromMaybe a (l f' a) -- > where -- > f' b | fb == b = Nothing -- > | otherwise = Just fb -- > where -- > fb = f b -- * Traversals -- -- | '^.' can be used with traversals to access monoidal fields. -- The result will be a 'Data.Monid.mconcat' of all the fields referenced. -- The various @fooOf@ functions can be used to access different monoidal summaries of some kinds of values. -- -- '^?' can be used to access the first value of a traversal. -- 'Nothing' is returned when the traversal has no references. -- -- '^..' can be used with a traversals and will return a list of all fields referenced. -- -- When '.~' is used with a traversal, all referenced fields will be set to the same value, and when '%~' is used with a traversal, all referenced fields will be modified with the same function. -- -- Like lenses, traversals can be composed with '.', and because every lens is automatically a traversal, lenses and traversals can be composed with '.' yielding a traversal. -- -- Traversals are implemented in van Laarhoven style. -- Traversals have type @'Applicative' f => (b -> f b) -> a -> f a@ and traversal families have type @'Applicative' f => (b i -> f (b j)) -> a i -> f (a j)@. -- -- For stock lenses and traversals, see "Lens.Family.Stock". -- -- To build your own lenses and traversals, see "Lens.Family.Unchecked". -- -- References: -- -- * -- -- * -- -- * -- -- * -- * Documentation to, view, (^.) , folding, views, (^..), (^?) , toListOf, allOf, anyOf, firstOf, lastOf, sumOf, productOf , lengthOf, nullOf , backwards , over, (%~), set, (.~) , (&) -- * Pseudo-imperatives , (+~), (*~), (-~), (//~), (&&~), (||~), (<>~) -- * Types , LensLike, LensLike' , FoldLike, FoldLike' , ASetter, ASetter' , Phantom , Constant, Identity -- * Re-exports , Applicative, Foldable, Monoid , Backwards, All, Any, First, Last, Sum, Product ) where import Control.Applicative (Applicative) import Control.Applicative.Backwards (Backwards(..)) import Data.Foldable (Foldable, traverse_) import Data.Functor.Identity (Identity(..)) import Data.Functor.Constant (Constant(..)) import Data.Monoid ( Monoid, mappend , All(..), Any(..) , First(..), Last(..) , Sum(..), Product(..) ) import Lens.Family.Phantom (Phantom, coerce) import Lens.Family.Unchecked ( LensLike, LensLike' ) type FoldLike r a a' b b' = LensLike (Constant r) a a' b b' type FoldLike' r a b = LensLike' (Constant r) a b type ASetter a a' b b' = LensLike Identity a a' b b' type ASetter' a b = LensLike' Identity a b to :: Phantom f => (a -> b) -> LensLike f a a' b b' -- ^ @ -- to :: (a -> b) -> Getter a a' b b' -- @ -- -- 'to' promotes a projection function to a read-only lens called a getter. -- To demote a lens to a projection function, use the section @(^.l)@ or @view l@. -- -- >>> (3 :+ 4, "example")^._1.to(abs) -- 5.0 :+ 0.0 to p f = coerce . f . p view :: FoldLike b a a' b b' -> a -> b -- ^ @ -- view :: Getter a a' b b' -> a -> b -- @ -- -- Demote a lens or getter to a projection function. -- -- @ -- view :: Monoid b => Fold a a' b b' -> a -> b -- @ -- -- Returns the monoidal summary of a traversal or a fold. view l = (^.l) folding :: (Foldable g, Phantom f, Applicative f) => (a -> g b) -> LensLike f a a' b b' -- ^ @ -- folding :: (a -> [b]) -> Fold a a' b b' -- @ -- -- 'folding' promotes a \"toList\" function to a read-only traversal called a fold. -- -- To demote a traversal or fold to a \"toList\" function use the section @(^..l)@ or @toListOf l@. folding p f = coerce . traverse_ f . p views :: FoldLike r a a' b b' -> (b -> r) -> a -> r -- ^ @ -- views :: Monoid r => Fold a a' b b' -> (b -> r) -> a -> r -- @ -- -- Given a fold or traversal, return the 'foldMap' of all the values using the given function. -- -- @ -- views :: Getter a a' b b' -> (b -> r) -> a -> r -- @ -- -- 'views' is not particularly useful for getters or lenses, but given a getter or lens, it returns the referenced value passed through the given function. -- -- @ -- views l f a = f (view l a) -- @ views l f = getConstant . l (Constant . f) toListOf :: FoldLike [b] a a' b b' -> a -> [b] -- ^ @ -- toListOf :: Fold a a' b b' -> a -> [b] -- @ -- -- Returns a list of all of the referenced values in order. toListOf l = views l (:[]) allOf :: FoldLike All a a' b b' -> (b -> Bool) -> a -> Bool -- ^ @ -- allOf :: Fold a a' b b' -> (b -> Bool) -> a -> Bool -- @ -- -- Returns true if all of the referenced values satisfy the given predicate. allOf l p = getAll . views l (All . p) anyOf :: FoldLike Any a a' b b' -> (b -> Bool) -> a -> Bool -- ^ @ -- anyOf :: Fold a a' b b' -> (b -> Bool) -> a -> Bool -- @ -- -- Returns true if any of the referenced values satisfy the given predicate. anyOf l p = getAny . views l (Any . p) firstOf :: FoldLike (First b) a a' b b' -> a -> Maybe b -- ^ @ -- firstOf :: Fold a a' b b' -> a -> Maybe b -- @ -- -- Returns 'Just' the first referenced value. -- Returns 'Nothing' if there are no referenced values. -- See '^?' for an infix version of 'firstOf' firstOf l = getFirst . views l (First . Just) lastOf :: FoldLike (Last b) a a' b b' -> a -> Maybe b -- ^ @ -- lastOf :: Fold a a' b b' -> a -> Maybe b -- @ -- -- Returns 'Just' the last referenced value. -- Returns 'Nothing' if there are no referenced values. lastOf l = getLast . views l (Last . Just) sumOf :: Num b => FoldLike (Sum b) a a' b b' -> a -> b -- ^ @ -- sumOf :: Num b => Fold a a' b b' -> a -> b -- @ -- -- Returns the sum of all the referenced values. sumOf l = getSum . views l Sum productOf :: Num b => FoldLike (Product b) a a' b b' -> a -> b -- ^ @ -- productOf :: Num b => Fold a a' b b' -> a -> b -- @ -- -- Returns the product of all the referenced values. productOf l = getProduct . views l Product lengthOf :: Num r => FoldLike (Sum r) a a' b b' -> a -> r -- ^ @ -- lengthOf :: Num r => Fold a a' b b' -> a -> r -- @ -- -- Counts the number of references in a traversal or fold for the input. lengthOf l = getSum . views l (const (Sum 1)) nullOf :: FoldLike All a a' b b' -> a -> Bool -- ^ @ -- nullOf :: Fold a a' b b' -> a -> Bool -- @ -- -- Returns true if the number of references in the input is zero. nullOf l = allOf l (const False) infixl 8 ^. (^.) :: a -> FoldLike b a a' b b' -> b -- ^ @ -- (^.) :: a -> Getter a a' b b' -> b -- @ -- -- Access the value referenced by a getter or lens. -- -- @ -- (^.) :: Monoid b => a -> Fold a a' b b' -> b -- @ -- -- Access the monoidal summary referenced by a getter or lens. x^.l = getConstant $ l Constant x infixl 8 ^.. (^..) :: a -> FoldLike [b] a a' b b' -> [b] -- ^ @ -- (^..) :: a -> Getter a a' b b' -> [b] -- @ -- -- Returns a list of all of the referenced values in order. x^..l = toListOf l x infixl 8 ^? (^?) :: a -> FoldLike (First b) a a' b b' -> Maybe b -- ^ @ -- (^?) :: a -> Fold a a' b b' -> Maybe b -- @ -- -- Returns 'Just' the first referenced value. -- Returns 'Nothing' if there are no referenced values. x^?l = firstOf l x backwards :: LensLike (Backwards f) a a' b b' -> LensLike f a a' b b' -- ^ @ -- backwards :: Traversal a a' b b' -> Traversal a a' b b' -- backwards :: Fold a a' b b' -> Fold a a' b b' -- @ -- -- Given a traversal or fold, reverse the order that elements are traversed. -- -- @ -- backwards :: Lens a a' b b' -> Lens a a' b b' -- backwards :: Getter a a' b b' -> Getter a a' b b' -- backwards :: Setter a a' b b' -> Setter a a' b b' -- @ -- -- No effect on lenses, getters or setters. backwards l f = forwards . l (Backwards . f) -- | Demote a setter to a semantic editor combinator. over :: ASetter a a' b b' -> (b -> b') -> a -> a' over l = (l %~) infixr 4 %~ -- | Modify all referenced fields. (%~) :: ASetter a a' b b' -> (b -> b') -> a -> a' l %~ f = runIdentity . l (Identity . f) infixr 4 .~ -- | Set all referenced fields to the given value. (.~) :: ASetter a a' b b' -> b' -> a -> a' l .~ b = l %~ const b -- | Set all referenced fields to the given value. set :: ASetter a a' b b' -> b' -> a -> a' set = (.~) infixl 1 & -- | A flipped version of @($)@. (&) :: a -> (a -> b) -> b (&) = flip ($) infixr 4 +~, -~, *~ (+~), (-~), (*~) :: Num b => ASetter' a b -> b -> a -> a f +~ b = f %~ (+ b) f -~ b = f %~ subtract b f *~ b = f %~ (* b) infixr 4 //~ (//~) :: Fractional b => ASetter' a b -> b -> a -> a f //~ b = f %~ (/ b) infixr 4 &&~, ||~ (&&~), (||~) :: ASetter' a Bool -> Bool -> a -> a f &&~ b = f %~ (&& b) f ||~ b = f %~ (|| b) infixr 4 <>~ -- | Monoidally append a value to all referenced fields. (<>~) :: (Monoid o) => ASetter' a o -> o -> a -> a f <>~ o = f %~ (`mappend` o)