From 57257b3ccab7b06259f92b2d9f12754c7184859b Mon Sep 17 00:00:00 2001 From: Edward Kmett Date: Mon, 13 Aug 2012 00:49:45 -0400 Subject: [PATCH] renamed adjust to under to line up with over from Iso and Control.Newtype. added auf --- lens.cabal | 4 +-- src/Control/Lens/Iso.hs | 30 +++++++++++++----- src/Control/Lens/Setter.hs | 62 +++++++++++++++++++------------------- src/Data/Array/Lens.hs | 8 ++--- src/Data/Bits/Lens.hs | 4 +-- src/Data/IntSet/Lens.hs | 2 +- src/Data/Set/Lens.hs | 2 +- 7 files changed, 64 insertions(+), 48 deletions(-) diff --git a/lens.cabal b/lens.cabal index abf21d952..575ba26bd 100644 --- a/lens.cabal +++ b/lens.cabal @@ -1,6 +1,6 @@ name: lens category: Data, Lenses -version: 2.0.1 +version: 2.1 license: BSD3 cabal-version: >= 1.8 license-file: LICENSE @@ -33,7 +33,7 @@ description: . The core of this hierarchy looks like: . - <> + <> . You can compose any two elements of the hierarchy above using (.) from the Prelude, and you can use any element of the hierarchy as any type it links to above it. diff --git a/src/Control/Lens/Iso.hs b/src/Control/Lens/Iso.hs index b8c752a43..282de3079 100644 --- a/src/Control/Lens/Iso.hs +++ b/src/Control/Lens/Iso.hs @@ -17,6 +17,8 @@ module Control.Lens.Iso , iso , isos , au + , auf + , over -- ** Combinators , via , from @@ -162,24 +164,38 @@ iso ab ba = isos ab ba ab ba {-# SPECIALIZE iso :: Functor f => (a -> b) -> (b -> a) -> (b -> f b) -> a -> f a #-} {-# SPECIALIZE iso :: Functor f => (a -> b) -> (b -> a) -> Isomorphism (b -> f b) (a -> f a) #-} --- | Based on @ala@ from Conor McBride's work on Epigram and @Control.Newtype@ from the --- 'newtype package. +-- | Based on @ala@ from Conor McBride's work on Epigram. -- -- Mnemonically, /au/ is a French contraction of /à le/. -- -- >>> :m + Control.Lens Data.Monoid.Lens Data.Foldable -- >>> au _sum foldMap [1,2,3,4] -- 10 -au :: Simple Iso a b -> ((a -> b) -> e -> b) -> e -> a +au :: Simple Iso a b -> ((a -> b) -> c -> b) -> c -> a au l f e = f (view l) e ^. from l +{-# INLINE au #-} -{- -under :: Setter a b c d -> (c -> d) -> a -> b -under = adjust +-- | +-- Based on @ala'@ from Conor McBride's work on Epigram. +-- +-- Mnemonically, the German /auf/ both plays a similar role to /à la/, and it is /au/ with an +-- extra function argument. +auf :: Simple Iso a b -> ((d -> b) -> c -> b) -> (d -> a) -> c -> a +auf l f g e = f (view l . g) e ^. from l +{-# INLINE auf #-} +-- | The opposite of working 'under' an isomorphism. +-- +-- @'over' = 'under' . 'from'@ +-- +-- >>> :m + Control.Lens Data.Monoid Data.Monoid.Lens +-- >>> over _sum (mappend (Sum 2)) 10 +-- 12 +-- +-- @'over' :: Iso a b c d -> (a -> b) -> (c -> d)@ over :: Isomorphism (c -> Identity d) (a -> Identity b) -> (a -> b) -> c -> d over = under . from --} +{-# INLINE over #-} ----------------------------------------------------------------------------- -- Isomorphisms diff --git a/src/Control/Lens/Setter.hs b/src/Control/Lens/Setter.hs index b44a18e1f..9ee1b322e 100644 --- a/src/Control/Lens/Setter.hs +++ b/src/Control/Lens/Setter.hs @@ -31,7 +31,7 @@ module Control.Lens.Setter -- * Common Setters , mapped -- * Functional Combinators - , adjust + , under , mapOf , set , (.~), (%~) @@ -73,8 +73,8 @@ infixr 2 <~ -- However, two 'Functor' laws apply to a 'Setter': -- -- @ --- 'adjust' l 'id' = 'id' --- 'adjust' l f . 'adjust' l g = 'adjust' l (f . g) +-- 'under' l 'id' = 'id' +-- 'under' l f . 'under' l g = 'under' l (f . g) -- @ -- -- These an be stated more directly: @@ -162,8 +162,8 @@ instance Settable Mutator where -- | This setter can be used to map over all of the values in a 'Functor'. -- -- @ --- 'fmap' = 'adjust' 'mapped' --- 'Data.Traversable.fmapDefault' = 'adjust' 'Data.Traversable.traverse' +-- 'fmap' = 'under' 'mapped' +-- 'Data.Traversable.fmapDefault' = 'under' 'Data.Traversable.traverse' -- ('<$') = 'set' 'mapped' -- @ mapped :: Functor f => Setter (f a) (f b) a b @@ -182,8 +182,8 @@ mapped = sets fmap -- Equational reasoning: -- -- @ --- 'sets' . 'adjust' = 'id' --- 'adjust' . 'sets' = 'id' +-- 'sets' . 'under' = 'id' +-- 'under' . 'sets' = 'id' -- @ -- -- Another way to view 'sets' is that it takes a \"semantic editor combinator\" @@ -200,25 +200,25 @@ sets f g = pure . f (untainted . g) -- with a function. -- -- @ --- 'fmap' = 'adjust' 'mapped' --- 'Data.Traversable.fmapDefault' = 'adjust' 'Data.Traversable.traverse' --- 'sets' . 'adjust' = 'id' --- 'adjust' . 'sets' = 'id' +-- 'fmap' = 'under' 'mapped' +-- 'Data.Traversable.fmapDefault' = 'under' 'Data.Traversable.traverse' +-- 'sets' . 'under' = 'id' +-- 'under' . 'sets' = 'id' -- @ -- --- Another way to view 'adjust' is to say that it transformers a 'Setter' into a +-- Another way to view 'under' is to say that it transformers a 'Setter' into a -- \"semantic editor combinator\". -- --- @'adjust' :: 'Setter' a b c d -> (c -> d) -> a -> b@ -adjust :: Setting a b c d -> (c -> d) -> a -> b -adjust l f = runMutator . l (Mutator . f) -{-# INLINE adjust #-} +-- @'under' :: 'Setter' a b c d -> (c -> d) -> a -> b@ +under :: Setting a b c d -> (c -> d) -> a -> b +under l f = runMutator . l (Mutator . f) +{-# INLINE under #-} -- | Modify the target of a 'Control.Lens.Type.Lens' or all the targets of a 'Setter' or 'Control.Lens.Traversal.Traversal' --- with a function. This is an alias for adjust that is provided for consistency. +-- with a function. This is an alias for 'under' that is provided for consistency. -- -- @ --- 'mapOf' = 'adjust' +-- 'mapOf' = 'under' -- 'fmap' = 'mapOf' 'mapped' -- 'fmapDefault' = 'mapOf' 'traverse' -- 'sets' . 'mapOf' = 'id' @@ -232,7 +232,7 @@ adjust l f = runMutator . l (Mutator . f) -- mapOf :: 'Control.Lens.Traversal.Traversal' a b c d -> (c -> d) -> a -> b -- @ mapOf :: Setting a b c d -> (c -> d) -> a -> b -mapOf = adjust +mapOf = under {-# INLINE mapOf #-} -- | Replace the target of a 'Control.Lens.Type.Lens' or all of the targets of a 'Setter' @@ -263,7 +263,7 @@ set l d = runMutator . l (\_ -> Mutator d) -- | Modifies the target of a 'Control.Lens.Type.Lens' or all of the targets of a 'Setter' or -- 'Control.Lens.Traversal.Traversal' with a user supplied function. -- --- This is an infix version of 'adjust' +-- This is an infix version of 'under' -- -- @ -- 'fmap' f = 'mapped' '%~' f @@ -281,7 +281,7 @@ set l d = runMutator . l (\_ -> Mutator d) -- (%~) :: 'Control.Lens.Traversal.Traversal' a b c d -> (c -> d) -> a -> b -- @ (%~) :: Setting a b c d -> (c -> d) -> a -> b -(%~) = adjust +(%~) = under {-# INLINE (%~) #-} -- | Replace the target of a 'Control.Lens.Type.Lens' or all of the targets of a 'Setter' @@ -334,7 +334,7 @@ l <.~ d = \a -> (d, l .~ d $ a) -- (+~) :: Num c => 'Control.Lens.Traversal.Traversal' a b c c -> c -> a -> b -- @ (+~) :: Num c => Setting a b c c -> c -> a -> b -l +~ n = adjust l (+ n) +l +~ n = under l (+ n) {-# INLINE (+~) #-} -- | Multiply the target(s) of a numerically valued 'Control.Lens.Type.Lens', 'Control.Lens.Iso.Iso', 'Setter' or 'Control.Lens.Traversal.Traversal' @@ -350,7 +350,7 @@ l +~ n = adjust l (+ n) -- (*~) :: 'Num' c => 'Control.Lens.Traversal.Traversal' a b c c -> c -> a -> b -- @ (*~) :: Num c => Setting a b c c -> c -> a -> b -l *~ n = adjust l (* n) +l *~ n = under l (* n) {-# INLINE (*~) #-} -- | Decrement the target(s) of a numerically valued 'Control.Lens.Type.Lens', 'Control.Lens.Iso.Iso', 'Setter' or 'Control.Lens.Traversal.Traversal' @@ -366,7 +366,7 @@ l *~ n = adjust l (* n) -- (-~) :: 'Num' c => 'Control.Lens.Traversal.Traversal' a b c c -> c -> a -> b -- @ (-~) :: Num c => Setting a b c c -> c -> a -> b -l -~ n = adjust l (subtract n) +l -~ n = under l (subtract n) {-# INLINE (-~) #-} -- | Divide the target(s) of a numerically valued 'Control.Lens.Type.Lens', 'Control.Lens.Iso.Iso', 'Setter' or 'Control.Lens.Traversal.Traversal' @@ -378,7 +378,7 @@ l -~ n = adjust l (subtract n) -- (//~) :: 'Fractional' c => 'Control.Lens.Traversal.Traversal' a b c c -> c -> a -> b -- @ (//~) :: Fractional c => Setting a b c c -> c -> a -> b -l //~ n = adjust l (/ n) +l //~ n = under l (/ n) -- | Raise the target(s) of a numerically valued 'Control.Lens.Type.Lens', 'Setter' or 'Control.Lens.Traversal.Traversal' to a non-negative integral power -- @@ -386,7 +386,7 @@ l //~ n = adjust l (/ n) -- >>> _2 ^~ 2 $ (1,3) -- (1,9) (^~) :: (Num c, Integral e) => Setting a b c c -> e -> a -> b -l ^~ n = adjust l (^ n) +l ^~ n = under l (^ n) {-# INLINE (^~) #-} -- | Raise the target(s) of a fractionally valued 'Control.Lens.Type.Lens', 'Setter' or 'Control.Lens.Traversal.Traversal' to an integral power @@ -403,7 +403,7 @@ l ^~ n = adjust l (^ n) -- @ -- (^^~) :: (Fractional c, Integral e) => Setting a b c c -> e -> a -> b -l ^^~ n = adjust l (^^ n) +l ^^~ n = under l (^^ n) {-# INLINE (^^~) #-} -- | Raise the target(s) of a floating-point valued 'Control.Lens.Type.Lens', 'Setter' or 'Control.Lens.Traversal.Traversal' to an arbitrary power. @@ -419,7 +419,7 @@ l ^^~ n = adjust l (^^ n) -- (**~) :: 'Floating' c => 'Control.Lens.Traversal.Traversal' a b c c -> c -> a -> b -- @ (**~) :: Floating c => Setting a b c c -> c -> a -> b -l **~ n = adjust l (** n) +l **~ n = under l (** n) {-# INLINE (**~) #-} -- | Logically '||' the target(s) of a 'Bool'-valued 'Control.Lens.Type.Lens' or 'Setter' @@ -439,7 +439,7 @@ l **~ n = adjust l (** n) -- (||~):: 'Control.Lens.Traversal.Traversal' a b 'Bool' 'Bool' -> 'Bool' -> a -> b -- @ (||~):: Setting a b Bool Bool -> Bool -> a -> b -l ||~ n = adjust l (|| n) +l ||~ n = under l (|| n) {-# INLINE (||~) #-} -- | Logically '&&' the target(s) of a 'Bool'-valued 'Control.Lens.Type.Lens' or 'Setter' @@ -459,7 +459,7 @@ l ||~ n = adjust l (|| n) -- (&&~):: 'Control.Lens.Traversal.Traversal' a b 'Bool' 'Bool' -> 'Bool' -> a -> b -- @ (&&~) :: Setting a b Bool Bool -> Bool -> a -> b -l &&~ n = adjust l (&& n) +l &&~ n = under l (&& n) {-# INLINE (&&~) #-} -- | Modify the target of a monoidally valued by 'mappend'ing another value. @@ -475,7 +475,7 @@ l &&~ n = adjust l (&& n) -- (<>~) :: 'Monoid' c => 'Control.Lens.Traversal.Traversal' a b c c -> c -> a -> b -- @ (<>~) :: Monoid c => Setting a b c c -> c -> a -> b -l <>~ n = adjust l (`mappend` n) +l <>~ n = under l (`mappend` n) {-# INLINE (<>~) #-} ------------------------------------------------------------------------------ diff --git a/src/Data/Array/Lens.hs b/src/Data/Array/Lens.hs index ec5a2d190..1061820ab 100644 --- a/src/Data/Array/Lens.hs +++ b/src/Data/Array/Lens.hs @@ -44,13 +44,13 @@ ix i f arr = (\e -> arr // [(i,e)]) <$> f (arr ! i) -- -- This is a /contravariant/ 'Setter'. -- --- @'ixmap' = 'adjust' . 'ixmapped'@ +-- @'ixmap' = 'under' . 'ixmapped'@ -- -- @'ixmapped' = 'sets' . 'ixmap'@ -- --- @'adjust' ('ixmapped' b) f arr '!' i = arr '!' f i@ +-- @'under' ('ixmapped' b) f arr '!' i = arr '!' f i@ -- --- @'bounds' ('adjust' ('ixmapped' b) f arr) = b@ +-- @'bounds' ('under' ('ixmapped' b) f arr) = b@ ixmapped :: (IArray a e, Ix i, Ix j) => (i,i) -> Setter (a j e) (a i e) i j ixmapped = sets . ixmap {-# INLINE ixmapped #-} @@ -58,7 +58,7 @@ ixmapped = sets . ixmap -- | An 'IndexedTraversal' of the elements of an 'IArray', using the -- index into the array as the index of the traversal. -- --- @'amap' = 'adjust' 'traverseArray'@ +-- @'amap' = 'under' 'traverseArray'@ traverseArray :: (IArray a c, IArray a d, Ix i) => IndexedTraversal i (a i c) (a i d) c d traverseArray = index $ \f arr -> array (bounds arr) <$> traverse (\(i,a) -> (,) i <$> f i a) (assocs arr) {-# INLINE traverseArray #-} diff --git a/src/Data/Bits/Lens.hs b/src/Data/Bits/Lens.hs index b3356599a..5a5384538 100644 --- a/src/Data/Bits/Lens.hs +++ b/src/Data/Bits/Lens.hs @@ -30,7 +30,7 @@ infix 4 |=, &= -- >>> _2 |~ 6 $ ("hello",3) -- ("hello",7) (|~):: Bits c => Setting a b c c -> c -> a -> b -l |~ n = adjust l (.|. n) +l |~ n = under l (.|. n) {-# INLINE (|~) #-} -- | Bitwise '.&.' the target(s) of a 'Bool'-valued 'Lens' or 'Setter' @@ -38,7 +38,7 @@ l |~ n = adjust l (.|. n) -- >>> _2 &~ 7 $ ("hello",254) -- ("hello",6) (&~) :: Bits c => Setting a b c c -> c -> a -> b -l &~ n = adjust l (.&. n) +l &~ n = under l (.&. n) {-# INLINE (&~) #-} -- | Modify the target(s) of a 'Simple' 'Lens', 'Setter' or 'Traversal' by computing its bitwise '.&.' with another value. diff --git a/src/Data/IntSet/Lens.hs b/src/Data/IntSet/Lens.hs index 9fd9d2abe..e8b64b610 100644 --- a/src/Data/IntSet/Lens.hs +++ b/src/Data/IntSet/Lens.hs @@ -45,7 +45,7 @@ members = folding IntSet.toAscList -- elements might change but you can manipulate it by reading using 'folded' and -- reindexing it via 'setmap'. -- --- >>> adjust setmapped (+1) (fromList [1,2,3,4]) +-- >>> under setmapped (+1) (fromList [1,2,3,4]) -- fromList [2,3,4,5] setmapped :: Simple Setter IntSet Int setmapped = sets IntSet.map diff --git a/src/Data/Set/Lens.hs b/src/Data/Set/Lens.hs index 889a51c77..a22e4b002 100644 --- a/src/Data/Set/Lens.hs +++ b/src/Data/Set/Lens.hs @@ -40,7 +40,7 @@ contains k f s = go <$> f (Set.member k s) where -- manipulate it by reading using 'folded' and reindexing it via 'setmap'. -- -- >>> :m + Data.Set.Lens Control.Lens --- >>> adjust setmapped (+1) (fromList [1,2,3,4]) +-- >>> under setmapped (+1) (fromList [1,2,3,4]) -- fromList [2,3,4,5] setmapped :: (Ord i, Ord j) => Setter (Set i) (Set j) i j setmapped = sets Set.map