{-# LANGUAGE RankNTypes #-} -- | Compose polymorphic record updates with /van Laarhoven/ lenses module Mini.Optics.Lens ( -- * Type Lens, -- * Construction lens, -- * Operations view, over, set, ) where import Control.Applicative ( Const ( Const, getConst ), ) import Data.Functor.Identity ( Identity ( Identity, runIdentity ), ) {- - Type -} -- | A reference updating structures from /s/ to /t/ and fields from /a/ to /b/ type Lens s t a b = forall f. (Functor f) => (a -> f b) -> (s -> f t) {- - Construction -} -- | Make a lens from a getter and a setter lens :: (s -> a) -> (s -> b -> t) -> Lens s t a b lens sa sbt ab s = sbt s <$> ab (sa s) {- - Operations -} -- | Fetch the field referenced by a lens from a structure view :: Lens s t a b -> s -> a view o = getConst . o Const -- | Update the field referenced by a lens with an operation on a structure over :: Lens s t a b -> (a -> b) -> s -> t over o ab = runIdentity . o (Identity . ab) -- | Overwrite the field referenced by a lens with a value on a structure set :: Lens s t a b -> b -> s -> t set o b = runIdentity . o (const $ Identity b)