module Lens.Family (
to, view, (^.)
, folding, views, (^..), (^?)
, toListOf, allOf, anyOf, firstOf, lastOf, sumOf, productOf
, lengthOf, nullOf
, matching
, over, (%~), set, (.~)
, review, zipWithOf, degrating
, under, reset
, (&)
, (+~), (*~), (-~), (//~), (&&~), (||~), (<>~)
, AdapterLike, AdapterLike'
, LensLike, LensLike'
, FoldLike, FoldLike'
, GrateLike, GrateLike'
, AGrate, AGrate'
, ASetter, ASetter'
, AResetter, AResetter'
, PCont
, First, Last
, Phantom
, Constant, Identity, Prod
, All, Any, Sum, Product
) where
import Data.Foldable (traverse_)
import Data.Functor.Constant (Constant(..))
import Data.Functor.Identity (Identity(..))
import qualified Data.Functor.Product
import Data.Monoid ( All(..), Any(..)
, Sum(..), Product(..)
)
import Lens.Family.Phantom
import Lens.Family.Unchecked
type Prod = Data.Functor.Product.Product
newtype PCont i j a = PCont ((a -> j) -> i)
instance Functor (PCont i j) where
fmap :: forall a b. (a -> b) -> PCont i j a -> PCont i j b
fmap a -> b
f (PCont (a -> j) -> i
h) = ((b -> j) -> i) -> PCont i j b
forall i j a. ((a -> j) -> i) -> PCont i j a
PCont (((b -> j) -> i) -> PCont i j b) -> ((b -> j) -> i) -> PCont i j b
forall a b. (a -> b) -> a -> b
$ \b -> j
k -> (a -> j) -> i
h (b -> j
k (b -> j) -> (a -> b) -> a -> j
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> b
f)
runPCont :: PCont i a a -> i
runPCont :: forall i a. PCont i a a -> i
runPCont (PCont (a -> a) -> i
h) = (a -> a) -> i
h a -> a
forall a. a -> a
id
type FoldLike r s t a b = LensLike (Constant r) s t a b
type FoldLike' r s a = LensLike' (Constant r) s a
type AGrate s t a b = GrateLike (PCont b a) s t a b
type AGrate' s a = GrateLike' (PCont a a) s a
type ASetter s t a b = LensLike Identity s t a b
type ASetter' s a = LensLike' Identity s a
type AResetter s t a b = GrateLike Identity s t a b
type AResetter' s a = GrateLike' Identity s a
to :: Phantom f => (s -> a) -> LensLike f s t a b
to :: forall (f :: * -> *) s a t b.
Phantom f =>
(s -> a) -> LensLike f s t a b
to s -> a
p a -> f b
f = f b -> f t
forall a b. f a -> f b
forall (f :: * -> *) a b. Phantom f => f a -> f b
coerce (f b -> f t) -> (s -> f b) -> s -> f t
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> f b
f (a -> f b) -> (s -> a) -> s -> f b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. s -> a
p
view :: FoldLike a s t a b -> s -> a
view :: forall a s t b. FoldLike a s t a b -> s -> a
view FoldLike a s t a b
l = (s -> FoldLike a s t a b -> a
forall s a t b. s -> FoldLike a s t a b -> a
^.FoldLike a s t a b
l)
folding :: (Foldable g, Phantom f, Applicative f) => (s -> g a) -> LensLike f s t a b
folding :: forall (g :: * -> *) (f :: * -> *) s a t b.
(Foldable g, Phantom f, Applicative f) =>
(s -> g a) -> LensLike f s t a b
folding s -> g a
p a -> f b
f = f () -> f t
forall a b. f a -> f b
forall (f :: * -> *) a b. Phantom f => f a -> f b
coerce (f () -> f t) -> (s -> f ()) -> s -> f t
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> f b) -> g a -> f ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
(a -> f b) -> t a -> f ()
traverse_ a -> f b
f (g a -> f ()) -> (s -> g a) -> s -> f ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. s -> g a
p
views :: FoldLike r s t a b -> (a -> r) -> s -> r
views :: forall r s t a b. FoldLike r s t a b -> (a -> r) -> s -> r
views FoldLike r s t a b
l a -> r
f = Constant r t -> r
forall {k} a (b :: k). Constant a b -> a
getConstant (Constant r t -> r) -> (s -> Constant r t) -> s -> r
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FoldLike r s t a b
l (r -> Constant r b
forall {k} a (b :: k). a -> Constant a b
Constant (r -> Constant r b) -> (a -> r) -> a -> Constant r b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> r
f)
toListOf :: FoldLike [a] s t a b -> s -> [a]
toListOf :: forall a s t b. FoldLike [a] s t a b -> s -> [a]
toListOf FoldLike [a] s t a b
l = FoldLike [a] s t a b -> (a -> [a]) -> s -> [a]
forall r s t a b. FoldLike r s t a b -> (a -> r) -> s -> r
views FoldLike [a] s t a b
l (a -> [a] -> [a]
forall a. a -> [a] -> [a]
:[])
allOf :: FoldLike All s t a b -> (a -> Bool) -> s -> Bool
allOf :: forall s t a b. FoldLike All s t a b -> (a -> Bool) -> s -> Bool
allOf FoldLike All s t a b
l a -> Bool
p = All -> Bool
getAll (All -> Bool) -> (s -> All) -> s -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FoldLike All s t a b -> (a -> All) -> s -> All
forall r s t a b. FoldLike r s t a b -> (a -> r) -> s -> r
views FoldLike All s t a b
l (Bool -> All
All (Bool -> All) -> (a -> Bool) -> a -> All
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Bool
p)
anyOf :: FoldLike Any s t a b -> (a -> Bool) -> s -> Bool
anyOf :: forall s t a b. FoldLike Any s t a b -> (a -> Bool) -> s -> Bool
anyOf FoldLike Any s t a b
l a -> Bool
p = Any -> Bool
getAny (Any -> Bool) -> (s -> Any) -> s -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FoldLike Any s t a b -> (a -> Any) -> s -> Any
forall r s t a b. FoldLike r s t a b -> (a -> r) -> s -> r
views FoldLike Any s t a b
l (Bool -> Any
Any (Bool -> Any) -> (a -> Bool) -> a -> Any
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Bool
p)
firstOf :: FoldLike (First a) s t a b -> s -> Maybe a
firstOf :: forall a s t b. FoldLike (First a) s t a b -> s -> Maybe a
firstOf FoldLike (First a) s t a b
l = First a -> Maybe a
forall a. First a -> Maybe a
getFirst (First a -> Maybe a) -> (s -> First a) -> s -> Maybe a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FoldLike (First a) s t a b -> (a -> First a) -> s -> First a
forall r s t a b. FoldLike r s t a b -> (a -> r) -> s -> r
views FoldLike (First a) s t a b
l (Maybe a -> First a
forall a. Maybe a -> First a
First (Maybe a -> First a) -> (a -> Maybe a) -> a -> First a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Maybe a
forall a. a -> Maybe a
Just)
lastOf :: FoldLike (Last a) s t a b -> s -> Maybe a
lastOf :: forall a s t b. FoldLike (Last a) s t a b -> s -> Maybe a
lastOf FoldLike (Last a) s t a b
l = Last a -> Maybe a
forall a. Last a -> Maybe a
getLast (Last a -> Maybe a) -> (s -> Last a) -> s -> Maybe a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FoldLike (Last a) s t a b -> (a -> Last a) -> s -> Last a
forall r s t a b. FoldLike r s t a b -> (a -> r) -> s -> r
views FoldLike (Last a) s t a b
l (Maybe a -> Last a
forall a. Maybe a -> Last a
Last (Maybe a -> Last a) -> (a -> Maybe a) -> a -> Last a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Maybe a
forall a. a -> Maybe a
Just)
sumOf :: Num a => FoldLike (Sum a) s t a b -> s -> a
sumOf :: forall a s t b. Num a => FoldLike (Sum a) s t a b -> s -> a
sumOf FoldLike (Sum a) s t a b
l = Sum a -> a
forall a. Sum a -> a
getSum (Sum a -> a) -> (s -> Sum a) -> s -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FoldLike (Sum a) s t a b -> (a -> Sum a) -> s -> Sum a
forall r s t a b. FoldLike r s t a b -> (a -> r) -> s -> r
views FoldLike (Sum a) s t a b
l a -> Sum a
forall a. a -> Sum a
Sum
productOf :: Num a => FoldLike (Product a) s t a b -> s -> a
productOf :: forall a s t b. Num a => FoldLike (Product a) s t a b -> s -> a
productOf FoldLike (Product a) s t a b
l = Product a -> a
forall a. Product a -> a
getProduct (Product a -> a) -> (s -> Product a) -> s -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FoldLike (Product a) s t a b -> (a -> Product a) -> s -> Product a
forall r s t a b. FoldLike r s t a b -> (a -> r) -> s -> r
views FoldLike (Product a) s t a b
l a -> Product a
forall a. a -> Product a
Product
lengthOf :: Num r => FoldLike (Sum r) s t a b -> s -> r
lengthOf :: forall r s t a b. Num r => FoldLike (Sum r) s t a b -> s -> r
lengthOf FoldLike (Sum r) s t a b
l = Sum r -> r
forall a. Sum a -> a
getSum (Sum r -> r) -> (s -> Sum r) -> s -> r
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FoldLike (Sum r) s t a b -> (a -> Sum r) -> s -> Sum r
forall r s t a b. FoldLike r s t a b -> (a -> r) -> s -> r
views FoldLike (Sum r) s t a b
l (Sum r -> a -> Sum r
forall a b. a -> b -> a
const (r -> Sum r
forall a. a -> Sum a
Sum r
1))
nullOf :: FoldLike All s t a b -> s -> Bool
nullOf :: forall s t a b. FoldLike All s t a b -> s -> Bool
nullOf FoldLike All s t a b
l = FoldLike All s t a b -> (a -> Bool) -> s -> Bool
forall s t a b. FoldLike All s t a b -> (a -> Bool) -> s -> Bool
allOf FoldLike All s t a b
l (Bool -> a -> Bool
forall a b. a -> b -> a
const Bool
False)
infixl 8 ^.
(^.) :: s -> FoldLike a s t a b -> a
s
s^. :: forall s a t b. s -> FoldLike a s t a b -> a
^.FoldLike a s t a b
l = Constant a t -> a
forall {k} a (b :: k). Constant a b -> a
getConstant (Constant a t -> a) -> Constant a t -> a
forall a b. (a -> b) -> a -> b
$ FoldLike a s t a b
l a -> Constant a b
forall {k} a (b :: k). a -> Constant a b
Constant s
s
infixl 8 ^..
(^..) :: s -> FoldLike [a] s t a b -> [a]
s
s^.. :: forall s a t b. s -> FoldLike [a] s t a b -> [a]
^..FoldLike [a] s t a b
l = FoldLike [a] s t a b -> s -> [a]
forall a s t b. FoldLike [a] s t a b -> s -> [a]
toListOf FoldLike [a] s t a b
l s
s
infixl 8 ^?
(^?) :: s -> FoldLike (First a) s t a b -> Maybe a
s
s^? :: forall s a t b. s -> FoldLike (First a) s t a b -> Maybe a
^?FoldLike (First a) s t a b
l = FoldLike (First a) s t a b -> s -> Maybe a
forall a s t b. FoldLike (First a) s t a b -> s -> Maybe a
firstOf FoldLike (First a) s t a b
l s
s
matching :: LensLike (Either a) s t a b -> s -> Either t a
matching :: forall a s t b. LensLike (Either a) s t a b -> s -> Either t a
matching LensLike (Either a) s t a b
l = (a -> Either t a) -> (t -> Either t a) -> Either a t -> Either t a
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either a -> Either t a
forall a b. b -> Either a b
Right t -> Either t a
forall a b. a -> Either a b
Left (Either a t -> Either t a) -> (s -> Either a t) -> s -> Either t a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LensLike (Either a) s t a b
l a -> Either a b
forall a b. a -> Either a b
Left
review :: GrateLike (Constant ()) s t a b -> b -> t
review :: forall s t a b. GrateLike (Constant ()) s t a b -> b -> t
review GrateLike (Constant ()) s t a b
l b
b = GrateLike (Constant ()) s t a b
l (b -> Constant () a -> b
forall a b. a -> b -> a
const b
b) (() -> Constant () s
forall {k} a (b :: k). a -> Constant a b
Constant ())
zipWithOf :: GrateLike (Prod Identity Identity) s t a b -> (a -> a -> b) -> s -> s -> t
zipWithOf :: forall s t a b.
GrateLike (Prod Identity Identity) s t a b
-> (a -> a -> b) -> s -> s -> t
zipWithOf GrateLike (Prod Identity Identity) s t a b
l a -> a -> b
f s
s1 s
s2 = GrateLike (Prod Identity Identity) s t a b
l (\(Data.Functor.Product.Pair (Identity a
a1) (Identity a
a2)) -> a -> a -> b
f a
a1 a
a2)
(Identity s -> Identity s -> Product Identity Identity s
forall {k} (f :: k -> *) (g :: k -> *) (a :: k).
f a -> g a -> Product f g a
Data.Functor.Product.Pair (s -> Identity s
forall a. a -> Identity a
Identity s
s1) (s -> Identity s
forall a. a -> Identity a
Identity s
s2))
degrating :: AGrate s t a b -> ((s -> a) -> b) -> t
degrating :: forall s t a b. AGrate s t a b -> ((s -> a) -> b) -> t
degrating AGrate s t a b
l = AGrate s t a b
l PCont b a a -> b
forall i a. PCont i a a -> i
runPCont (PCont b a s -> t)
-> (((s -> a) -> b) -> PCont b a s) -> ((s -> a) -> b) -> t
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((s -> a) -> b) -> PCont b a s
forall i j a. ((a -> j) -> i) -> PCont i j a
PCont
under :: AResetter s t a b -> (a -> b) -> s -> t
under :: forall s t a b. AResetter s t a b -> (a -> b) -> s -> t
under AResetter s t a b
l a -> b
f = AResetter s t a b
l (a -> b
f (a -> b) -> (Identity a -> a) -> Identity a -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Identity a -> a
forall a. Identity a -> a
runIdentity) (Identity s -> t) -> (s -> Identity s) -> s -> t
forall b c a. (b -> c) -> (a -> b) -> a -> c
. s -> Identity s
forall a. a -> Identity a
Identity
reset :: AResetter s t a b -> b -> s -> t
reset :: forall s t a b. AResetter s t a b -> b -> s -> t
reset AResetter s t a b
l b
b = AResetter s t a b -> (a -> b) -> s -> t
forall s t a b. AResetter s t a b -> (a -> b) -> s -> t
under AResetter s t a b
l (b -> a -> b
forall a b. a -> b -> a
const b
b)
over :: ASetter s t a b -> (a -> b) -> s -> t
over :: forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over ASetter s t a b
l = (ASetter s t a b
l ASetter s t a b -> (a -> b) -> s -> t
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~)
infixr 4 %~
(%~) :: ASetter s t a b -> (a -> b) -> s -> t
ASetter s t a b
l %~ :: forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ a -> b
f = Identity t -> t
forall a. Identity a -> a
runIdentity (Identity t -> t) -> (s -> Identity t) -> s -> t
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ASetter s t a b
l (b -> Identity b
forall a. a -> Identity a
Identity (b -> Identity b) -> (a -> b) -> a -> Identity b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> b
f)
infixr 4 .~
(.~) :: ASetter s t a b -> b -> s -> t
ASetter s t a b
l .~ :: forall s t a b. ASetter s t a b -> b -> s -> t
.~ b
b = ASetter s t a b
l ASetter s t a b -> (a -> b) -> s -> t
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ b -> a -> b
forall a b. a -> b -> a
const b
b
set :: ASetter s t a b -> b -> s -> t
set :: forall s t a b. ASetter s t a b -> b -> s -> t
set = ASetter s t a b -> b -> s -> t
forall s t a b. ASetter s t a b -> b -> s -> t
(.~)
infixl 1 &
(&) :: s -> (s -> t) -> t
& :: forall s t. s -> (s -> t) -> t
(&) = ((s -> t) -> s -> t) -> s -> (s -> t) -> t
forall a b c. (a -> b -> c) -> b -> a -> c
flip (s -> t) -> s -> t
forall a b. (a -> b) -> a -> b
($)
infixr 4 +~, -~, *~
(+~), (-~), (*~) :: Num a => ASetter s t a a -> a -> s -> t
ASetter s t a a
l +~ :: forall a s t. Num a => ASetter s t a a -> a -> s -> t
+~ a
a = ASetter s t a a
l ASetter s t a a -> (a -> a) -> s -> t
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ (a -> a -> a
forall a. Num a => a -> a -> a
+ a
a)
ASetter s t a a
l -~ :: forall a s t. Num a => ASetter s t a a -> a -> s -> t
-~ a
a = ASetter s t a a
l ASetter s t a a -> (a -> a) -> s -> t
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ a -> a -> a
forall a. Num a => a -> a -> a
subtract a
a
ASetter s t a a
l *~ :: forall a s t. Num a => ASetter s t a a -> a -> s -> t
*~ a
a = ASetter s t a a
l ASetter s t a a -> (a -> a) -> s -> t
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ (a -> a -> a
forall a. Num a => a -> a -> a
* a
a)
infixr 4 //~
(//~) :: Fractional a => ASetter s t a a -> a -> s -> t
ASetter s t a a
l //~ :: forall a s t. Fractional a => ASetter s t a a -> a -> s -> t
//~ a
a = ASetter s t a a
l ASetter s t a a -> (a -> a) -> s -> t
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ (a -> a -> a
forall a. Fractional a => a -> a -> a
/ a
a)
infixr 4 &&~, ||~
(&&~), (||~) :: ASetter s t Bool Bool -> Bool -> s -> t
ASetter s t Bool Bool
l &&~ :: forall s t. ASetter s t Bool Bool -> Bool -> s -> t
&&~ Bool
a = ASetter s t Bool Bool
l ASetter s t Bool Bool -> (Bool -> Bool) -> s -> t
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ (Bool -> Bool -> Bool
&& Bool
a)
ASetter s t Bool Bool
l ||~ :: forall s t. ASetter s t Bool Bool -> Bool -> s -> t
||~ Bool
a = ASetter s t Bool Bool
l ASetter s t Bool Bool -> (Bool -> Bool) -> s -> t
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ (Bool -> Bool -> Bool
|| Bool
a)
infixr 4 <>~
(<>~) :: (Monoid a) => ASetter s t a a -> a -> s -> t
ASetter s t a a
l <>~ :: forall a s t. Monoid a => ASetter s t a a -> a -> s -> t
<>~ a
a = ASetter s t a a
l ASetter s t a a -> (a -> a) -> s -> t
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ (a -> a -> a
forall a. Semigroup a => a -> a -> a
<> a
a)
newtype First a = First { forall a. First a -> Maybe a
getFirst :: Maybe a }
newtype Last a = Last { forall a. Last a -> Maybe a
getLast :: Maybe a }
instance Monoid (First a) where
mempty :: First a
mempty = Maybe a -> First a
forall a. Maybe a -> First a
First Maybe a
forall a. Maybe a
Nothing
(First Maybe a
Nothing) mappend :: First a -> First a -> First a
`mappend` First a
b = First a
b
First a
a `mappend` First a
_ = First a
a
instance Monoid (Last a) where
mempty :: Last a
mempty = Maybe a -> Last a
forall a. Maybe a -> Last a
Last Maybe a
forall a. Maybe a
Nothing
Last a
a mappend :: Last a -> Last a -> Last a
`mappend` (Last Maybe a
Nothing) = Last a
a
Last a
_ `mappend` Last a
b = Last a
b
instance Semigroup (First a) where
<> :: First a -> First a -> First a
(<>) = First a -> First a -> First a
forall a. Monoid a => a -> a -> a
mappend
instance Semigroup (Last a) where
<> :: Last a -> Last a -> Last a
(<>) = Last a -> Last a -> Last a
forall a. Monoid a => a -> a -> a
mappend