lens-4.13.2.1: Lenses, Folds and Traversals

Copyright(C) 2012-2016 Edward Kmett
LicenseBSD-style (see the file LICENSE)
MaintainerEdward Kmett <ekmett@gmail.com>
Stabilityprovisional
Portabilitynon-portable
Safe HaskellSafe
LanguageHaskell98

Control.Lens.Internal.Getter

Description

 

Synopsis

Documentation

newtype AlongsideLeft f b a Source

Constructors

AlongsideLeft 

Fields

Instances

Functor f => Bifunctor (AlongsideLeft f) Source 

Methods

bimap :: (a -> b) -> (c -> d) -> AlongsideLeft f a c -> AlongsideLeft f b d

first :: (a -> b) -> AlongsideLeft f a c -> AlongsideLeft f b c

second :: (b -> c) -> AlongsideLeft f a b -> AlongsideLeft f a c

Traversable f => Bitraversable (AlongsideLeft f) Source 

Methods

bitraverse :: Applicative b => (a -> b c) -> (d -> b e) -> AlongsideLeft f a d -> b (AlongsideLeft f c e)

Foldable f => Bifoldable (AlongsideLeft f) Source 

Methods

bifold :: Monoid m => AlongsideLeft f m m -> m

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> AlongsideLeft f a b -> m

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> AlongsideLeft f a b -> c

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> AlongsideLeft f a b -> c

Functor f => Functor (AlongsideLeft f b) Source 

Methods

fmap :: (a -> c) -> AlongsideLeft f b a -> AlongsideLeft f b c

(<$) :: a -> AlongsideLeft f b c -> AlongsideLeft f b a

Foldable f => Foldable (AlongsideLeft f b) Source 

Methods

fold :: Monoid m => AlongsideLeft f b m -> m

foldMap :: Monoid m => (a -> m) -> AlongsideLeft f b a -> m

foldr :: (a -> c -> c) -> c -> AlongsideLeft f b a -> c

foldr' :: (a -> c -> c) -> c -> AlongsideLeft f b a -> c

foldl :: (a -> c -> a) -> a -> AlongsideLeft f b c -> a

foldl' :: (a -> c -> a) -> a -> AlongsideLeft f b c -> a

foldr1 :: (a -> a -> a) -> AlongsideLeft f b a -> a

foldl1 :: (a -> a -> a) -> AlongsideLeft f b a -> a

toList :: AlongsideLeft f b a -> [a]

null :: AlongsideLeft f b a -> Bool

length :: AlongsideLeft f b a -> Int

elem :: Eq a => a -> AlongsideLeft f b a -> Bool

maximum :: Ord a => AlongsideLeft f b a -> a

minimum :: Ord a => AlongsideLeft f b a -> a

sum :: Num a => AlongsideLeft f b a -> a

product :: Num a => AlongsideLeft f b a -> a

Traversable f => Traversable (AlongsideLeft f b) Source 

Methods

traverse :: Applicative c => (a -> c d) -> AlongsideLeft f b a -> c (AlongsideLeft f b d)

sequenceA :: Applicative a => AlongsideLeft f b (a c) -> a (AlongsideLeft f b c)

mapM :: Monad m => (a -> m c) -> AlongsideLeft f b a -> m (AlongsideLeft f b c)

sequence :: Monad m => AlongsideLeft f b (m a) -> m (AlongsideLeft f b a)

Contravariant f => Contravariant (AlongsideLeft f b) Source 

Methods

contramap :: (a -> c) -> AlongsideLeft f b c -> AlongsideLeft f b a

(>$) :: a -> AlongsideLeft f b a -> AlongsideLeft f b c

Traversable1 f => Traversable1 (AlongsideLeft f b) Source 

Methods

traverse1 :: Apply c => (a -> c d) -> AlongsideLeft f b a -> c (AlongsideLeft f b d)

sequence1 :: Apply a => AlongsideLeft f b (a c) -> a (AlongsideLeft f b c)

Foldable1 f => Foldable1 (AlongsideLeft f b) Source 

Methods

fold1 :: Semigroup m => AlongsideLeft f b m -> m

foldMap1 :: Semigroup m => (a -> m) -> AlongsideLeft f b a -> m

Read (f (a, b)) => Read (AlongsideLeft f b a) Source 
Show (f (a, b)) => Show (AlongsideLeft f b a) Source 

Methods

showsPrec :: Int -> AlongsideLeft f b a -> ShowS

show :: AlongsideLeft f b a -> String

showList :: [AlongsideLeft f b a] -> ShowS

newtype AlongsideRight f a b Source

Constructors

AlongsideRight 

Fields

Instances

Functor f => Bifunctor (AlongsideRight f) Source 

Methods

bimap :: (a -> b) -> (c -> d) -> AlongsideRight f a c -> AlongsideRight f b d

first :: (a -> b) -> AlongsideRight f a c -> AlongsideRight f b c

second :: (b -> c) -> AlongsideRight f a b -> AlongsideRight f a c

Traversable f => Bitraversable (AlongsideRight f) Source 

Methods

bitraverse :: Applicative b => (a -> b c) -> (d -> b e) -> AlongsideRight f a d -> b (AlongsideRight f c e)

Foldable f => Bifoldable (AlongsideRight f) Source 

Methods

bifold :: Monoid m => AlongsideRight f m m -> m

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> AlongsideRight f a b -> m

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> AlongsideRight f a b -> c

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> AlongsideRight f a b -> c

Functor f => Functor (AlongsideRight f a) Source 

Methods

fmap :: (b -> c) -> AlongsideRight f a b -> AlongsideRight f a c

(<$) :: b -> AlongsideRight f a c -> AlongsideRight f a b

Foldable f => Foldable (AlongsideRight f a) Source 

Methods

fold :: Monoid m => AlongsideRight f a m -> m

foldMap :: Monoid m => (b -> m) -> AlongsideRight f a b -> m

foldr :: (b -> c -> c) -> c -> AlongsideRight f a b -> c

foldr' :: (b -> c -> c) -> c -> AlongsideRight f a b -> c

foldl :: (b -> c -> b) -> b -> AlongsideRight f a c -> b

foldl' :: (b -> c -> b) -> b -> AlongsideRight f a c -> b

foldr1 :: (b -> b -> b) -> AlongsideRight f a b -> b

foldl1 :: (b -> b -> b) -> AlongsideRight f a b -> b

toList :: AlongsideRight f a b -> [b]

null :: AlongsideRight f a b -> Bool

length :: AlongsideRight f a b -> Int

elem :: Eq b => b -> AlongsideRight f a b -> Bool

maximum :: Ord b => AlongsideRight f a b -> b

minimum :: Ord b => AlongsideRight f a b -> b

sum :: Num b => AlongsideRight f a b -> b

product :: Num b => AlongsideRight f a b -> b

Traversable f => Traversable (AlongsideRight f a) Source 

Methods

traverse :: Applicative c => (b -> c d) -> AlongsideRight f a b -> c (AlongsideRight f a d)

sequenceA :: Applicative b => AlongsideRight f a (b c) -> b (AlongsideRight f a c)

mapM :: Monad m => (b -> m c) -> AlongsideRight f a b -> m (AlongsideRight f a c)

sequence :: Monad m => AlongsideRight f a (m b) -> m (AlongsideRight f a b)

Contravariant f => Contravariant (AlongsideRight f a) Source 

Methods

contramap :: (b -> c) -> AlongsideRight f a c -> AlongsideRight f a b

(>$) :: b -> AlongsideRight f a b -> AlongsideRight f a c

Traversable1 f => Traversable1 (AlongsideRight f a) Source 

Methods

traverse1 :: Apply c => (b -> c d) -> AlongsideRight f a b -> c (AlongsideRight f a d)

sequence1 :: Apply b => AlongsideRight f a (b c) -> b (AlongsideRight f a c)

Foldable1 f => Foldable1 (AlongsideRight f a) Source 

Methods

fold1 :: Semigroup m => AlongsideRight f a m -> m

foldMap1 :: Semigroup m => (b -> m) -> AlongsideRight f a b -> m

Read (f (a, b)) => Read (AlongsideRight f a b) Source 
Show (f (a, b)) => Show (AlongsideRight f a b) Source 

Methods

showsPrec :: Int -> AlongsideRight f a b -> ShowS

show :: AlongsideRight f a b -> String

showList :: [AlongsideRight f a b] -> ShowS