lens-labels-0.2.0.1: Integration of lenses with OverloadedLabels.

Safe HaskellNone
LanguageHaskell2010

Lens.Labels

Contents

Description

A lens library that integrates with OverloadedLabels.

Unlike the lens package (and others), lenses are defined as a newtype instead of a type synonym, to avoid overlapping with other IsLabel instances. However, the LensFn and runLens functions allow converting between the two types; for example:

LensFn :: Control.Lens.LensLike f s t a b -> Lens.Labels.LensLike f s t a b
runLens :: Lens.Labels.LensLike f s t a b -> Control.Lens.LensLike f s t a b

TODO: support more general optic types (e.g., prisms).

Synopsis

Lenses

newtype LensFn a b Source #

A newtype for defining lenses. Can be composed using '(Control.Category..)', which is exported from this module.

Constructors

LensFn 

Fields

Instances

((~) * p (a -> f b), (~) * q (s -> f t), HasLens f s t x a b) => IsLabel x (LensFn p q) Source # 

Methods

fromLabel :: LensFn p q #

Category * LensFn Source # 

Methods

id :: cat a a #

(.) :: cat b c -> cat a b -> cat a c #

type LensLike f s t a b = LensFn (a -> f b) (s -> f t) Source #

type LensLike' f s a = LensLike f s s a a Source #

(&) :: a -> (a -> b) -> b infixl 1 #

& is a reverse application operator. This provides notational convenience. Its precedence is one higher than that of the forward application operator $, which allows & to be nested in $.

Since: 4.8.0.0

(.) :: Category k cat => forall (b :: k) (c :: k) (a :: k). cat b c -> cat a b -> cat a c infixr 9 #

morphism composition

type Lens s t a b = forall f. Functor f => LensLike f s t a b Source #

type Lens' s a = Lens s s a a Source #

HasLens

class HasLens f s t (x :: Symbol) a b | x s -> a, x t -> b, x s b -> t, x t a -> s where Source #

A type class for lens fields.

Minimal complete definition

lensOf

Methods

lensOf :: Proxy# x -> (a -> f b) -> s -> f t Source #

data Proxy# :: forall k0. k0 -> TYPE (TupleRep ([] RuntimeRep)) #

The type constructor Proxy# is used to bear witness to some type variable. It's used when you want to pass around proxy values for doing things like modelling type applications. A Proxy# is not only unboxed, it also has a polymorphic kind, and has no runtime representation, being totally free.

proxy# :: Proxy# k0 a #

Witness for an unboxed Proxy# value, which has no runtime representation.

class HasLens f s s x a a => HasLens' f s x a | x s -> a where Source #

A type class for lens fields of monomorphic types (i.e., where the lens doesn't change the outer type).

This class can be used to simplify instance declarations and type errors, by "forwarding" HasLens to simpler instances. For example:

    instance (HasLens' f Foo x a, a ~ b) => HasLens f Foo Foo x a b where
        where lensOf = lensOf'
    instance Functor f => HasLens' f Foo "a" Int where ...
    instance Functor f => HasLens' f Foo "b" Double where ...
    instance Functor f => HasLens' f Foo "c" [Float]  where ...
    ...

Minimal complete definition

lensOf'

Methods

lensOf' :: Proxy# x -> (a -> f a) -> s -> f s Source #

Setters

type ASetter s t a b = LensLike Identity s t a b Source #

(.~) :: ASetter s t a b -> b -> s -> t infixr 4 Source #

(%~) :: ASetter s t a b -> (a -> b) -> s -> t infixr 4 Source #

set :: ASetter s t a b -> b -> s -> t Source #

over :: ASetter s t a b -> (a -> b) -> s -> t Source #

Getters

newtype Const k a (b :: k) :: forall k. * -> k -> * #

The Const functor.

Constructors

Const 

Fields

Instances

Generic1 k (Const k a) 

Associated Types

type Rep1 (Const k a) (f :: Const k a -> *) :: k -> * #

Methods

from1 :: f a -> Rep1 (Const k a) f a #

to1 :: Rep1 (Const k a) f a -> f a #

Functor (Const * m)

Since: 2.1

Methods

fmap :: (a -> b) -> Const * m a -> Const * m b #

(<$) :: a -> Const * m b -> Const * m a #

Monoid m => Applicative (Const * m)

Since: 2.0.1

Methods

pure :: a -> Const * m a #

(<*>) :: Const * m (a -> b) -> Const * m a -> Const * m b #

liftA2 :: (a -> b -> c) -> Const * m a -> Const * m b -> Const * m c #

(*>) :: Const * m a -> Const * m b -> Const * m b #

(<*) :: Const * m a -> Const * m b -> Const * m a #

Foldable (Const * m)

Since: 4.7.0.0

Methods

fold :: Monoid m => Const * m m -> m #

foldMap :: Monoid m => (a -> m) -> Const * m a -> m #

foldr :: (a -> b -> b) -> b -> Const * m a -> b #

foldr' :: (a -> b -> b) -> b -> Const * m a -> b #

foldl :: (b -> a -> b) -> b -> Const * m a -> b #

foldl' :: (b -> a -> b) -> b -> Const * m a -> b #

foldr1 :: (a -> a -> a) -> Const * m a -> a #

foldl1 :: (a -> a -> a) -> Const * m a -> a #

toList :: Const * m a -> [a] #

null :: Const * m a -> Bool #

length :: Const * m a -> Int #

elem :: Eq a => a -> Const * m a -> Bool #

maximum :: Ord a => Const * m a -> a #

minimum :: Ord a => Const * m a -> a #

sum :: Num a => Const * m a -> a #

product :: Num a => Const * m a -> a #

Traversable (Const * m)

Since: 4.7.0.0

Methods

traverse :: Applicative f => (a -> f b) -> Const * m a -> f (Const * m b) #

sequenceA :: Applicative f => Const * m (f a) -> f (Const * m a) #

mapM :: Monad m => (a -> m b) -> Const * m a -> m (Const * m b) #

sequence :: Monad m => Const * m (m a) -> m (Const * m a) #

Bounded a => Bounded (Const k a b) 

Methods

minBound :: Const k a b #

maxBound :: Const k a b #

Enum a => Enum (Const k a b) 

Methods

succ :: Const k a b -> Const k a b #

pred :: Const k a b -> Const k a b #

toEnum :: Int -> Const k a b #

fromEnum :: Const k a b -> Int #

enumFrom :: Const k a b -> [Const k a b] #

enumFromThen :: Const k a b -> Const k a b -> [Const k a b] #

enumFromTo :: Const k a b -> Const k a b -> [Const k a b] #

enumFromThenTo :: Const k a b -> Const k a b -> Const k a b -> [Const k a b] #

Eq a => Eq (Const k a b) 

Methods

(==) :: Const k a b -> Const k a b -> Bool #

(/=) :: Const k a b -> Const k a b -> Bool #

Floating a => Floating (Const k a b) 

Methods

pi :: Const k a b #

exp :: Const k a b -> Const k a b #

log :: Const k a b -> Const k a b #

sqrt :: Const k a b -> Const k a b #

(**) :: Const k a b -> Const k a b -> Const k a b #

logBase :: Const k a b -> Const k a b -> Const k a b #

sin :: Const k a b -> Const k a b #

cos :: Const k a b -> Const k a b #

tan :: Const k a b -> Const k a b #

asin :: Const k a b -> Const k a b #

acos :: Const k a b -> Const k a b #

atan :: Const k a b -> Const k a b #

sinh :: Const k a b -> Const k a b #

cosh :: Const k a b -> Const k a b #

tanh :: Const k a b -> Const k a b #

asinh :: Const k a b -> Const k a b #

acosh :: Const k a b -> Const k a b #

atanh :: Const k a b -> Const k a b #

log1p :: Const k a b -> Const k a b #

expm1 :: Const k a b -> Const k a b #

log1pexp :: Const k a b -> Const k a b #

log1mexp :: Const k a b -> Const k a b #

Fractional a => Fractional (Const k a b) 

Methods

(/) :: Const k a b -> Const k a b -> Const k a b #

recip :: Const k a b -> Const k a b #

fromRational :: Rational -> Const k a b #

Integral a => Integral (Const k a b) 

Methods

quot :: Const k a b -> Const k a b -> Const k a b #

rem :: Const k a b -> Const k a b -> Const k a b #

div :: Const k a b -> Const k a b -> Const k a b #

mod :: Const k a b -> Const k a b -> Const k a b #

quotRem :: Const k a b -> Const k a b -> (Const k a b, Const k a b) #

divMod :: Const k a b -> Const k a b -> (Const k a b, Const k a b) #

toInteger :: Const k a b -> Integer #

Num a => Num (Const k a b) 

Methods

(+) :: Const k a b -> Const k a b -> Const k a b #

(-) :: Const k a b -> Const k a b -> Const k a b #

(*) :: Const k a b -> Const k a b -> Const k a b #

negate :: Const k a b -> Const k a b #

abs :: Const k a b -> Const k a b #

signum :: Const k a b -> Const k a b #

fromInteger :: Integer -> Const k a b #

Ord a => Ord (Const k a b) 

Methods

compare :: Const k a b -> Const k a b -> Ordering #

(<) :: Const k a b -> Const k a b -> Bool #

(<=) :: Const k a b -> Const k a b -> Bool #

(>) :: Const k a b -> Const k a b -> Bool #

(>=) :: Const k a b -> Const k a b -> Bool #

max :: Const k a b -> Const k a b -> Const k a b #

min :: Const k a b -> Const k a b -> Const k a b #

Read a => Read (Const k a b)

This instance would be equivalent to the derived instances of the Const newtype if the runConst field were removed

Since: 4.8.0.0

Methods

readsPrec :: Int -> ReadS (Const k a b) #

readList :: ReadS [Const k a b] #

readPrec :: ReadPrec (Const k a b) #

readListPrec :: ReadPrec [Const k a b] #

Real a => Real (Const k a b) 

Methods

toRational :: Const k a b -> Rational #

RealFloat a => RealFloat (Const k a b) 

Methods

floatRadix :: Const k a b -> Integer #

floatDigits :: Const k a b -> Int #

floatRange :: Const k a b -> (Int, Int) #

decodeFloat :: Const k a b -> (Integer, Int) #

encodeFloat :: Integer -> Int -> Const k a b #

exponent :: Const k a b -> Int #

significand :: Const k a b -> Const k a b #

scaleFloat :: Int -> Const k a b -> Const k a b #

isNaN :: Const k a b -> Bool #

isInfinite :: Const k a b -> Bool #

isDenormalized :: Const k a b -> Bool #

isNegativeZero :: Const k a b -> Bool #

isIEEE :: Const k a b -> Bool #

atan2 :: Const k a b -> Const k a b -> Const k a b #

RealFrac a => RealFrac (Const k a b) 

Methods

properFraction :: Integral b => Const k a b -> (b, Const k a b) #

truncate :: Integral b => Const k a b -> b #

round :: Integral b => Const k a b -> b #

ceiling :: Integral b => Const k a b -> b #

floor :: Integral b => Const k a b -> b #

Show a => Show (Const k a b)

This instance would be equivalent to the derived instances of the Const newtype if the runConst field were removed

Since: 4.8.0.0

Methods

showsPrec :: Int -> Const k a b -> ShowS #

show :: Const k a b -> String #

showList :: [Const k a b] -> ShowS #

Ix a => Ix (Const k a b) 

Methods

range :: (Const k a b, Const k a b) -> [Const k a b] #

index :: (Const k a b, Const k a b) -> Const k a b -> Int #

unsafeIndex :: (Const k a b, Const k a b) -> Const k a b -> Int

inRange :: (Const k a b, Const k a b) -> Const k a b -> Bool #

rangeSize :: (Const k a b, Const k a b) -> Int #

unsafeRangeSize :: (Const k a b, Const k a b) -> Int

Generic (Const k a b) 

Associated Types

type Rep (Const k a b) :: * -> * #

Methods

from :: Const k a b -> Rep (Const k a b) x #

to :: Rep (Const k a b) x -> Const k a b #

Monoid a => Monoid (Const k a b) 

Methods

mempty :: Const k a b #

mappend :: Const k a b -> Const k a b -> Const k a b #

mconcat :: [Const k a b] -> Const k a b #

Storable a => Storable (Const k a b) 

Methods

sizeOf :: Const k a b -> Int #

alignment :: Const k a b -> Int #

peekElemOff :: Ptr (Const k a b) -> Int -> IO (Const k a b) #

pokeElemOff :: Ptr (Const k a b) -> Int -> Const k a b -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Const k a b) #

pokeByteOff :: Ptr b -> Int -> Const k a b -> IO () #

peek :: Ptr (Const k a b) -> IO (Const k a b) #

poke :: Ptr (Const k a b) -> Const k a b -> IO () #

Bits a => Bits (Const k a b) 

Methods

(.&.) :: Const k a b -> Const k a b -> Const k a b #

(.|.) :: Const k a b -> Const k a b -> Const k a b #

xor :: Const k a b -> Const k a b -> Const k a b #

complement :: Const k a b -> Const k a b #

shift :: Const k a b -> Int -> Const k a b #

rotate :: Const k a b -> Int -> Const k a b #

zeroBits :: Const k a b #

bit :: Int -> Const k a b #

setBit :: Const k a b -> Int -> Const k a b #

clearBit :: Const k a b -> Int -> Const k a b #

complementBit :: Const k a b -> Int -> Const k a b #

testBit :: Const k a b -> Int -> Bool #

bitSizeMaybe :: Const k a b -> Maybe Int #

bitSize :: Const k a b -> Int #

isSigned :: Const k a b -> Bool #

shiftL :: Const k a b -> Int -> Const k a b #

unsafeShiftL :: Const k a b -> Int -> Const k a b #

shiftR :: Const k a b -> Int -> Const k a b #

unsafeShiftR :: Const k a b -> Int -> Const k a b #

rotateL :: Const k a b -> Int -> Const k a b #

rotateR :: Const k a b -> Int -> Const k a b #

popCount :: Const k a b -> Int #

FiniteBits a => FiniteBits (Const k a b) 

Methods

finiteBitSize :: Const k a b -> Int #

countLeadingZeros :: Const k a b -> Int #

countTrailingZeros :: Const k a b -> Int #

type Rep1 k (Const k a) 
type Rep1 k (Const k a) = D1 k (MetaData "Const" "Data.Functor.Const" "base" True) (C1 k (MetaCons "Const" PrefixI True) (S1 k (MetaSel (Just Symbol "getConst") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 k a)))
type Rep (Const k a b) 
type Rep (Const k a b) = D1 * (MetaData "Const" "Data.Functor.Const" "base" True) (C1 * (MetaCons "Const" PrefixI True) (S1 * (MetaSel (Just Symbol "getConst") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)))

type Getting r s t a b = LensLike (Const r) s t a b Source #

(^.) :: s -> Getting a s t a b -> a infixl 8 Source #

view :: Getting a s t a b -> s -> a Source #