data-has-0.4.0.0: Simple extensible product
Copyright(c) Winterland 2016
LicenseBSD
Maintainerdrkoster@qq.com
Stabilityexperimental
PortabilityPORTABLE
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Has

Description

This module provide Has class which provide simple extensible product. The use case for this class is illustrated as following:

 {-# LANGUAGE FlexibleContexts #-}

 -- in some library code
 ...
 logInAnyReaderHasLogger :: (Has Logger r, MonadReader r m) => LogString -> m ()
 logInAnyReaderHasLogger s = asks getter >>= logWithLogger s

 queryInAnyReaderHasSQL :: (Has SqlBackEnd r, MonadReader r m) => Query -> m a
 queryInAnyReaderHasSQL q = asks getter >>= queryWithSQL q
 ...

 -- now you want to use these effects together
 ...
 logger <- initLogger  ...
 sql <- initSqlBackEnd ...

 (`runReader` (logger, sql)) $ do
       ...
       logInAnyReaderHasLogger ...
       ...
       x <- queryInAnyReaderHasSQL ...
       ...

If you need multiple elements with same type, you can use tagged like:

(Has (Tagged "StdLogger" Logger) r, Has (Tagged "FileLogger" Logger) r, ...) => ...

runYourMonad ... ( stdLogger :: Tagged "StdLogger" Logger
                 , fileLogger :: Tagged "FileLogger" Logger, ...)

Or you can define newtypes(which is less verbose and require no dependency):

newtype StdLogger = StdLogger Logger
newtype FileLogger = FileLogger Logger

runYourMonad ... (StdLogger stdLogger, FileLogger fileLogger)

Polymorphic values, such as numeric and string literals(with OverloadedString Enabled) may lead to type inference failure, you simply need type annotations in these cases:

 ... (3 :: Int, "hello" :: String, ...)

This module also provide infix type operator and pattern synonym of tuple, i.e. inductive procducts, which is more convenient to write. An overlapping instance prefer first(left) one is provided:

> getter (True :*: "hello" :*: 1) :: Integer
> 1
> getter (1 :*: 2 :*: 3) :: Integer
> 1
Synopsis

Documentation

type Lens t a = forall f. Functor f => (a -> f a) -> t -> f t Source #

type (:*:) a b = (a, b) infixr 1 Source #

Infix version of tuple(right associative).

pattern (:*:) :: a -> b -> (a, b) infixr 1 Source #

Infix pattern alias for tuple(right associative).

class Has a t where Source #

A type class for extensible product.

We provide instances for tuples up to 12 elements by default. You can define your own instance of Has, but most of the time tuples will do fine.

Minimal complete definition

getter, modifier | hasLens

Methods

getter :: t -> a Source #

modifier :: (a -> a) -> t -> t Source #

hasLens :: Lens t a Source #

Instances

Instances details
Has a a Source # 
Instance details

Defined in Data.Has

Methods

getter :: a -> a Source #

modifier :: (a -> a) -> a -> a Source #

hasLens :: Lens a a Source #

Has b bs => Has b (a, bs) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, bs) -> b Source #

modifier :: (b -> b) -> (a, bs) -> (a, bs) Source #

hasLens :: Lens (a, bs) b Source #

Has a (a, b) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b) -> a Source #

modifier :: (a -> a) -> (a, b) -> (a, b) Source #

hasLens :: Lens (a, b) a Source #

Has c (a, b, c) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c) -> c Source #

modifier :: (c -> c) -> (a, b, c) -> (a, b, c) Source #

hasLens :: Lens (a, b, c) c Source #

Has b (a, b, c) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c) -> b Source #

modifier :: (b -> b) -> (a, b, c) -> (a, b, c) Source #

hasLens :: Lens (a, b, c) b Source #

Has a (a, b, c) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c) -> a Source #

modifier :: (a -> a) -> (a, b, c) -> (a, b, c) Source #

hasLens :: Lens (a, b, c) a Source #

Has d (a, b, c, d) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d) -> d Source #

modifier :: (d -> d) -> (a, b, c, d) -> (a, b, c, d) Source #

hasLens :: Lens (a, b, c, d) d Source #

Has c (a, b, c, d) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d) -> c Source #

modifier :: (c -> c) -> (a, b, c, d) -> (a, b, c, d) Source #

hasLens :: Lens (a, b, c, d) c Source #

Has b (a, b, c, d) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d) -> b Source #

modifier :: (b -> b) -> (a, b, c, d) -> (a, b, c, d) Source #

hasLens :: Lens (a, b, c, d) b Source #

Has a (a, b, c, d) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d) -> a Source #

modifier :: (a -> a) -> (a, b, c, d) -> (a, b, c, d) Source #

hasLens :: Lens (a, b, c, d) a Source #

Has e (a, b, c, d, e) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d, e) -> e Source #

modifier :: (e -> e) -> (a, b, c, d, e) -> (a, b, c, d, e) Source #

hasLens :: Lens (a, b, c, d, e) e Source #

Has d (a, b, c, d, e) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d, e) -> d Source #

modifier :: (d -> d) -> (a, b, c, d, e) -> (a, b, c, d, e) Source #

hasLens :: Lens (a, b, c, d, e) d Source #

Has c (a, b, c, d, e) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d, e) -> c Source #

modifier :: (c -> c) -> (a, b, c, d, e) -> (a, b, c, d, e) Source #

hasLens :: Lens (a, b, c, d, e) c Source #

Has b (a, b, c, d, e) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d, e) -> b Source #

modifier :: (b -> b) -> (a, b, c, d, e) -> (a, b, c, d, e) Source #

hasLens :: Lens (a, b, c, d, e) b Source #

Has a (a, b, c, d, e) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d, e) -> a Source #

modifier :: (a -> a) -> (a, b, c, d, e) -> (a, b, c, d, e) Source #

hasLens :: Lens (a, b, c, d, e) a Source #

Has f (a, b, c, d, e, f) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d, e, f) -> f Source #

modifier :: (f -> f) -> (a, b, c, d, e, f) -> (a, b, c, d, e, f) Source #

hasLens :: Lens (a, b, c, d, e, f) f Source #

Has e (a, b, c, d, e, f) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d, e, f) -> e Source #

modifier :: (e -> e) -> (a, b, c, d, e, f) -> (a, b, c, d, e, f) Source #

hasLens :: Lens (a, b, c, d, e, f) e Source #

Has d (a, b, c, d, e, f) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d, e, f) -> d Source #

modifier :: (d -> d) -> (a, b, c, d, e, f) -> (a, b, c, d, e, f) Source #

hasLens :: Lens (a, b, c, d, e, f) d Source #

Has c (a, b, c, d, e, f) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d, e, f) -> c Source #

modifier :: (c -> c) -> (a, b, c, d, e, f) -> (a, b, c, d, e, f) Source #

hasLens :: Lens (a, b, c, d, e, f) c Source #

Has b (a, b, c, d, e, f) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d, e, f) -> b Source #

modifier :: (b -> b) -> (a, b, c, d, e, f) -> (a, b, c, d, e, f) Source #

hasLens :: Lens (a, b, c, d, e, f) b Source #

Has a (a, b, c, d, e, f) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d, e, f) -> a Source #

modifier :: (a -> a) -> (a, b, c, d, e, f) -> (a, b, c, d, e, f) Source #

hasLens :: Lens (a, b, c, d, e, f) a Source #

Has g (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d, e, f, g) -> g Source #

modifier :: (g -> g) -> (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) Source #

hasLens :: Lens (a, b, c, d, e, f, g) g Source #

Has f (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d, e, f, g) -> f Source #

modifier :: (f -> f) -> (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) Source #

hasLens :: Lens (a, b, c, d, e, f, g) f Source #

Has e (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d, e, f, g) -> e Source #

modifier :: (e -> e) -> (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) Source #

hasLens :: Lens (a, b, c, d, e, f, g) e Source #

Has d (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d, e, f, g) -> d Source #

modifier :: (d -> d) -> (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) Source #

hasLens :: Lens (a, b, c, d, e, f, g) d Source #

Has c (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d, e, f, g) -> c Source #

modifier :: (c -> c) -> (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) Source #

hasLens :: Lens (a, b, c, d, e, f, g) c Source #

Has b (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d, e, f, g) -> b Source #

modifier :: (b -> b) -> (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) Source #

hasLens :: Lens (a, b, c, d, e, f, g) b Source #

Has a (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d, e, f, g) -> a Source #

modifier :: (a -> a) -> (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) Source #

hasLens :: Lens (a, b, c, d, e, f, g) a Source #

Has h (a, b, c, d, e, f, g, h) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d, e, f, g, h) -> h Source #

modifier :: (h -> h) -> (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) Source #

hasLens :: Lens (a, b, c, d, e, f, g, h) h Source #

Has g (a, b, c, d, e, f, g, h) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d, e, f, g, h) -> g Source #

modifier :: (g -> g) -> (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) Source #

hasLens :: Lens (a, b, c, d, e, f, g, h) g Source #

Has f (a, b, c, d, e, f, g, h) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d, e, f, g, h) -> f Source #

modifier :: (f -> f) -> (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) Source #

hasLens :: Lens (a, b, c, d, e, f, g, h) f Source #

Has e (a, b, c, d, e, f, g, h) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d, e, f, g, h) -> e Source #

modifier :: (e -> e) -> (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) Source #

hasLens :: Lens (a, b, c, d, e, f, g, h) e Source #

Has d (a, b, c, d, e, f, g, h) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d, e, f, g, h) -> d Source #

modifier :: (d -> d) -> (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) Source #

hasLens :: Lens (a, b, c, d, e, f, g, h) d Source #

Has c (a, b, c, d, e, f, g, h) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d, e, f, g, h) -> c Source #

modifier :: (c -> c) -> (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) Source #

hasLens :: Lens (a, b, c, d, e, f, g, h) c Source #

Has b (a, b, c, d, e, f, g, h) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d, e, f, g, h) -> b Source #

modifier :: (b -> b) -> (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) Source #

hasLens :: Lens (a, b, c, d, e, f, g, h) b Source #

Has a (a, b, c, d, e, f, g, h) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d, e, f, g, h) -> a Source #

modifier :: (a -> a) -> (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) Source #

hasLens :: Lens (a, b, c, d, e, f, g, h) a Source #

Has i (a, b, c, d, e, f, g, h, i) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d, e, f, g, h, i) -> i Source #

modifier :: (i -> i) -> (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) Source #

hasLens :: Lens (a, b, c, d, e, f, g, h, i) i Source #

Has h (a, b, c, d, e, f, g, h, i) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d, e, f, g, h, i) -> h Source #

modifier :: (h -> h) -> (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) Source #

hasLens :: Lens (a, b, c, d, e, f, g, h, i) h Source #

Has g (a, b, c, d, e, f, g, h, i) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d, e, f, g, h, i) -> g Source #

modifier :: (g -> g) -> (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) Source #

hasLens :: Lens (a, b, c, d, e, f, g, h, i) g Source #

Has f (a, b, c, d, e, f, g, h, i) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d, e, f, g, h, i) -> f Source #

modifier :: (f -> f) -> (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) Source #

hasLens :: Lens (a, b, c, d, e, f, g, h, i) f Source #

Has e (a, b, c, d, e, f, g, h, i) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d, e, f, g, h, i) -> e Source #

modifier :: (e -> e) -> (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) Source #

hasLens :: Lens (a, b, c, d, e, f, g, h, i) e Source #

Has d (a, b, c, d, e, f, g, h, i) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d, e, f, g, h, i) -> d Source #

modifier :: (d -> d) -> (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) Source #

hasLens :: Lens (a, b, c, d, e, f, g, h, i) d Source #

Has c (a, b, c, d, e, f, g, h, i) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d, e, f, g, h, i) -> c Source #

modifier :: (c -> c) -> (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) Source #

hasLens :: Lens (a, b, c, d, e, f, g, h, i) c Source #

Has b (a, b, c, d, e, f, g, h, i) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d, e, f, g, h, i) -> b Source #

modifier :: (b -> b) -> (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) Source #

hasLens :: Lens (a, b, c, d, e, f, g, h, i) b Source #

Has a (a, b, c, d, e, f, g, h, i) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d, e, f, g, h, i) -> a Source #

modifier :: (a -> a) -> (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) Source #

hasLens :: Lens (a, b, c, d, e, f, g, h, i) a Source #

Has j (a, b, c, d, e, f, g, h, i, j) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d, e, f, g, h, i, j) -> j Source #

modifier :: (j -> j) -> (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) Source #

hasLens :: Lens (a, b, c, d, e, f, g, h, i, j) j Source #

Has i (a, b, c, d, e, f, g, h, i, j) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d, e, f, g, h, i, j) -> i Source #

modifier :: (i -> i) -> (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) Source #

hasLens :: Lens (a, b, c, d, e, f, g, h, i, j) i Source #

Has h (a, b, c, d, e, f, g, h, i, j) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d, e, f, g, h, i, j) -> h Source #

modifier :: (h -> h) -> (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) Source #

hasLens :: Lens (a, b, c, d, e, f, g, h, i, j) h Source #

Has g (a, b, c, d, e, f, g, h, i, j) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d, e, f, g, h, i, j) -> g Source #

modifier :: (g -> g) -> (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) Source #

hasLens :: Lens (a, b, c, d, e, f, g, h, i, j) g Source #

Has f (a, b, c, d, e, f, g, h, i, j) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d, e, f, g, h, i, j) -> f Source #

modifier :: (f -> f) -> (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) Source #

hasLens :: Lens (a, b, c, d, e, f, g, h, i, j) f Source #

Has e (a, b, c, d, e, f, g, h, i, j) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d, e, f, g, h, i, j) -> e Source #

modifier :: (e -> e) -> (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) Source #

hasLens :: Lens (a, b, c, d, e, f, g, h, i, j) e Source #

Has d (a, b, c, d, e, f, g, h, i, j) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d, e, f, g, h, i, j) -> d Source #

modifier :: (d -> d) -> (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) Source #

hasLens :: Lens (a, b, c, d, e, f, g, h, i, j) d Source #

Has c (a, b, c, d, e, f, g, h, i, j) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d, e, f, g, h, i, j) -> c Source #

modifier :: (c -> c) -> (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) Source #

hasLens :: Lens (a, b, c, d, e, f, g, h, i, j) c Source #

Has b (a, b, c, d, e, f, g, h, i, j) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d, e, f, g, h, i, j) -> b Source #

modifier :: (b -> b) -> (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) Source #

hasLens :: Lens (a, b, c, d, e, f, g, h, i, j) b Source #

Has a (a, b, c, d, e, f, g, h, i, j) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d, e, f, g, h, i, j) -> a Source #

modifier :: (a -> a) -> (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) Source #

hasLens :: Lens (a, b, c, d, e, f, g, h, i, j) a Source #

Has k (a, b, c, d, e, f, g, h, i, j, k) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d, e, f, g, h, i, j, k) -> k Source #

modifier :: (k -> k) -> (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) Source #

hasLens :: Lens (a, b, c, d, e, f, g, h, i, j, k) k Source #

Has j (a, b, c, d, e, f, g, h, i, j, k) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d, e, f, g, h, i, j, k) -> j Source #

modifier :: (j -> j) -> (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) Source #

hasLens :: Lens (a, b, c, d, e, f, g, h, i, j, k) j Source #

Has i (a, b, c, d, e, f, g, h, i, j, k) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d, e, f, g, h, i, j, k) -> i Source #

modifier :: (i -> i) -> (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) Source #

hasLens :: Lens (a, b, c, d, e, f, g, h, i, j, k) i Source #

Has h (a, b, c, d, e, f, g, h, i, j, k) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d, e, f, g, h, i, j, k) -> h Source #

modifier :: (h -> h) -> (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) Source #

hasLens :: Lens (a, b, c, d, e, f, g, h, i, j, k) h Source #

Has g (a, b, c, d, e, f, g, h, i, j, k) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d, e, f, g, h, i, j, k) -> g Source #

modifier :: (g -> g) -> (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) Source #

hasLens :: Lens (a, b, c, d, e, f, g, h, i, j, k) g Source #

Has f (a, b, c, d, e, f, g, h, i, j, k) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d, e, f, g, h, i, j, k) -> f Source #

modifier :: (f -> f) -> (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) Source #

hasLens :: Lens (a, b, c, d, e, f, g, h, i, j, k) f Source #

Has e (a, b, c, d, e, f, g, h, i, j, k) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d, e, f, g, h, i, j, k) -> e Source #

modifier :: (e -> e) -> (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) Source #

hasLens :: Lens (a, b, c, d, e, f, g, h, i, j, k) e Source #

Has d (a, b, c, d, e, f, g, h, i, j, k) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d, e, f, g, h, i, j, k) -> d Source #

modifier :: (d -> d) -> (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) Source #

hasLens :: Lens (a, b, c, d, e, f, g, h, i, j, k) d Source #

Has c (a, b, c, d, e, f, g, h, i, j, k) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d, e, f, g, h, i, j, k) -> c Source #

modifier :: (c -> c) -> (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) Source #

hasLens :: Lens (a, b, c, d, e, f, g, h, i, j, k) c Source #

Has b (a, b, c, d, e, f, g, h, i, j, k) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d, e, f, g, h, i, j, k) -> b Source #

modifier :: (b -> b) -> (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) Source #

hasLens :: Lens (a, b, c, d, e, f, g, h, i, j, k) b Source #

Has a (a, b, c, d, e, f, g, h, i, j, k) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d, e, f, g, h, i, j, k) -> a Source #

modifier :: (a -> a) -> (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) Source #

hasLens :: Lens (a, b, c, d, e, f, g, h, i, j, k) a Source #

Has l (a, b, c, d, e, f, g, h, i, j, k, l) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d, e, f, g, h, i, j, k, l) -> l Source #

modifier :: (l -> l) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) Source #

hasLens :: Lens (a, b, c, d, e, f, g, h, i, j, k, l) l Source #

Has k (a, b, c, d, e, f, g, h, i, j, k, l) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d, e, f, g, h, i, j, k, l) -> k Source #

modifier :: (k -> k) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) Source #

hasLens :: Lens (a, b, c, d, e, f, g, h, i, j, k, l) k Source #

Has j (a, b, c, d, e, f, g, h, i, j, k, l) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d, e, f, g, h, i, j, k, l) -> j Source #

modifier :: (j -> j) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) Source #

hasLens :: Lens (a, b, c, d, e, f, g, h, i, j, k, l) j Source #

Has i (a, b, c, d, e, f, g, h, i, j, k, l) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d, e, f, g, h, i, j, k, l) -> i Source #

modifier :: (i -> i) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) Source #

hasLens :: Lens (a, b, c, d, e, f, g, h, i, j, k, l) i Source #

Has h (a, b, c, d, e, f, g, h, i, j, k, l) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d, e, f, g, h, i, j, k, l) -> h Source #

modifier :: (h -> h) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) Source #

hasLens :: Lens (a, b, c, d, e, f, g, h, i, j, k, l) h Source #

Has g (a, b, c, d, e, f, g, h, i, j, k, l) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d, e, f, g, h, i, j, k, l) -> g Source #

modifier :: (g -> g) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) Source #

hasLens :: Lens (a, b, c, d, e, f, g, h, i, j, k, l) g Source #

Has f (a, b, c, d, e, f, g, h, i, j, k, l) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d, e, f, g, h, i, j, k, l) -> f Source #

modifier :: (f -> f) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) Source #

hasLens :: Lens (a, b, c, d, e, f, g, h, i, j, k, l) f Source #

Has e (a, b, c, d, e, f, g, h, i, j, k, l) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d, e, f, g, h, i, j, k, l) -> e Source #

modifier :: (e -> e) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) Source #

hasLens :: Lens (a, b, c, d, e, f, g, h, i, j, k, l) e Source #

Has d (a, b, c, d, e, f, g, h, i, j, k, l) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d, e, f, g, h, i, j, k, l) -> d Source #

modifier :: (d -> d) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) Source #

hasLens :: Lens (a, b, c, d, e, f, g, h, i, j, k, l) d Source #

Has c (a, b, c, d, e, f, g, h, i, j, k, l) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d, e, f, g, h, i, j, k, l) -> c Source #

modifier :: (c -> c) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) Source #

hasLens :: Lens (a, b, c, d, e, f, g, h, i, j, k, l) c Source #

Has b (a, b, c, d, e, f, g, h, i, j, k, l) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d, e, f, g, h, i, j, k, l) -> b Source #

modifier :: (b -> b) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) Source #

hasLens :: Lens (a, b, c, d, e, f, g, h, i, j, k, l) b Source #

Has a (a, b, c, d, e, f, g, h, i, j, k, l) Source # 
Instance details

Defined in Data.Has

Methods

getter :: (a, b, c, d, e, f, g, h, i, j, k, l) -> a Source #

modifier :: (a -> a) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) Source #

hasLens :: Lens (a, b, c, d, e, f, g, h, i, j, k, l) a Source #