Copyright | (c) The University of Glasgow 2001 |
---|---|
License | BSD-style (see the file libraries/base/LICENSE) |
Maintainer | libraries@haskell.org |
Stability | stable |
Portability | portable |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
Functions associated with the tuple data types.
Synopsis
- data Solo a where
- getSolo :: (a) -> a
- fst :: (a, b) -> a
- snd :: (a, b) -> b
- curry :: ((a, b) -> c) -> a -> b -> c
- uncurry :: (a -> b -> c) -> (a, b) -> c
- swap :: (a, b) -> (b, a)
- data Unit = ()
- data Solo a = MkSolo a
- data Tuple2 a b = (,) a b
- data Tuple3 a b c = (,,) a b c
- data Tuple4 a b c d = (,,,) a b c d
- data Tuple5 a b c d e = (,,,,) a b c d e
- data Tuple6 a b c d e f = (,,,,,) a b c d e f
- data Tuple7 a b c d e f g = (,,,,,,) a b c d e f g
- data Tuple8 a b c d e f g h = (,,,,,,,) a b c d e f g h
- data Tuple9 a b c d e f g h i = (,,,,,,,,) a b c d e f g h i
- data Tuple10 a b c d e f g h i j = (,,,,,,,,,) a b c d e f g h i j
- data Tuple11 a b c d e f g h i j k = (,,,,,,,,,,) a b c d e f g h i j k
- data Tuple12 a b c d e f g h i j k l = (,,,,,,,,,,,) a b c d e f g h i j k l
- data Tuple13 a b c d e f g h i j k l m = (,,,,,,,,,,,,) a b c d e f g h i j k l m
- data Tuple14 a b c d e f g h i j k l m n = (,,,,,,,,,,,,,) a b c d e f g h i j k l m n
- data Tuple15 a b c d e f g h i j k l m n o = (,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o
Documentation
Solo
is the canonical lifted 1-tuple, just like Tuple2
is the canonical
lifted 2-tuple (pair) and Tuple3
is the canonical lifted 3-tuple (triple).
The most important feature of Solo
is that it is possible to force its
"outside" (usually by pattern matching) without forcing its "inside",
because it is defined as a datatype rather than a newtype. One situation
where this can be useful is when writing a function to extract a value from
a data structure. Suppose you write an implementation of arrays and offer
only this function to index into them:
index :: Array a -> Int -> a
Now imagine that someone wants to extract a value from an array and store it in a lazy-valued finite map/dictionary:
insert "hello" (arr index
12) m
This can actually lead to a space leak. The value is not actually extracted from the array until that value (now buried in a map) is forced. That means the entire array may be kept live by just that value! Often, the solution is to use a strict map, or to force the value before storing it, but for some purposes that's undesirable.
One common solution is to include an indexing function that can produce its
result in an arbitrary Applicative
context:
indexA :: Applicative f => Array a -> Int -> f a
When using indexA
in a pure context, Solo
serves as a handy
Applicative
functor to hold the result. You could write a non-leaky
version of the above example thus:
case arr indexA
12 of
Solo a -> insert "hello" a m
While such simple extraction functions are the most common uses for unary tuples, they can also be useful for fine-grained control of strict-spined data structure traversals, and for unifying the implementations of lazy and strict mapping functions.
MkSolo a |
pattern Solo :: a -> (a) |
Instances
MonadFix Solo Source # | Since: base-4.15 | ||||
Defined in Control.Monad.Fix | |||||
MonadZip Solo Source # | Since: base-4.15.0.0 | ||||
Foldable Solo Source # | Since: base-4.15 | ||||
Defined in Data.Foldable fold :: Monoid m => (m) -> m Source # foldMap :: Monoid m => (a -> m) -> (a) -> m Source # foldMap' :: Monoid m => (a -> m) -> (a) -> m Source # foldr :: (a -> b -> b) -> b -> (a) -> b Source # foldr' :: (a -> b -> b) -> b -> (a) -> b Source # foldl :: (b -> a -> b) -> b -> (a) -> b Source # foldl' :: (b -> a -> b) -> b -> (a) -> b Source # foldr1 :: (a -> a -> a) -> (a) -> a Source # foldl1 :: (a -> a -> a) -> (a) -> a Source # elem :: Eq a => a -> (a) -> Bool Source # maximum :: Ord a => (a) -> a Source # minimum :: Ord a => (a) -> a Source # | |||||
Foldable1 Solo Source # | Since: base-4.18.0.0 | ||||
Defined in Data.Foldable1 fold1 :: Semigroup m => (m) -> m Source # foldMap1 :: Semigroup m => (a -> m) -> (a) -> m Source # foldMap1' :: Semigroup m => (a -> m) -> (a) -> m Source # toNonEmpty :: (a) -> NonEmpty a Source # maximum :: Ord a => (a) -> a Source # minimum :: Ord a => (a) -> a Source # foldrMap1 :: (a -> b) -> (a -> b -> b) -> (a) -> b Source # foldlMap1' :: (a -> b) -> (b -> a -> b) -> (a) -> b Source # foldlMap1 :: (a -> b) -> (b -> a -> b) -> (a) -> b Source # foldrMap1' :: (a -> b) -> (a -> b -> b) -> (a) -> b Source # | |||||
Eq1 Solo Source # | Since: base-4.15 | ||||
Ord1 Solo Source # | Since: base-4.15 | ||||
Defined in Data.Functor.Classes liftCompare :: (a -> b -> Ordering) -> (a) -> (b) -> Ordering Source # | |||||
Read1 Solo Source # | Since: base-4.15 | ||||
Defined in Data.Functor.Classes | |||||
Show1 Solo Source # | Since: base-4.15 | ||||
Traversable Solo Source # | Since: base-4.15 | ||||
Applicative Solo Source # | Since: base-4.15 | ||||
Functor Solo Source # | Since: base-4.15 | ||||
Monad Solo Source # | Since: base-4.15 | ||||
Generic1 Solo Source # | |||||
Defined in GHC.Generics
| |||||
Data a => Data (a) Source # | Since: base-4.15 | ||||
Defined in Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> (a) -> c (a) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (a) Source # toConstr :: (a) -> Constr Source # dataTypeOf :: (a) -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (a)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (a)) Source # gmapT :: (forall b. Data b => b -> b) -> (a) -> (a) Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> (a) -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> (a) -> r Source # gmapQ :: (forall d. Data d => d -> u) -> (a) -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> (a) -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> (a) -> m (a) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> (a) -> m (a) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> (a) -> m (a) Source # | |||||
Monoid a => Monoid (a) Source # | Since: base-4.15 | ||||
Semigroup a => Semigroup (a) Source # | Since: base-4.15 | ||||
Bounded a => Bounded (a) Source # | |||||
Enum a => Enum (a) Source # | |||||
Defined in GHC.Enum | |||||
Generic (a) Source # | |||||
Defined in GHC.Generics
| |||||
Ix a => Ix (a) Source # | |||||
Read a => Read (a) Source # | Since: base-4.15 | ||||
Show a => Show (a) Source # | Since: base-4.15 | ||||
Eq a => Eq (a) | |||||
Ord a => Ord (a) | |||||
type Rep1 Solo Source # | Since: base-4.15 | ||||
Defined in GHC.Generics | |||||
type Rep (a) Source # | Since: base-4.15 | ||||
Defined in GHC.Generics |
Extract the value from a Solo
. Very often, values should be extracted
directly using pattern matching, to control just what gets evaluated when.
getSolo
is for convenience in situations where that is not the case:
When the result is passed to a strict function, it makes no difference whether the pattern matching is done on the "outside" or on the "inside":
Data.Set.insert (getSolo sol) set === case sol of Solo v -> Data.Set.insert v set
A traversal may be performed in Solo
in order to control evaluation
internally, while using getSolo
to extract the final result. A strict
mapping function, for example, could be defined
map' :: Traversable t => (a -> b) -> t a -> t b map' f = getSolo . traverse ((Solo $!) . f)
uncurry :: (a -> b -> c) -> (a, b) -> c Source #
uncurry
converts a curried function to a function on pairs.
Examples
>>>
uncurry (+) (1,2)
3
>>>
uncurry ($) (show, 1)
"1"
>>>
map (uncurry max) [(1,2), (3,4), (6,8)]
[2,4,8]
The unit datatype Unit
has one non-undefined member, the nullary
constructor ()
.
Since: ghc-prim-0.11.0
Instances
Data () Source # | Since: base-4.0.0.0 | ||||
Defined in Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> () -> c () Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c () Source # toConstr :: () -> Constr Source # dataTypeOf :: () -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ()) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ()) Source # gmapT :: (forall b. Data b => b -> b) -> () -> () Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> () -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> () -> r Source # gmapQ :: (forall d. Data d => d -> u) -> () -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> () -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> () -> m () Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> () -> m () Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> () -> m () Source # | |||||
Storable () Source # | Since: base-4.9.0.0 | ||||
Monoid () Source # | Since: base-2.1 | ||||
Semigroup () Source # | Since: base-4.9.0.0 | ||||
Bounded () Source # | Since: base-2.1 | ||||
Enum () Source # | Since: base-2.1 | ||||
Generic () Source # | |||||
Ix () Source # | Since: base-2.1 | ||||
Read () Source # | Since: base-2.1 | ||||
Show () Source # | Since: base-2.1 | ||||
Eq () | |||||
Ord () | |||||
Generic1 (URec (Ptr ()) :: k -> Type) Source # | |||||
Defined in GHC.Generics
| |||||
Foldable (UAddr :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Foldable fold :: Monoid m => UAddr m -> m Source # foldMap :: Monoid m => (a -> m) -> UAddr a -> m Source # foldMap' :: Monoid m => (a -> m) -> UAddr a -> m Source # foldr :: (a -> b -> b) -> b -> UAddr a -> b Source # foldr' :: (a -> b -> b) -> b -> UAddr a -> b Source # foldl :: (b -> a -> b) -> b -> UAddr a -> b Source # foldl' :: (b -> a -> b) -> b -> UAddr a -> b Source # foldr1 :: (a -> a -> a) -> UAddr a -> a Source # foldl1 :: (a -> a -> a) -> UAddr a -> a Source # toList :: UAddr a -> [a] Source # null :: UAddr a -> Bool Source # length :: UAddr a -> Int Source # elem :: Eq a => a -> UAddr a -> Bool Source # maximum :: Ord a => UAddr a -> a Source # minimum :: Ord a => UAddr a -> a Source # | |||||
Traversable (UAddr :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Functor (URec (Ptr ()) :: Type -> Type) Source # | Since: base-4.9.0.0 | ||||
Generic (URec (Ptr ()) p) Source # | |||||
Defined in GHC.Generics
| |||||
Eq (URec (Ptr ()) p) Source # | Since: base-4.9.0.0 | ||||
Ord (URec (Ptr ()) p) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Generics compare :: URec (Ptr ()) p -> URec (Ptr ()) p -> Ordering Source # (<) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool Source # (<=) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool Source # (>) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool Source # (>=) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool Source # max :: URec (Ptr ()) p -> URec (Ptr ()) p -> URec (Ptr ()) p Source # min :: URec (Ptr ()) p -> URec (Ptr ()) p -> URec (Ptr ()) p Source # | |||||
type Rep () Source # | Since: base-4.6.0.0 | ||||
data URec (Ptr ()) (p :: k) Source # | Used for marking occurrences of Since: base-4.9.0.0 | ||||
type Rep1 (URec (Ptr ()) :: k -> Type) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Generics | |||||
type Rep (URec (Ptr ()) p) Source # | Since: base-4.9.0.0 | ||||
Defined in GHC.Generics |
Solo
is the canonical lifted 1-tuple, just like Tuple2
is the canonical
lifted 2-tuple (pair) and Tuple3
is the canonical lifted 3-tuple (triple).
The most important feature of Solo
is that it is possible to force its
"outside" (usually by pattern matching) without forcing its "inside",
because it is defined as a datatype rather than a newtype. One situation
where this can be useful is when writing a function to extract a value from
a data structure. Suppose you write an implementation of arrays and offer
only this function to index into them:
index :: Array a -> Int -> a
Now imagine that someone wants to extract a value from an array and store it in a lazy-valued finite map/dictionary:
insert "hello" (arr index
12) m
This can actually lead to a space leak. The value is not actually extracted from the array until that value (now buried in a map) is forced. That means the entire array may be kept live by just that value! Often, the solution is to use a strict map, or to force the value before storing it, but for some purposes that's undesirable.
One common solution is to include an indexing function that can produce its
result in an arbitrary Applicative
context:
indexA :: Applicative f => Array a -> Int -> f a
When using indexA
in a pure context, Solo
serves as a handy
Applicative
functor to hold the result. You could write a non-leaky
version of the above example thus:
case arr indexA
12 of
Solo a -> insert "hello" a m
While such simple extraction functions are the most common uses for unary tuples, they can also be useful for fine-grained control of strict-spined data structure traversals, and for unifying the implementations of lazy and strict mapping functions.
MkSolo a |
Instances
MonadFix Solo Source # | Since: base-4.15 | ||||
Defined in Control.Monad.Fix | |||||
MonadZip Solo Source # | Since: base-4.15.0.0 | ||||
Foldable Solo Source # | Since: base-4.15 | ||||
Defined in Data.Foldable fold :: Monoid m => (m) -> m Source # foldMap :: Monoid m => (a -> m) -> (a) -> m Source # foldMap' :: Monoid m => (a -> m) -> (a) -> m Source # foldr :: (a -> b -> b) -> b -> (a) -> b Source # foldr' :: (a -> b -> b) -> b -> (a) -> b Source # foldl :: (b -> a -> b) -> b -> (a) -> b Source # foldl' :: (b -> a -> b) -> b -> (a) -> b Source # foldr1 :: (a -> a -> a) -> (a) -> a Source # foldl1 :: (a -> a -> a) -> (a) -> a Source # elem :: Eq a => a -> (a) -> Bool Source # maximum :: Ord a => (a) -> a Source # minimum :: Ord a => (a) -> a Source # | |||||
Foldable1 Solo Source # | Since: base-4.18.0.0 | ||||
Defined in Data.Foldable1 fold1 :: Semigroup m => (m) -> m Source # foldMap1 :: Semigroup m => (a -> m) -> (a) -> m Source # foldMap1' :: Semigroup m => (a -> m) -> (a) -> m Source # toNonEmpty :: (a) -> NonEmpty a Source # maximum :: Ord a => (a) -> a Source # minimum :: Ord a => (a) -> a Source # foldrMap1 :: (a -> b) -> (a -> b -> b) -> (a) -> b Source # foldlMap1' :: (a -> b) -> (b -> a -> b) -> (a) -> b Source # foldlMap1 :: (a -> b) -> (b -> a -> b) -> (a) -> b Source # foldrMap1' :: (a -> b) -> (a -> b -> b) -> (a) -> b Source # | |||||
Eq1 Solo Source # | Since: base-4.15 | ||||
Ord1 Solo Source # | Since: base-4.15 | ||||
Defined in Data.Functor.Classes liftCompare :: (a -> b -> Ordering) -> (a) -> (b) -> Ordering Source # | |||||
Read1 Solo Source # | Since: base-4.15 | ||||
Defined in Data.Functor.Classes | |||||
Show1 Solo Source # | Since: base-4.15 | ||||
Traversable Solo Source # | Since: base-4.15 | ||||
Applicative Solo Source # | Since: base-4.15 | ||||
Functor Solo Source # | Since: base-4.15 | ||||
Monad Solo Source # | Since: base-4.15 | ||||
Generic1 Solo Source # | |||||
Defined in GHC.Generics
| |||||
Data a => Data (a) Source # | Since: base-4.15 | ||||
Defined in Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> (a) -> c (a) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (a) Source # toConstr :: (a) -> Constr Source # dataTypeOf :: (a) -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (a)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (a)) Source # gmapT :: (forall b. Data b => b -> b) -> (a) -> (a) Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> (a) -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> (a) -> r Source # gmapQ :: (forall d. Data d => d -> u) -> (a) -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> (a) -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> (a) -> m (a) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> (a) -> m (a) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> (a) -> m (a) Source # | |||||
Monoid a => Monoid (a) Source # | Since: base-4.15 | ||||
Semigroup a => Semigroup (a) Source # | Since: base-4.15 | ||||
Bounded a => Bounded (a) Source # | |||||
Enum a => Enum (a) Source # | |||||
Defined in GHC.Enum | |||||
Generic (a) Source # | |||||
Defined in GHC.Generics
| |||||
Ix a => Ix (a) Source # | |||||
Read a => Read (a) Source # | Since: base-4.15 | ||||
Show a => Show (a) Source # | Since: base-4.15 | ||||
Eq a => Eq (a) | |||||
Ord a => Ord (a) | |||||
type Rep1 Solo Source # | Since: base-4.15 | ||||
Defined in GHC.Generics | |||||
type Rep (a) Source # | Since: base-4.15 | ||||
Defined in GHC.Generics |
A tuple of two elements.
Since: ghc-prim-0.11.0
(,) a b |
Instances
Bifoldable Tuple2 Source # | Since: base-4.10.0.0 | ||||
Bifoldable1 Tuple2 Source # | |||||
Defined in Data.Bifoldable1 | |||||
Bifunctor Tuple2 Source # | Class laws for tuples hold only up to laziness. Both
Since: base-4.8.0.0 | ||||
Bitraversable Tuple2 Source # | Since: base-4.10.0.0 | ||||
Defined in Data.Bitraversable bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> (a, b) -> f (c, d) Source # | |||||
Eq2 Tuple2 Source # | Since: base-4.9.0.0 | ||||
Ord2 Tuple2 Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Functor.Classes | |||||
Read2 Tuple2 Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Functor.Classes liftReadsPrec2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> Int -> ReadS (a, b) Source # liftReadList2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [(a, b)] Source # liftReadPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (a, b) Source # liftReadListPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [(a, b)] Source # | |||||
Show2 Tuple2 Source # | Since: base-4.9.0.0 | ||||
Generic1 (Tuple2 a :: Type -> Type) Source # | |||||
Defined in GHC.Generics
| |||||
Foldable (Tuple2 a) Source # | Since: base-4.7.0.0 | ||||
Defined in Data.Foldable fold :: Monoid m => (a, m) -> m Source # foldMap :: Monoid m => (a0 -> m) -> (a, a0) -> m Source # foldMap' :: Monoid m => (a0 -> m) -> (a, a0) -> m Source # foldr :: (a0 -> b -> b) -> b -> (a, a0) -> b Source # foldr' :: (a0 -> b -> b) -> b -> (a, a0) -> b Source # foldl :: (b -> a0 -> b) -> b -> (a, a0) -> b Source # foldl' :: (b -> a0 -> b) -> b -> (a, a0) -> b Source # foldr1 :: (a0 -> a0 -> a0) -> (a, a0) -> a0 Source # foldl1 :: (a0 -> a0 -> a0) -> (a, a0) -> a0 Source # toList :: (a, a0) -> [a0] Source # null :: (a, a0) -> Bool Source # length :: (a, a0) -> Int Source # elem :: Eq a0 => a0 -> (a, a0) -> Bool Source # maximum :: Ord a0 => (a, a0) -> a0 Source # minimum :: Ord a0 => (a, a0) -> a0 Source # | |||||
Foldable1 (Tuple2 a) Source # | Since: base-4.18.0.0 | ||||
Defined in Data.Foldable1 fold1 :: Semigroup m => (a, m) -> m Source # foldMap1 :: Semigroup m => (a0 -> m) -> (a, a0) -> m Source # foldMap1' :: Semigroup m => (a0 -> m) -> (a, a0) -> m Source # toNonEmpty :: (a, a0) -> NonEmpty a0 Source # maximum :: Ord a0 => (a, a0) -> a0 Source # minimum :: Ord a0 => (a, a0) -> a0 Source # head :: (a, a0) -> a0 Source # last :: (a, a0) -> a0 Source # foldrMap1 :: (a0 -> b) -> (a0 -> b -> b) -> (a, a0) -> b Source # foldlMap1' :: (a0 -> b) -> (b -> a0 -> b) -> (a, a0) -> b Source # foldlMap1 :: (a0 -> b) -> (b -> a0 -> b) -> (a, a0) -> b Source # foldrMap1' :: (a0 -> b) -> (a0 -> b -> b) -> (a, a0) -> b Source # | |||||
Eq a => Eq1 (Tuple2 a) Source # | Since: base-4.9.0.0 | ||||
Ord a => Ord1 (Tuple2 a) Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Functor.Classes liftCompare :: (a0 -> b -> Ordering) -> (a, a0) -> (a, b) -> Ordering Source # | |||||
Read a => Read1 (Tuple2 a) Source # | Since: base-4.9.0.0 | ||||
Defined in Data.Functor.Classes liftReadsPrec :: (Int -> ReadS a0) -> ReadS [a0] -> Int -> ReadS (a, a0) Source # liftReadList :: (Int -> ReadS a0) -> ReadS [a0] -> ReadS [(a, a0)] Source # liftReadPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec (a, a0) Source # liftReadListPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec [(a, a0)] Source # | |||||
Show a => Show1 (Tuple2 a) Source # | Since: base-4.9.0.0 | ||||
Traversable (Tuple2 a) Source # | Since: base-4.7.0.0 | ||||
Monoid a => Applicative (Tuple2 a) Source # | For tuples, the ("hello ", (+15)) <*> ("world!", 2002) ("hello world!",2017) Since: base-2.1 | ||||
Functor (Tuple2 a) Source # | Since: base-2.1 | ||||
Monoid a => Monad (Tuple2 a) Source # | Since: base-4.9.0.0 | ||||
(Data a, Data b) => Data (a, b) Source # | Since: base-4.0.0.0 | ||||
Defined in Data.Data gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> (a, b) -> c (a, b) Source # gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (a, b) Source # toConstr :: (a, b) -> Constr Source # dataTypeOf :: (a, b) -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (a, b)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (a, b)) Source # gmapT :: (forall b0. Data b0 => b0 -> b0) -> (a, b) -> (a, b) Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> (a, b) -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> (a, b) -> r Source # gmapQ :: (forall d. Data d => d -> u) -> (a, b) -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> (a, b) -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> (a, b) -> m (a, b) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> (a, b) -> m (a, b) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> (a, b) -> m (a, b) Source # | |||||
(Monoid a, Monoid b) => Monoid (a, b) Source # | Since: base-2.1 | ||||
(Semigroup a, Semigroup b) => Semigroup (a, b) Source # | Since: base-4.9.0.0 | ||||
(Bounded a, Bounded b) => Bounded (a, b) Source # | Since: base-2.1 | ||||
Generic (a, b) Source # | |||||
Defined in GHC.Generics
| |||||
(Ix a, Ix b) => Ix (a, b) Source # | Since: base-2.1 | ||||
Defined in GHC.Ix range :: ((a, b), (a, b)) -> [(a, b)] Source # index :: ((a, b), (a, b)) -> (a, b) -> Int Source # unsafeIndex :: ((a, b), (a, b)) -> (a, b) -> Int Source # inRange :: ((a, b), (a, b)) -> (a, b) -> Bool Source # rangeSize :: ((a, b), (a, b)) -> Int Source # unsafeRangeSize :: ((a, b), (a, b)) -> Int Source # | |||||
(Read a, Read b) => Read (a, b) Source # | Since: base-2.1 | ||||
(Show a, Show b) => Show (a, b) Source # | Since: base-2.1 | ||||
(Eq a, Eq b) => Eq (a, b) | |||||
(Ord a, Ord b) => Ord (a, b) | |||||
Defined in GHC.Classes | |||||
type Rep1 (Tuple2 a :: Type -> Type) Source # | Since: base-4.6.0.0 | ||||
Defined in GHC.Generics type Rep1 (Tuple2 a :: Type -> Type) = D1 ('MetaData "Tuple2" "GHC.Tuple.Prim" "ghc-prim" 'False) (C1 ('MetaCons "(,)" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1)) | |||||
type Rep (a, b) Source # | Since: base-4.6.0.0 | ||||
Defined in GHC.Generics type Rep (a, b) = D1 ('MetaData "Tuple2" "GHC.Tuple.Prim" "ghc-prim" 'False) (C1 ('MetaCons "(,)" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b))) |
A tuple of three elements.
Since: ghc-prim-0.11.0
(,,) a b c |
Instances
Generic1 (Tuple3 a b :: Type -> Type) Source # | |||||
Defined in GHC.Generics
| |||||
Bifoldable (Tuple3 x) Source # | Since: base-4.10.0.0 | ||||
Bifoldable1 (Tuple3 x) Source # | |||||
Defined in Data.Bifoldable1 | |||||
Bifunctor (Tuple3 x1) Source # | Since: base-4.8.0.0 | ||||
Bitraversable (Tuple3 x) Source # | Since: base-4.10.0.0 | ||||
Defined in Data.Bitraversable bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> (x, a, b) -> f (x, c, d) Source # | |||||
Eq a => Eq2 (Tuple3 a) Source # |
Since: base-4.16.0.0 | ||||
Ord a => Ord2 (Tuple3 a) Source # |
Since: base-4.16.0.0 | ||||
Defined in Data.Functor.Classes | |||||
Read a => Read2 (Tuple3 a) Source # |
Since: base-4.16.0.0 | ||||
Defined in Data.Functor.Classes liftReadsPrec2 :: (Int -> ReadS a0) -> ReadS [a0] -> (Int -> ReadS b) -> ReadS [b] -> Int -> ReadS (a, a0, b) Source # liftReadList2 :: (Int -> ReadS a0) -> ReadS [a0] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [(a, a0, b)] Source # liftReadPrec2 :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (a, a0, b) Source # liftReadListPrec2 :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [(a, a0, b)] Source # | |||||
Show a => Show2 (Tuple3 a) Source # |
Since: base-4.16.0.0 | ||||
Defined in Data.Functor.Classes | |||||
(Eq a, Eq b) => Eq1 (Tuple3 a b) Source # | Since: base-4.16.0.0 | ||||
(Ord a, Ord b) => Ord1 (Tuple3 a b) Source # | Since: base-4.16.0.0 | ||||
Defined in Data.Functor.Classes liftCompare :: (a0 -> b0 -> Ordering) -> (a, b, a0) -> (a, b, b0) -> Ordering Source # | |||||
(Read a, Read b) => Read1 (Tuple3 a b) Source # | Since: base-4.16.0.0 | ||||
Defined in Data.Functor.Classes liftReadsPrec :: (Int -> ReadS a0) -> ReadS [a0] -> Int -> ReadS (a, b, a0) Source # liftReadList :: (Int -> ReadS a0) -> ReadS [a0] -> ReadS [(a, b, a0)] Source # liftReadPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec (a, b, a0) Source # liftReadListPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec [(a, b, a0)] Source # | |||||
(Show a, Show b) => Show1 (Tuple3 a b) Source # | Since: base-4.16.0.0 | ||||
(Monoid a, Monoid b) => Applicative (Tuple3 a b) Source # | Since: base-4.14.0.0 | ||||
Defined in GHC.Base | |||||
Functor (Tuple3 a b) Source # | Since: base-4.14.0.0 | ||||
(Monoid a, Monoid b) => Monad (Tuple3 a b) Source # | Since: base-4.14.0.0 | ||||
(Data a, Data b, Data c) => Data (a, b, c) Source # | Since: base-4.0.0.0 | ||||
Defined in Data.Data gfoldl :: (forall d b0. Data d => c0 (d -> b0) -> d -> c0 b0) -> (forall g. g -> c0 g) -> (a, b, c) -> c0 (a, b, c) Source # gunfold :: (forall b0 r. Data b0 => c0 (b0 -> r) -> c0 r) -> (forall r. r -> c0 r) -> Constr -> c0 (a, b, c) Source # toConstr :: (a, b, c) -> Constr Source # dataTypeOf :: (a, b, c) -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c0 (t d)) -> Maybe (c0 (a, b, c)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c0 (t d e)) -> Maybe (c0 (a, b, c)) Source # gmapT :: (forall b0. Data b0 => b0 -> b0) -> (a, b, c) -> (a, b, c) Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> (a, b, c) -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> (a, b, c) -> r Source # gmapQ :: (forall d. Data d => d -> u) -> (a, b, c) -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> (a, b, c) -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> (a, b, c) -> m (a, b, c) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> (a, b, c) -> m (a, b, c) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> (a, b, c) -> m (a, b, c) Source # | |||||
(Monoid a, Monoid b, Monoid c) => Monoid (a, b, c) Source # | Since: base-2.1 | ||||
(Semigroup a, Semigroup b, Semigroup c) => Semigroup (a, b, c) Source # | Since: base-4.9.0.0 | ||||
(Bounded a, Bounded b, Bounded c) => Bounded (a, b, c) Source # | Since: base-2.1 | ||||
Generic (a, b, c) Source # | |||||
Defined in GHC.Generics
| |||||
(Ix a1, Ix a2, Ix a3) => Ix (a1, a2, a3) Source # | Since: base-2.1 | ||||
Defined in GHC.Ix range :: ((a1, a2, a3), (a1, a2, a3)) -> [(a1, a2, a3)] Source # index :: ((a1, a2, a3), (a1, a2, a3)) -> (a1, a2, a3) -> Int Source # unsafeIndex :: ((a1, a2, a3), (a1, a2, a3)) -> (a1, a2, a3) -> Int Source # inRange :: ((a1, a2, a3), (a1, a2, a3)) -> (a1, a2, a3) -> Bool Source # rangeSize :: ((a1, a2, a3), (a1, a2, a3)) -> Int Source # unsafeRangeSize :: ((a1, a2, a3), (a1, a2, a3)) -> Int Source # | |||||
(Read a, Read b, Read c) => Read (a, b, c) Source # | Since: base-2.1 | ||||
(Show a, Show b, Show c) => Show (a, b, c) Source # | Since: base-2.1 | ||||
(Eq a, Eq b, Eq c) => Eq (a, b, c) | |||||
(Ord a, Ord b, Ord c) => Ord (a, b, c) | |||||
Defined in GHC.Classes | |||||
type Rep1 (Tuple3 a b :: Type -> Type) Source # | Since: base-4.6.0.0 | ||||
Defined in GHC.Generics type Rep1 (Tuple3 a b :: Type -> Type) = D1 ('MetaData "Tuple3" "GHC.Tuple.Prim" "ghc-prim" 'False) (C1 ('MetaCons "(,,)" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))) | |||||
type Rep (a, b, c) Source # | Since: base-4.6.0.0 | ||||
Defined in GHC.Generics type Rep (a, b, c) = D1 ('MetaData "Tuple3" "GHC.Tuple.Prim" "ghc-prim" 'False) (C1 ('MetaCons "(,,)" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c)))) |
A tuple of four elements.
Since: ghc-prim-0.11.0
(,,,) a b c d |
Instances
Generic1 (Tuple4 a b c :: Type -> Type) Source # | |||||
Defined in GHC.Generics
| |||||
Bifoldable (Tuple4 x y) Source # | Since: base-4.10.0.0 | ||||
Defined in Data.Bifoldable | |||||
Bifoldable1 (Tuple4 x y) Source # | |||||
Defined in Data.Bifoldable1 | |||||
Bifunctor (Tuple4 x1 x2) Source # | Since: base-4.8.0.0 | ||||
Bitraversable (Tuple4 x y) Source # | Since: base-4.10.0.0 | ||||
Defined in Data.Bitraversable bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> (x, y, a, b) -> f (x, y, c, d) Source # | |||||
(Eq a, Eq b) => Eq2 (Tuple4 a b) Source # |
Since: base-4.16.0.0 | ||||
(Ord a, Ord b) => Ord2 (Tuple4 a b) Source # |
Since: base-4.16.0.0 | ||||
Defined in Data.Functor.Classes | |||||
(Read a, Read b) => Read2 (Tuple4 a b) Source # |
Since: base-4.16.0.0 | ||||
Defined in Data.Functor.Classes liftReadsPrec2 :: (Int -> ReadS a0) -> ReadS [a0] -> (Int -> ReadS b0) -> ReadS [b0] -> Int -> ReadS (a, b, a0, b0) Source # liftReadList2 :: (Int -> ReadS a0) -> ReadS [a0] -> (Int -> ReadS b0) -> ReadS [b0] -> ReadS [(a, b, a0, b0)] Source # liftReadPrec2 :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec b0 -> ReadPrec [b0] -> ReadPrec (a, b, a0, b0) Source # liftReadListPrec2 :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec b0 -> ReadPrec [b0] -> ReadPrec [(a, b, a0, b0)] Source # | |||||
(Show a, Show b) => Show2 (Tuple4 a b) Source # |
Since: base-4.16.0.0 | ||||
Defined in Data.Functor.Classes | |||||
(Eq a, Eq b, Eq c) => Eq1 (Tuple4 a b c) Source # | Since: base-4.16.0.0 | ||||
(Ord a, Ord b, Ord c) => Ord1 (Tuple4 a b c) Source # | Since: base-4.16.0.0 | ||||
Defined in Data.Functor.Classes liftCompare :: (a0 -> b0 -> Ordering) -> (a, b, c, a0) -> (a, b, c, b0) -> Ordering Source # | |||||
(Read a, Read b, Read c) => Read1 (Tuple4 a b c) Source # | Since: base-4.16.0.0 | ||||
Defined in Data.Functor.Classes liftReadsPrec :: (Int -> ReadS a0) -> ReadS [a0] -> Int -> ReadS (a, b, c, a0) Source # liftReadList :: (Int -> ReadS a0) -> ReadS [a0] -> ReadS [(a, b, c, a0)] Source # liftReadPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec (a, b, c, a0) Source # liftReadListPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec [(a, b, c, a0)] Source # | |||||
(Show a, Show b, Show c) => Show1 (Tuple4 a b c) Source # | Since: base-4.16.0.0 | ||||
(Monoid a, Monoid b, Monoid c) => Applicative (Tuple4 a b c) Source # | Since: base-4.14.0.0 | ||||
Defined in GHC.Base pure :: a0 -> (a, b, c, a0) Source # (<*>) :: (a, b, c, a0 -> b0) -> (a, b, c, a0) -> (a, b, c, b0) Source # liftA2 :: (a0 -> b0 -> c0) -> (a, b, c, a0) -> (a, b, c, b0) -> (a, b, c, c0) Source # (*>) :: (a, b, c, a0) -> (a, b, c, b0) -> (a, b, c, b0) Source # (<*) :: (a, b, c, a0) -> (a, b, c, b0) -> (a, b, c, a0) Source # | |||||
Functor (Tuple4 a b c) Source # | Since: base-4.14.0.0 | ||||
(Monoid a, Monoid b, Monoid c) => Monad (Tuple4 a b c) Source # | Since: base-4.14.0.0 | ||||
(Data a, Data b, Data c, Data d) => Data (a, b, c, d) Source # | Since: base-4.0.0.0 | ||||
Defined in Data.Data gfoldl :: (forall d0 b0. Data d0 => c0 (d0 -> b0) -> d0 -> c0 b0) -> (forall g. g -> c0 g) -> (a, b, c, d) -> c0 (a, b, c, d) Source # gunfold :: (forall b0 r. Data b0 => c0 (b0 -> r) -> c0 r) -> (forall r. r -> c0 r) -> Constr -> c0 (a, b, c, d) Source # toConstr :: (a, b, c, d) -> Constr Source # dataTypeOf :: (a, b, c, d) -> DataType Source # dataCast1 :: Typeable t => (forall d0. Data d0 => c0 (t d0)) -> Maybe (c0 (a, b, c, d)) Source # dataCast2 :: Typeable t => (forall d0 e. (Data d0, Data e) => c0 (t d0 e)) -> Maybe (c0 (a, b, c, d)) Source # gmapT :: (forall b0. Data b0 => b0 -> b0) -> (a, b, c, d) -> (a, b, c, d) Source # gmapQl :: (r -> r' -> r) -> r -> (forall d0. Data d0 => d0 -> r') -> (a, b, c, d) -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d0. Data d0 => d0 -> r') -> (a, b, c, d) -> r Source # gmapQ :: (forall d0. Data d0 => d0 -> u) -> (a, b, c, d) -> [u] Source # gmapQi :: Int -> (forall d0. Data d0 => d0 -> u) -> (a, b, c, d) -> u Source # gmapM :: Monad m => (forall d0. Data d0 => d0 -> m d0) -> (a, b, c, d) -> m (a, b, c, d) Source # gmapMp :: MonadPlus m => (forall d0. Data d0 => d0 -> m d0) -> (a, b, c, d) -> m (a, b, c, d) Source # gmapMo :: MonadPlus m => (forall d0. Data d0 => d0 -> m d0) -> (a, b, c, d) -> m (a, b, c, d) Source # | |||||
(Monoid a, Monoid b, Monoid c, Monoid d) => Monoid (a, b, c, d) Source # | Since: base-2.1 | ||||
(Semigroup a, Semigroup b, Semigroup c, Semigroup d) => Semigroup (a, b, c, d) Source # | Since: base-4.9.0.0 | ||||
(Bounded a, Bounded b, Bounded c, Bounded d) => Bounded (a, b, c, d) Source # | Since: base-2.1 | ||||
Generic (a, b, c, d) Source # | |||||
Defined in GHC.Generics
| |||||
(Ix a1, Ix a2, Ix a3, Ix a4) => Ix (a1, a2, a3, a4) Source # | Since: base-2.1 | ||||
Defined in GHC.Ix range :: ((a1, a2, a3, a4), (a1, a2, a3, a4)) -> [(a1, a2, a3, a4)] Source # index :: ((a1, a2, a3, a4), (a1, a2, a3, a4)) -> (a1, a2, a3, a4) -> Int Source # unsafeIndex :: ((a1, a2, a3, a4), (a1, a2, a3, a4)) -> (a1, a2, a3, a4) -> Int Source # inRange :: ((a1, a2, a3, a4), (a1, a2, a3, a4)) -> (a1, a2, a3, a4) -> Bool Source # rangeSize :: ((a1, a2, a3, a4), (a1, a2, a3, a4)) -> Int Source # unsafeRangeSize :: ((a1, a2, a3, a4), (a1, a2, a3, a4)) -> Int Source # | |||||
(Read a, Read b, Read c, Read d) => Read (a, b, c, d) Source # | Since: base-2.1 | ||||
(Show a, Show b, Show c, Show d) => Show (a, b, c, d) Source # | Since: base-2.1 | ||||
(Eq a, Eq b, Eq c, Eq d) => Eq (a, b, c, d) | |||||
(Ord a, Ord b, Ord c, Ord d) => Ord (a, b, c, d) | |||||
Defined in GHC.Classes compare :: (a, b, c, d) -> (a, b, c, d) -> Ordering Source # (<) :: (a, b, c, d) -> (a, b, c, d) -> Bool Source # (<=) :: (a, b, c, d) -> (a, b, c, d) -> Bool Source # (>) :: (a, b, c, d) -> (a, b, c, d) -> Bool Source # (>=) :: (a, b, c, d) -> (a, b, c, d) -> Bool Source # max :: (a, b, c, d) -> (a, b, c, d) -> (a, b, c, d) Source # min :: (a, b, c, d) -> (a, b, c, d) -> (a, b, c, d) Source # | |||||
type Rep1 (Tuple4 a b c :: Type -> Type) Source # | Since: base-4.6.0.0 | ||||
Defined in GHC.Generics type Rep1 (Tuple4 a b c :: Type -> Type) = D1 ('MetaData "Tuple4" "GHC.Tuple.Prim" "ghc-prim" 'False) (C1 ('MetaCons "(,,,)" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))) | |||||
type Rep (a, b, c, d) Source # | Since: base-4.6.0.0 | ||||
Defined in GHC.Generics type Rep (a, b, c, d) = D1 ('MetaData "Tuple4" "GHC.Tuple.Prim" "ghc-prim" 'False) (C1 ('MetaCons "(,,,)" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 d)))) |
data Tuple5 a b c d e Source #
A tuple of five elements.
Since: ghc-prim-0.11.0
(,,,,) a b c d e |
Instances
Generic1 (Tuple5 a b c d :: Type -> Type) Source # | |||||
Defined in GHC.Generics
| |||||
Bifoldable (Tuple5 x y z) Source # | Since: base-4.10.0.0 | ||||
Defined in Data.Bifoldable | |||||
Bifoldable1 (Tuple5 x y z) Source # | |||||
Defined in Data.Bifoldable1 | |||||
Bifunctor (Tuple5 x1 x2 x3) Source # | Since: base-4.8.0.0 | ||||
Bitraversable (Tuple5 x y z) Source # | Since: base-4.10.0.0 | ||||
Defined in Data.Bitraversable bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> (x, y, z, a, b) -> f (x, y, z, c, d) Source # | |||||
Functor (Tuple5 a b c d) Source # | Since: base-4.18.0.0 | ||||
(Data a, Data b, Data c, Data d, Data e) => Data (a, b, c, d, e) Source # | Since: base-4.0.0.0 | ||||
Defined in Data.Data gfoldl :: (forall d0 b0. Data d0 => c0 (d0 -> b0) -> d0 -> c0 b0) -> (forall g. g -> c0 g) -> (a, b, c, d, e) -> c0 (a, b, c, d, e) Source # gunfold :: (forall b0 r. Data b0 => c0 (b0 -> r) -> c0 r) -> (forall r. r -> c0 r) -> Constr -> c0 (a, b, c, d, e) Source # toConstr :: (a, b, c, d, e) -> Constr Source # dataTypeOf :: (a, b, c, d, e) -> DataType Source # dataCast1 :: Typeable t => (forall d0. Data d0 => c0 (t d0)) -> Maybe (c0 (a, b, c, d, e)) Source # dataCast2 :: Typeable t => (forall d0 e0. (Data d0, Data e0) => c0 (t d0 e0)) -> Maybe (c0 (a, b, c, d, e)) Source # gmapT :: (forall b0. Data b0 => b0 -> b0) -> (a, b, c, d, e) -> (a, b, c, d, e) Source # gmapQl :: (r -> r' -> r) -> r -> (forall d0. Data d0 => d0 -> r') -> (a, b, c, d, e) -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d0. Data d0 => d0 -> r') -> (a, b, c, d, e) -> r Source # gmapQ :: (forall d0. Data d0 => d0 -> u) -> (a, b, c, d, e) -> [u] Source # gmapQi :: Int -> (forall d0. Data d0 => d0 -> u) -> (a, b, c, d, e) -> u Source # gmapM :: Monad m => (forall d0. Data d0 => d0 -> m d0) -> (a, b, c, d, e) -> m (a, b, c, d, e) Source # gmapMp :: MonadPlus m => (forall d0. Data d0 => d0 -> m d0) -> (a, b, c, d, e) -> m (a, b, c, d, e) Source # gmapMo :: MonadPlus m => (forall d0. Data d0 => d0 -> m d0) -> (a, b, c, d, e) -> m (a, b, c, d, e) Source # | |||||
(Monoid a, Monoid b, Monoid c, Monoid d, Monoid e) => Monoid (a, b, c, d, e) Source # | Since: base-2.1 | ||||
(Semigroup a, Semigroup b, Semigroup c, Semigroup d, Semigroup e) => Semigroup (a, b, c, d, e) Source # | Since: base-4.9.0.0 | ||||
(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e) => Bounded (a, b, c, d, e) Source # | Since: base-2.1 | ||||
Generic (a, b, c, d, e) Source # | |||||
Defined in GHC.Generics
| |||||
(Ix a1, Ix a2, Ix a3, Ix a4, Ix a5) => Ix (a1, a2, a3, a4, a5) Source # | Since: base-2.1 | ||||
Defined in GHC.Ix range :: ((a1, a2, a3, a4, a5), (a1, a2, a3, a4, a5)) -> [(a1, a2, a3, a4, a5)] Source # index :: ((a1, a2, a3, a4, a5), (a1, a2, a3, a4, a5)) -> (a1, a2, a3, a4, a5) -> Int Source # unsafeIndex :: ((a1, a2, a3, a4, a5), (a1, a2, a3, a4, a5)) -> (a1, a2, a3, a4, a5) -> Int Source # inRange :: ((a1, a2, a3, a4, a5), (a1, a2, a3, a4, a5)) -> (a1, a2, a3, a4, a5) -> Bool Source # rangeSize :: ((a1, a2, a3, a4, a5), (a1, a2, a3, a4, a5)) -> Int Source # unsafeRangeSize :: ((a1, a2, a3, a4, a5), (a1, a2, a3, a4, a5)) -> Int Source # | |||||
(Read a, Read b, Read c, Read d, Read e) => Read (a, b, c, d, e) Source # | Since: base-2.1 | ||||
(Show a, Show b, Show c, Show d, Show e) => Show (a, b, c, d, e) Source # | Since: base-2.1 | ||||
(Eq a, Eq b, Eq c, Eq d, Eq e) => Eq (a, b, c, d, e) | |||||
(Ord a, Ord b, Ord c, Ord d, Ord e) => Ord (a, b, c, d, e) | |||||
Defined in GHC.Classes compare :: (a, b, c, d, e) -> (a, b, c, d, e) -> Ordering Source # (<) :: (a, b, c, d, e) -> (a, b, c, d, e) -> Bool Source # (<=) :: (a, b, c, d, e) -> (a, b, c, d, e) -> Bool Source # (>) :: (a, b, c, d, e) -> (a, b, c, d, e) -> Bool Source # (>=) :: (a, b, c, d, e) -> (a, b, c, d, e) -> Bool Source # max :: (a, b, c, d, e) -> (a, b, c, d, e) -> (a, b, c, d, e) Source # min :: (a, b, c, d, e) -> (a, b, c, d, e) -> (a, b, c, d, e) Source # | |||||
type Rep1 (Tuple5 a b c d :: Type -> Type) Source # | Since: base-4.6.0.0 | ||||
Defined in GHC.Generics type Rep1 (Tuple5 a b c d :: Type -> Type) = D1 ('MetaData "Tuple5" "GHC.Tuple.Prim" "ghc-prim" 'False) (C1 ('MetaCons "(,,,,)" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 d) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1)))) | |||||
type Rep (a, b, c, d, e) Source # | Since: base-4.6.0.0 | ||||
Defined in GHC.Generics type Rep (a, b, c, d, e) = D1 ('MetaData "Tuple5" "GHC.Tuple.Prim" "ghc-prim" 'False) (C1 ('MetaCons "(,,,,)" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 d) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 e))))) |
data Tuple6 a b c d e f Source #
A tuple of six elements.
Since: ghc-prim-0.11.0
(,,,,,) a b c d e f |
Instances
Generic1 (Tuple6 a b c d e :: Type -> Type) Source # | |||||
Defined in GHC.Generics
| |||||
Bifoldable (Tuple6 x y z w) Source # | Since: base-4.10.0.0 | ||||
Defined in Data.Bifoldable | |||||
Bifunctor (Tuple6 x1 x2 x3 x4) Source # | Since: base-4.8.0.0 | ||||
Bitraversable (Tuple6 x y z w) Source # | Since: base-4.10.0.0 | ||||
Defined in Data.Bitraversable bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> (x, y, z, w, a, b) -> f (x, y, z, w, c, d) Source # | |||||
Functor (Tuple6 a b c d e) Source # | Since: base-4.18.0.0 | ||||
(Data a, Data b, Data c, Data d, Data e, Data f) => Data (a, b, c, d, e, f) Source # | Since: base-4.0.0.0 | ||||
Defined in Data.Data gfoldl :: (forall d0 b0. Data d0 => c0 (d0 -> b0) -> d0 -> c0 b0) -> (forall g. g -> c0 g) -> (a, b, c, d, e, f) -> c0 (a, b, c, d, e, f) Source # gunfold :: (forall b0 r. Data b0 => c0 (b0 -> r) -> c0 r) -> (forall r. r -> c0 r) -> Constr -> c0 (a, b, c, d, e, f) Source # toConstr :: (a, b, c, d, e, f) -> Constr Source # dataTypeOf :: (a, b, c, d, e, f) -> DataType Source # dataCast1 :: Typeable t => (forall d0. Data d0 => c0 (t d0)) -> Maybe (c0 (a, b, c, d, e, f)) Source # dataCast2 :: Typeable t => (forall d0 e0. (Data d0, Data e0) => c0 (t d0 e0)) -> Maybe (c0 (a, b, c, d, e, f)) Source # gmapT :: (forall b0. Data b0 => b0 -> b0) -> (a, b, c, d, e, f) -> (a, b, c, d, e, f) Source # gmapQl :: (r -> r' -> r) -> r -> (forall d0. Data d0 => d0 -> r') -> (a, b, c, d, e, f) -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d0. Data d0 => d0 -> r') -> (a, b, c, d, e, f) -> r Source # gmapQ :: (forall d0. Data d0 => d0 -> u) -> (a, b, c, d, e, f) -> [u] Source # gmapQi :: Int -> (forall d0. Data d0 => d0 -> u) -> (a, b, c, d, e, f) -> u Source # gmapM :: Monad m => (forall d0. Data d0 => d0 -> m d0) -> (a, b, c, d, e, f) -> m (a, b, c, d, e, f) Source # gmapMp :: MonadPlus m => (forall d0. Data d0 => d0 -> m d0) -> (a, b, c, d, e, f) -> m (a, b, c, d, e, f) Source # gmapMo :: MonadPlus m => (forall d0. Data d0 => d0 -> m d0) -> (a, b, c, d, e, f) -> m (a, b, c, d, e, f) Source # | |||||
(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f) => Bounded (a, b, c, d, e, f) Source # | Since: base-2.1 | ||||
Generic (a, b, c, d, e, f) Source # | |||||
Defined in GHC.Generics
| |||||
(Ix a1, Ix a2, Ix a3, Ix a4, Ix a5, Ix a6) => Ix (a1, a2, a3, a4, a5, a6) Source # | Since: base-4.15.0.0 | ||||
Defined in GHC.Ix range :: ((a1, a2, a3, a4, a5, a6), (a1, a2, a3, a4, a5, a6)) -> [(a1, a2, a3, a4, a5, a6)] Source # index :: ((a1, a2, a3, a4, a5, a6), (a1, a2, a3, a4, a5, a6)) -> (a1, a2, a3, a4, a5, a6) -> Int Source # unsafeIndex :: ((a1, a2, a3, a4, a5, a6), (a1, a2, a3, a4, a5, a6)) -> (a1, a2, a3, a4, a5, a6) -> Int Source # inRange :: ((a1, a2, a3, a4, a5, a6), (a1, a2, a3, a4, a5, a6)) -> (a1, a2, a3, a4, a5, a6) -> Bool Source # rangeSize :: ((a1, a2, a3, a4, a5, a6), (a1, a2, a3, a4, a5, a6)) -> Int Source # unsafeRangeSize :: ((a1, a2, a3, a4, a5, a6), (a1, a2, a3, a4, a5, a6)) -> Int Source # | |||||
(Read a, Read b, Read c, Read d, Read e, Read f) => Read (a, b, c, d, e, f) Source # | Since: base-2.1 | ||||
(Show a, Show b, Show c, Show d, Show e, Show f) => Show (a, b, c, d, e, f) Source # | Since: base-2.1 | ||||
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f) => Eq (a, b, c, d, e, f) | |||||
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f) => Ord (a, b, c, d, e, f) | |||||
Defined in GHC.Classes compare :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> Ordering Source # (<) :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> Bool Source # (<=) :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> Bool Source # (>) :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> Bool Source # (>=) :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> Bool Source # max :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> (a, b, c, d, e, f) Source # min :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> (a, b, c, d, e, f) Source # | |||||
type Rep1 (Tuple6 a b c d e :: Type -> Type) Source # | Since: base-4.6.0.0 | ||||
Defined in GHC.Generics type Rep1 (Tuple6 a b c d e :: Type -> Type) = D1 ('MetaData "Tuple6" "GHC.Tuple.Prim" "ghc-prim" 'False) (C1 ('MetaCons "(,,,,,)" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 d) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 e) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1)))) | |||||
type Rep (a, b, c, d, e, f) Source # | Since: base-4.6.0.0 | ||||
Defined in GHC.Generics type Rep (a, b, c, d, e, f) = D1 ('MetaData "Tuple6" "GHC.Tuple.Prim" "ghc-prim" 'False) (C1 ('MetaCons "(,,,,,)" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 d) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 e) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 f))))) |
data Tuple7 a b c d e f g Source #
A tuple of seven elements.
Since: ghc-prim-0.11.0
(,,,,,,) a b c d e f g |
Instances
Generic1 (Tuple7 a b c d e f :: Type -> Type) Source # | |||||
Defined in GHC.Generics | |||||
Bifoldable (Tuple7 x y z w v) Source # | Since: base-4.10.0.0 | ||||
Defined in Data.Bifoldable bifold :: Monoid m => (x, y, z, w, v, m, m) -> m Source # bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> (x, y, z, w, v, a, b) -> m Source # bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> (x, y, z, w, v, a, b) -> c Source # bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> (x, y, z, w, v, a, b) -> c Source # | |||||
Bifunctor (Tuple7 x1 x2 x3 x4 x5) Source # | Since: base-4.8.0.0 | ||||
Bitraversable (Tuple7 x y z w v) Source # | Since: base-4.10.0.0 | ||||
Defined in Data.Bitraversable bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> (x, y, z, w, v, a, b) -> f (x, y, z, w, v, c, d) Source # | |||||
Functor (Tuple7 a b c d e f) Source # | Since: base-4.18.0.0 | ||||
(Data a, Data b, Data c, Data d, Data e, Data f, Data g) => Data (a, b, c, d, e, f, g) Source # | Since: base-4.0.0.0 | ||||
Defined in Data.Data gfoldl :: (forall d0 b0. Data d0 => c0 (d0 -> b0) -> d0 -> c0 b0) -> (forall g0. g0 -> c0 g0) -> (a, b, c, d, e, f, g) -> c0 (a, b, c, d, e, f, g) Source # gunfold :: (forall b0 r. Data b0 => c0 (b0 -> r) -> c0 r) -> (forall r. r -> c0 r) -> Constr -> c0 (a, b, c, d, e, f, g) Source # toConstr :: (a, b, c, d, e, f, g) -> Constr Source # dataTypeOf :: (a, b, c, d, e, f, g) -> DataType Source # dataCast1 :: Typeable t => (forall d0. Data d0 => c0 (t d0)) -> Maybe (c0 (a, b, c, d, e, f, g)) Source # dataCast2 :: Typeable t => (forall d0 e0. (Data d0, Data e0) => c0 (t d0 e0)) -> Maybe (c0 (a, b, c, d, e, f, g)) Source # gmapT :: (forall b0. Data b0 => b0 -> b0) -> (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) Source # gmapQl :: (r -> r' -> r) -> r -> (forall d0. Data d0 => d0 -> r') -> (a, b, c, d, e, f, g) -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d0. Data d0 => d0 -> r') -> (a, b, c, d, e, f, g) -> r Source # gmapQ :: (forall d0. Data d0 => d0 -> u) -> (a, b, c, d, e, f, g) -> [u] Source # gmapQi :: Int -> (forall d0. Data d0 => d0 -> u) -> (a, b, c, d, e, f, g) -> u Source # gmapM :: Monad m => (forall d0. Data d0 => d0 -> m d0) -> (a, b, c, d, e, f, g) -> m (a, b, c, d, e, f, g) Source # gmapMp :: MonadPlus m => (forall d0. Data d0 => d0 -> m d0) -> (a, b, c, d, e, f, g) -> m (a, b, c, d, e, f, g) Source # gmapMo :: MonadPlus m => (forall d0. Data d0 => d0 -> m d0) -> (a, b, c, d, e, f, g) -> m (a, b, c, d, e, f, g) Source # | |||||
(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g) => Bounded (a, b, c, d, e, f, g) Source # | Since: base-2.1 | ||||
Generic (a, b, c, d, e, f, g) Source # | |||||
Defined in GHC.Generics
| |||||
(Ix a1, Ix a2, Ix a3, Ix a4, Ix a5, Ix a6, Ix a7) => Ix (a1, a2, a3, a4, a5, a6, a7) Source # | Since: base-4.15.0.0 | ||||
Defined in GHC.Ix range :: ((a1, a2, a3, a4, a5, a6, a7), (a1, a2, a3, a4, a5, a6, a7)) -> [(a1, a2, a3, a4, a5, a6, a7)] Source # index :: ((a1, a2, a3, a4, a5, a6, a7), (a1, a2, a3, a4, a5, a6, a7)) -> (a1, a2, a3, a4, a5, a6, a7) -> Int Source # unsafeIndex :: ((a1, a2, a3, a4, a5, a6, a7), (a1, a2, a3, a4, a5, a6, a7)) -> (a1, a2, a3, a4, a5, a6, a7) -> Int Source # inRange :: ((a1, a2, a3, a4, a5, a6, a7), (a1, a2, a3, a4, a5, a6, a7)) -> (a1, a2, a3, a4, a5, a6, a7) -> Bool Source # rangeSize :: ((a1, a2, a3, a4, a5, a6, a7), (a1, a2, a3, a4, a5, a6, a7)) -> Int Source # unsafeRangeSize :: ((a1, a2, a3, a4, a5, a6, a7), (a1, a2, a3, a4, a5, a6, a7)) -> Int Source # | |||||
(Read a, Read b, Read c, Read d, Read e, Read f, Read g) => Read (a, b, c, d, e, f, g) Source # | Since: base-2.1 | ||||
(Show a, Show b, Show c, Show d, Show e, Show f, Show g) => Show (a, b, c, d, e, f, g) Source # | Since: base-2.1 | ||||
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g) => Eq (a, b, c, d, e, f, g) | |||||
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g) => Ord (a, b, c, d, e, f, g) | |||||
Defined in GHC.Classes compare :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> Ordering Source # (<) :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> Bool Source # (<=) :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> Bool Source # (>) :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> Bool Source # (>=) :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> Bool Source # max :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) Source # min :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) Source # | |||||
type Rep1 (Tuple7 a b c d e f :: Type -> Type) Source # | Since: base-4.6.0.0 | ||||
Defined in GHC.Generics type Rep1 (Tuple7 a b c d e f :: Type -> Type) = D1 ('MetaData "Tuple7" "GHC.Tuple.Prim" "ghc-prim" 'False) (C1 ('MetaCons "(,,,,,,)" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 d) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 e)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 f) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1)))) | |||||
type Rep (a, b, c, d, e, f, g) Source # | Since: base-4.6.0.0 | ||||
Defined in GHC.Generics type Rep (a, b, c, d, e, f, g) = D1 ('MetaData "Tuple7" "GHC.Tuple.Prim" "ghc-prim" 'False) (C1 ('MetaCons "(,,,,,,)" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 d) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 e)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 f) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 g))))) |
data Tuple8 a b c d e f g h Source #
A tuple of eight elements.
Since: ghc-prim-0.11.0
(,,,,,,,) a b c d e f g h |
Instances
data Tuple9 a b c d e f g h i Source #
A tuple of nine elements.
Since: ghc-prim-0.11.0
(,,,,,,,,) a b c d e f g h i |
Instances
Generic1 (Tuple9 a b c d e f g h :: Type -> Type) Source # | |||||
Defined in GHC.Generics
| |||||
(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g, Bounded h, Bounded i) => Bounded (a, b, c, d, e, f, g, h, i) Source # | Since: base-2.1 | ||||
Generic (a, b, c, d, e, f, g, h, i) Source # | |||||
Defined in GHC.Generics
| |||||
(Ix a1, Ix a2, Ix a3, Ix a4, Ix a5, Ix a6, Ix a7, Ix a8, Ix a9) => Ix (a1, a2, a3, a4, a5, a6, a7, a8, a9) Source # | Since: base-4.15.0.0 | ||||
Defined in GHC.Ix range :: ((a1, a2, a3, a4, a5, a6, a7, a8, a9), (a1, a2, a3, a4, a5, a6, a7, a8, a9)) -> [(a1, a2, a3, a4, a5, a6, a7, a8, a9)] Source # index :: ((a1, a2, a3, a4, a5, a6, a7, a8, a9), (a1, a2, a3, a4, a5, a6, a7, a8, a9)) -> (a1, a2, a3, a4, a5, a6, a7, a8, a9) -> Int Source # unsafeIndex :: ((a1, a2, a3, a4, a5, a6, a7, a8, a9), (a1, a2, a3, a4, a5, a6, a7, a8, a9)) -> (a1, a2, a3, a4, a5, a6, a7, a8, a9) -> Int Source # inRange :: ((a1, a2, a3, a4, a5, a6, a7, a8, a9), (a1, a2, a3, a4, a5, a6, a7, a8, a9)) -> (a1, a2, a3, a4, a5, a6, a7, a8, a9) -> Bool Source # rangeSize :: ((a1, a2, a3, a4, a5, a6, a7, a8, a9), (a1, a2, a3, a4, a5, a6, a7, a8, a9)) -> Int Source # unsafeRangeSize :: ((a1, a2, a3, a4, a5, a6, a7, a8, a9), (a1, a2, a3, a4, a5, a6, a7, a8, a9)) -> Int Source # | |||||
(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h, Read i) => Read (a, b, c, d, e, f, g, h, i) Source # | Since: base-2.1 | ||||
(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i) => Show (a, b, c, d, e, f, g, h, i) Source # | Since: base-2.1 | ||||
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i) => Eq (a, b, c, d, e, f, g, h, i) | |||||
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i) => Ord (a, b, c, d, e, f, g, h, i) | |||||
Defined in GHC.Classes compare :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> Ordering Source # (<) :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> Bool Source # (<=) :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> Bool Source # (>) :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> Bool Source # (>=) :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> Bool Source # max :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) Source # min :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) Source # | |||||
type Rep1 (Tuple9 a b c d e f g h :: Type -> Type) Source # | Since: base-4.16.0.0 | ||||
Defined in GHC.Generics type Rep1 (Tuple9 a b c d e f g h :: Type -> Type) = D1 ('MetaData "Tuple9" "GHC.Tuple.Prim" "ghc-prim" 'False) (C1 ('MetaCons "(,,,,,,,,)" 'PrefixI 'False) (((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 d))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 e) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 f)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 g) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 h) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))))) | |||||
type Rep (a, b, c, d, e, f, g, h, i) Source # | Since: base-4.16.0.0 | ||||
Defined in GHC.Generics type Rep (a, b, c, d, e, f, g, h, i) = D1 ('MetaData "Tuple9" "GHC.Tuple.Prim" "ghc-prim" 'False) (C1 ('MetaCons "(,,,,,,,,)" 'PrefixI 'False) (((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 d))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 e) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 f)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 g) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 h) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 i)))))) |
data Tuple10 a b c d e f g h i j Source #
A tuple of ten elements.
Since: ghc-prim-0.11.0
(,,,,,,,,,) a b c d e f g h i j |
Instances
Generic1 (Tuple10 a b c d e f g h i :: Type -> Type) Source # | |||||
Defined in GHC.Generics
| |||||
(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g, Bounded h, Bounded i, Bounded j) => Bounded (a, b, c, d, e, f, g, h, i, j) Source # | Since: base-2.1 | ||||
Generic (a, b, c, d, e, f, g, h, i, j) Source # | |||||
Defined in GHC.Generics
| |||||
(Ix a1, Ix a2, Ix a3, Ix a4, Ix a5, Ix a6, Ix a7, Ix a8, Ix a9, Ix aA) => Ix (a1, a2, a3, a4, a5, a6, a7, a8, a9, aA) Source # | Since: base-4.15.0.0 | ||||
Defined in GHC.Ix range :: ((a1, a2, a3, a4, a5, a6, a7, a8, a9, aA), (a1, a2, a3, a4, a5, a6, a7, a8, a9, aA)) -> [(a1, a2, a3, a4, a5, a6, a7, a8, a9, aA)] Source # index :: ((a1, a2, a3, a4, a5, a6, a7, a8, a9, aA), (a1, a2, a3, a4, a5, a6, a7, a8, a9, aA)) -> (a1, a2, a3, a4, a5, a6, a7, a8, a9, aA) -> Int Source # unsafeIndex :: ((a1, a2, a3, a4, a5, a6, a7, a8, a9, aA), (a1, a2, a3, a4, a5, a6, a7, a8, a9, aA)) -> (a1, a2, a3, a4, a5, a6, a7, a8, a9, aA) -> Int Source # inRange :: ((a1, a2, a3, a4, a5, a6, a7, a8, a9, aA), (a1, a2, a3, a4, a5, a6, a7, a8, a9, aA)) -> (a1, a2, a3, a4, a5, a6, a7, a8, a9, aA) -> Bool Source # rangeSize :: ((a1, a2, a3, a4, a5, a6, a7, a8, a9, aA), (a1, a2, a3, a4, a5, a6, a7, a8, a9, aA)) -> Int Source # unsafeRangeSize :: ((a1, a2, a3, a4, a5, a6, a7, a8, a9, aA), (a1, a2, a3, a4, a5, a6, a7, a8, a9, aA)) -> Int Source # | |||||
(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h, Read i, Read j) => Read (a, b, c, d, e, f, g, h, i, j) Source # | Since: base-2.1 | ||||
(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j) => Show (a, b, c, d, e, f, g, h, i, j) Source # | Since: base-2.1 | ||||
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j) => Eq (a, b, c, d, e, f, g, h, i, j) | |||||
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j) => Ord (a, b, c, d, e, f, g, h, i, j) | |||||
Defined in GHC.Classes compare :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> Ordering Source # (<) :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> Bool Source # (<=) :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> Bool Source # (>) :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> Bool Source # (>=) :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> Bool Source # max :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) Source # min :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) Source # | |||||
type Rep1 (Tuple10 a b c d e f g h i :: Type -> Type) Source # | Since: base-4.16.0.0 | ||||
Defined in GHC.Generics type Rep1 (Tuple10 a b c d e f g h i :: Type -> Type) = D1 ('MetaData "Tuple10" "GHC.Tuple.Prim" "ghc-prim" 'False) (C1 ('MetaCons "(,,,,,,,,,)" 'PrefixI 'False) (((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 d) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 e)))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 f) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 g)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 h) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 i) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))))) | |||||
type Rep (a, b, c, d, e, f, g, h, i, j) Source # | Since: base-4.16.0.0 | ||||
Defined in GHC.Generics type Rep (a, b, c, d, e, f, g, h, i, j) = D1 ('MetaData "Tuple10" "GHC.Tuple.Prim" "ghc-prim" 'False) (C1 ('MetaCons "(,,,,,,,,,)" 'PrefixI 'False) (((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 d) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 e)))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 f) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 g)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 h) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 i) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 j)))))) |
data Tuple11 a b c d e f g h i j k Source #
A tuple of eleven elements.
Since: ghc-prim-0.11.0
(,,,,,,,,,,) a b c d e f g h i j k |
Instances
Generic1 (Tuple11 a b c d e f g h i j :: Type -> Type) Source # | |||||
Defined in GHC.Generics
| |||||
(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g, Bounded h, Bounded i, Bounded j, Bounded k) => Bounded (a, b, c, d, e, f, g, h, i, j, k) Source # | Since: base-2.1 | ||||
Generic (a, b, c, d, e, f, g, h, i, j, k) Source # | |||||
Defined in GHC.Generics
| |||||
(Ix a1, Ix a2, Ix a3, Ix a4, Ix a5, Ix a6, Ix a7, Ix a8, Ix a9, Ix aA, Ix aB) => Ix (a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB) Source # | Since: base-4.15.0.0 | ||||
Defined in GHC.Ix range :: ((a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB), (a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB)) -> [(a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB)] Source # index :: ((a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB), (a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB)) -> (a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB) -> Int Source # unsafeIndex :: ((a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB), (a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB)) -> (a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB) -> Int Source # inRange :: ((a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB), (a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB)) -> (a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB) -> Bool Source # rangeSize :: ((a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB), (a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB)) -> Int Source # unsafeRangeSize :: ((a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB), (a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB)) -> Int Source # | |||||
(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h, Read i, Read j, Read k) => Read (a, b, c, d, e, f, g, h, i, j, k) Source # | Since: base-2.1 | ||||
(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k) => Show (a, b, c, d, e, f, g, h, i, j, k) Source # | Since: base-2.1 | ||||
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k) => Eq (a, b, c, d, e, f, g, h, i, j, k) | |||||
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k) => Ord (a, b, c, d, e, f, g, h, i, j, k) | |||||
Defined in GHC.Classes compare :: (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> Ordering Source # (<) :: (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> Bool Source # (<=) :: (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> Bool Source # (>) :: (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> Bool Source # (>=) :: (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> Bool Source # max :: (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) Source # min :: (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) Source # | |||||
type Rep1 (Tuple11 a b c d e f g h i j :: Type -> Type) Source # | Since: base-4.16.0.0 | ||||
Defined in GHC.Generics type Rep1 (Tuple11 a b c d e f g h i j :: Type -> Type) = D1 ('MetaData "Tuple11" "GHC.Tuple.Prim" "ghc-prim" 'False) (C1 ('MetaCons "(,,,,,,,,,,)" 'PrefixI 'False) (((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 d) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 e)))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 f) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 g) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 h))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 i) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 j) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))))) | |||||
type Rep (a, b, c, d, e, f, g, h, i, j, k) Source # | Since: base-4.16.0.0 | ||||
Defined in GHC.Generics type Rep (a, b, c, d, e, f, g, h, i, j, k) = D1 ('MetaData "Tuple11" "GHC.Tuple.Prim" "ghc-prim" 'False) (C1 ('MetaCons "(,,,,,,,,,,)" 'PrefixI 'False) (((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 d) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 e)))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 f) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 g) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 h))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 i) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 j) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 k)))))) |
data Tuple12 a b c d e f g h i j k l Source #
A tuple of twelve elements.
Since: ghc-prim-0.11.0
(,,,,,,,,,,,) a b c d e f g h i j k l |
Instances
Generic1 (Tuple12 a b c d e f g h i j k :: Type -> Type) Source # | |||||
Defined in GHC.Generics
| |||||
(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g, Bounded h, Bounded i, Bounded j, Bounded k, Bounded l) => Bounded (a, b, c, d, e, f, g, h, i, j, k, l) Source # | Since: base-2.1 | ||||
Generic (a, b, c, d, e, f, g, h, i, j, k, l) Source # | |||||
Defined in GHC.Generics
| |||||
(Ix a1, Ix a2, Ix a3, Ix a4, Ix a5, Ix a6, Ix a7, Ix a8, Ix a9, Ix aA, Ix aB, Ix aC) => Ix (a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC) Source # | Since: base-4.15.0.0 | ||||
Defined in GHC.Ix range :: ((a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC), (a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC)) -> [(a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC)] Source # index :: ((a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC), (a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC)) -> (a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC) -> Int Source # unsafeIndex :: ((a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC), (a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC)) -> (a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC) -> Int Source # inRange :: ((a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC), (a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC)) -> (a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC) -> Bool Source # rangeSize :: ((a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC), (a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC)) -> Int Source # unsafeRangeSize :: ((a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC), (a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC)) -> Int Source # | |||||
(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h, Read i, Read j, Read k, Read l) => Read (a, b, c, d, e, f, g, h, i, j, k, l) Source # | Since: base-2.1 | ||||
(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k, Show l) => Show (a, b, c, d, e, f, g, h, i, j, k, l) Source # | Since: base-2.1 | ||||
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l) => Eq (a, b, c, d, e, f, g, h, i, j, k, l) | |||||
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k, Ord l) => Ord (a, b, c, d, e, f, g, h, i, j, k, l) | |||||
Defined in GHC.Classes compare :: (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> Ordering Source # (<) :: (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> Bool Source # (<=) :: (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> Bool Source # (>) :: (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> Bool Source # (>=) :: (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> Bool Source # max :: (a, b, c, d, e, f, g, h, i, j, k, 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 # min :: (a, b, c, d, e, f, g, h, i, j, k, 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 # | |||||
type Rep1 (Tuple12 a b c d e f g h i j k :: Type -> Type) Source # | Since: base-4.16.0.0 | ||||
Defined in GHC.Generics type Rep1 (Tuple12 a b c d e f g h i j k :: Type -> Type) = D1 ('MetaData "Tuple12" "GHC.Tuple.Prim" "ghc-prim" 'False) (C1 ('MetaCons "(,,,,,,,,,,,)" 'PrefixI 'False) (((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 d) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 e) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 f)))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 g) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 h) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 i))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 j) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 k) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))))) | |||||
type Rep (a, b, c, d, e, f, g, h, i, j, k, l) Source # | Since: base-4.16.0.0 | ||||
Defined in GHC.Generics type Rep (a, b, c, d, e, f, g, h, i, j, k, l) = D1 ('MetaData "Tuple12" "GHC.Tuple.Prim" "ghc-prim" 'False) (C1 ('MetaCons "(,,,,,,,,,,,)" 'PrefixI 'False) (((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 d) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 e) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 f)))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 g) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 h) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 i))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 j) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 k) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l)))))) |
data Tuple13 a b c d e f g h i j k l m Source #
A tuple of 13 elements.
Since: ghc-prim-0.11.0
(,,,,,,,,,,,,) a b c d e f g h i j k l m |
Instances
Generic1 (Tuple13 a b c d e f g h i j k l :: Type -> Type) Source # | |||||
Defined in GHC.Generics
| |||||
(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g, Bounded h, Bounded i, Bounded j, Bounded k, Bounded l, Bounded m) => Bounded (a, b, c, d, e, f, g, h, i, j, k, l, m) Source # | Since: base-2.1 | ||||
Generic (a, b, c, d, e, f, g, h, i, j, k, l, m) Source # | |||||
Defined in GHC.Generics
| |||||
(Ix a1, Ix a2, Ix a3, Ix a4, Ix a5, Ix a6, Ix a7, Ix a8, Ix a9, Ix aA, Ix aB, Ix aC, Ix aD) => Ix (a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC, aD) Source # | Since: base-4.15.0.0 | ||||
Defined in GHC.Ix range :: ((a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC, aD), (a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC, aD)) -> [(a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC, aD)] Source # index :: ((a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC, aD), (a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC, aD)) -> (a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC, aD) -> Int Source # unsafeIndex :: ((a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC, aD), (a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC, aD)) -> (a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC, aD) -> Int Source # inRange :: ((a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC, aD), (a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC, aD)) -> (a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC, aD) -> Bool Source # rangeSize :: ((a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC, aD), (a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC, aD)) -> Int Source # unsafeRangeSize :: ((a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC, aD), (a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC, aD)) -> Int Source # | |||||
(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h, Read i, Read j, Read k, Read l, Read m) => Read (a, b, c, d, e, f, g, h, i, j, k, l, m) Source # | Since: base-2.1 | ||||
Defined in GHC.Read | |||||
(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k, Show l, Show m) => Show (a, b, c, d, e, f, g, h, i, j, k, l, m) Source # | Since: base-2.1 | ||||
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l, Eq m) => Eq (a, b, c, d, e, f, g, h, i, j, k, l, m) | |||||
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k, Ord l, Ord m) => Ord (a, b, c, d, e, f, g, h, i, j, k, l, m) | |||||
Defined in GHC.Classes compare :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Ordering Source # (<) :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Bool Source # (<=) :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Bool Source # (>) :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Bool Source # (>=) :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Bool Source # max :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) Source # min :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) Source # | |||||
type Rep1 (Tuple13 a b c d e f g h i j k l :: Type -> Type) Source # | Since: base-4.16.0.0 | ||||
Defined in GHC.Generics type Rep1 (Tuple13 a b c d e f g h i j k l :: Type -> Type) = D1 ('MetaData "Tuple13" "GHC.Tuple.Prim" "ghc-prim" 'False) (C1 ('MetaCons "(,,,,,,,,,,,,)" 'PrefixI 'False) (((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 d) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 e) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 f)))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 g) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 h) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 i))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 j) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 k)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))))) | |||||
type Rep (a, b, c, d, e, f, g, h, i, j, k, l, m) Source # | Since: base-4.16.0.0 | ||||
Defined in GHC.Generics type Rep (a, b, c, d, e, f, g, h, i, j, k, l, m) = D1 ('MetaData "Tuple13" "GHC.Tuple.Prim" "ghc-prim" 'False) (C1 ('MetaCons "(,,,,,,,,,,,,)" 'PrefixI 'False) (((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 d) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 e) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 f)))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 g) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 h) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 i))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 j) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 k)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 m)))))) |
data Tuple14 a b c d e f g h i j k l m n Source #
A tuple of 14 elements.
Since: ghc-prim-0.11.0
(,,,,,,,,,,,,,) a b c d e f g h i j k l m n |
Instances
Generic1 (Tuple14 a b c d e f g h i j k l m :: Type -> Type) Source # | |||||
Defined in GHC.Generics
| |||||
(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g, Bounded h, Bounded i, Bounded j, Bounded k, Bounded l, Bounded m, Bounded n) => Bounded (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source # | Since: base-2.1 | ||||
Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source # | |||||
Defined in GHC.Generics
| |||||
(Ix a1, Ix a2, Ix a3, Ix a4, Ix a5, Ix a6, Ix a7, Ix a8, Ix a9, Ix aA, Ix aB, Ix aC, Ix aD, Ix aE) => Ix (a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC, aD, aE) Source # | Since: base-4.15.0.0 | ||||
Defined in GHC.Ix range :: ((a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC, aD, aE), (a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC, aD, aE)) -> [(a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC, aD, aE)] Source # index :: ((a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC, aD, aE), (a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC, aD, aE)) -> (a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC, aD, aE) -> Int Source # unsafeIndex :: ((a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC, aD, aE), (a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC, aD, aE)) -> (a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC, aD, aE) -> Int Source # inRange :: ((a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC, aD, aE), (a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC, aD, aE)) -> (a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC, aD, aE) -> Bool Source # rangeSize :: ((a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC, aD, aE), (a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC, aD, aE)) -> Int Source # unsafeRangeSize :: ((a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC, aD, aE), (a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC, aD, aE)) -> Int Source # | |||||
(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h, Read i, Read j, Read k, Read l, Read m, Read n) => Read (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source # | Since: base-2.1 | ||||
Defined in GHC.Read | |||||
(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k, Show l, Show m, Show n) => Show (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source # | Since: base-2.1 | ||||
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l, Eq m, Eq n) => Eq (a, b, c, d, e, f, g, h, i, j, k, l, m, n) | |||||
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k, Ord l, Ord m, Ord n) => Ord (a, b, c, d, e, f, g, h, i, j, k, l, m, n) | |||||
Defined in GHC.Classes compare :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Ordering Source # (<) :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Bool Source # (<=) :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Bool Source # (>) :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Bool Source # (>=) :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Bool Source # max :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source # min :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source # | |||||
type Rep1 (Tuple14 a b c d e f g h i j k l m :: Type -> Type) Source # | Since: base-4.16.0.0 | ||||
Defined in GHC.Generics type Rep1 (Tuple14 a b c d e f g h i j k l m :: Type -> Type) = D1 ('MetaData "Tuple14" "GHC.Tuple.Prim" "ghc-prim" 'False) (C1 ('MetaCons "(,,,,,,,,,,,,,)" 'PrefixI 'False) (((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 d) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 e)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 f) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 g)))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 h) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 i) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 j))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 k) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 m) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))))) | |||||
type Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source # | Since: base-4.16.0.0 | ||||
Defined in GHC.Generics type Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n) = D1 ('MetaData "Tuple14" "GHC.Tuple.Prim" "ghc-prim" 'False) (C1 ('MetaCons "(,,,,,,,,,,,,,)" 'PrefixI 'False) (((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 d) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 e)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 f) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 g)))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 h) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 i) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 j))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 k) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 m) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 n)))))) |
data Tuple15 a b c d e f g h i j k l m n o Source #
A tuple of 15 elements.
Since: ghc-prim-0.11.0
(,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o |
Instances
Generic1 (Tuple15 a b c d e f g h i j k l m n :: Type -> Type) Source # | |||||
Defined in GHC.Generics
| |||||
(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g, Bounded h, Bounded i, Bounded j, Bounded k, Bounded l, Bounded m, Bounded n, Bounded o) => Bounded (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source # | Since: base-2.1 | ||||
Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source # | |||||
Defined in GHC.Generics
| |||||
(Ix a1, Ix a2, Ix a3, Ix a4, Ix a5, Ix a6, Ix a7, Ix a8, Ix a9, Ix aA, Ix aB, Ix aC, Ix aD, Ix aE, Ix aF) => Ix (a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC, aD, aE, aF) Source # | Since: base-4.15.0.0 | ||||
Defined in GHC.Ix range :: ((a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC, aD, aE, aF), (a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC, aD, aE, aF)) -> [(a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC, aD, aE, aF)] Source # index :: ((a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC, aD, aE, aF), (a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC, aD, aE, aF)) -> (a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC, aD, aE, aF) -> Int Source # unsafeIndex :: ((a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC, aD, aE, aF), (a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC, aD, aE, aF)) -> (a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC, aD, aE, aF) -> Int Source # inRange :: ((a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC, aD, aE, aF), (a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC, aD, aE, aF)) -> (a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC, aD, aE, aF) -> Bool Source # rangeSize :: ((a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC, aD, aE, aF), (a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC, aD, aE, aF)) -> Int Source # unsafeRangeSize :: ((a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC, aD, aE, aF), (a1, a2, a3, a4, a5, a6, a7, a8, a9, aA, aB, aC, aD, aE, aF)) -> Int Source # | |||||
(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h, Read i, Read j, Read k, Read l, Read m, Read n, Read o) => Read (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source # | Since: base-2.1 | ||||
Defined in GHC.Read readsPrec :: Int -> ReadS (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source # readList :: ReadS [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)] Source # readPrec :: ReadPrec (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source # readListPrec :: ReadPrec [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)] Source # | |||||
(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k, Show l, Show m, Show n, Show o) => Show (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source # | Since: base-2.1 | ||||
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l, Eq m, Eq n, Eq o) => Eq (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) | |||||
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k, Ord l, Ord m, Ord n, Ord o) => Ord (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) | |||||
Defined in GHC.Classes compare :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Ordering Source # (<) :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Bool Source # (<=) :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Bool Source # (>) :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Bool Source # (>=) :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Bool Source # max :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source # min :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source # | |||||
type Rep1 (Tuple15 a b c d e f g h i j k l m n :: Type -> Type) Source # | Since: base-4.16.0.0 | ||||
Defined in GHC.Generics type Rep1 (Tuple15 a b c d e f g h i j k l m n :: Type -> Type) = D1 ('MetaData "Tuple15" "GHC.Tuple.Prim" "ghc-prim" 'False) (C1 ('MetaCons "(,,,,,,,,,,,,,,)" 'PrefixI 'False) (((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 d) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 e)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 f) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 g)))) :*: (((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 h) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 i)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 j) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 k))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 m)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 n) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))))) | |||||
type Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source # | Since: base-4.16.0.0 | ||||
Defined in GHC.Generics type Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) = D1 ('MetaData "Tuple15" "GHC.Tuple.Prim" "ghc-prim" 'False) (C1 ('MetaCons "(,,,,,,,,,,,,,,)" 'PrefixI 'False) (((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 d) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 e)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 f) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 g)))) :*: (((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 h) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 i)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 j) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 k))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 m)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 n) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 o)))))) |