base-4.19.0.0: Basic libraries
Copyright(c) The University of Glasgow 2001
LicenseBSD-style (see the file libraries/base/LICENSE)
Maintainerlibraries@haskell.org
Stabilitystable
Portabilityportable
Safe HaskellTrustworthy
LanguageHaskell2010

Data.Tuple

Description

Functions associated with the tuple data types.

Synopsis

Documentation

data Solo a Source #

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.

Constructors

MkSolo a 

Bundled Patterns

pattern Solo :: a -> (a) 

Instances

Instances details
MonadFix Solo Source #

Since: base-4.15

Instance details

Defined in Control.Monad.Fix

Methods

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

MonadZip Solo Source #

Since: base-4.15.0.0

Instance details

Defined in Control.Monad.Zip

Methods

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

mzipWith :: (a -> b -> c) -> (a) -> (b) -> (c) Source #

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

Foldable Solo Source #

Since: base-4.15

Instance details

Defined in Data.Foldable

Methods

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 #

toList :: (a) -> [a] Source #

null :: (a) -> Bool Source #

length :: (a) -> Int Source #

elem :: Eq a => a -> (a) -> Bool Source #

maximum :: Ord a => (a) -> a Source #

minimum :: Ord a => (a) -> a Source #

sum :: Num a => (a) -> a Source #

product :: Num a => (a) -> a Source #

Foldable1 Solo Source #

Since: base-4.18.0.0

Instance details

Defined in Data.Foldable1

Methods

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 #

head :: (a) -> a Source #

last :: (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

Instance details

Defined in Data.Functor.Classes

Methods

liftEq :: (a -> b -> Bool) -> (a) -> (b) -> Bool Source #

Ord1 Solo Source #

Since: base-4.15

Instance details

Defined in Data.Functor.Classes

Methods

liftCompare :: (a -> b -> Ordering) -> (a) -> (b) -> Ordering Source #

Read1 Solo Source #

Since: base-4.15

Instance details

Defined in Data.Functor.Classes

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (a) Source #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [(a)] Source #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (a) Source #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [(a)] Source #

Show1 Solo Source #

Since: base-4.15

Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> (a) -> ShowS Source #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [(a)] -> ShowS Source #

Traversable Solo Source #

Since: base-4.15

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> (a) -> f (b) Source #

sequenceA :: Applicative f => (f a) -> f (a) Source #

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

sequence :: Monad m => (m a) -> m (a) Source #

Applicative Solo Source #

Since: base-4.15

Instance details

Defined in GHC.Base

Methods

pure :: a -> (a) Source #

(<*>) :: (a -> b) -> (a) -> (b) Source #

liftA2 :: (a -> b -> c) -> (a) -> (b) -> (c) Source #

(*>) :: (a) -> (b) -> (b) Source #

(<*) :: (a) -> (b) -> (a) Source #

Functor Solo Source #

Since: base-4.15

Instance details

Defined in GHC.Base

Methods

fmap :: (a -> b) -> (a) -> (b) Source #

(<$) :: a -> (b) -> (a) Source #

Monad Solo Source #

Since: base-4.15

Instance details

Defined in GHC.Base

Methods

(>>=) :: (a) -> (a -> (b)) -> (b) Source #

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

return :: a -> (a) Source #

Generic1 Solo Source # 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 Solo

Since: base-4.15

Instance details

Defined in GHC.Generics

type Rep1 Solo = D1 ('MetaData "Solo" "GHC.Tuple.Prim" "ghc-prim" 'False) (C1 ('MetaCons "MkSolo" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))

Methods

from1 :: (a) -> Rep1 Solo a Source #

to1 :: Rep1 Solo a -> (a) Source #

Data a => Data (a) Source #

Since: base-4.15

Instance details

Defined in Data.Data

Methods

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

Instance details

Defined in GHC.Base

Methods

mempty :: (a) Source #

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

mconcat :: [(a)] -> (a) Source #

Semigroup a => Semigroup (a) Source #

Since: base-4.15

Instance details

Defined in GHC.Base

Methods

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

sconcat :: NonEmpty (a) -> (a) Source #

stimes :: Integral b => b -> (a) -> (a) Source #

Bounded a => Bounded (a) Source # 
Instance details

Defined in GHC.Enum

Methods

minBound :: (a) Source #

maxBound :: (a) Source #

Enum a => Enum (a) Source # 
Instance details

Defined in GHC.Enum

Methods

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

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

toEnum :: Int -> (a) Source #

fromEnum :: (a) -> Int Source #

enumFrom :: (a) -> [(a)] Source #

enumFromThen :: (a) -> (a) -> [(a)] Source #

enumFromTo :: (a) -> (a) -> [(a)] Source #

enumFromThenTo :: (a) -> (a) -> (a) -> [(a)] Source #

Generic (a) Source # 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a)

Since: base-4.15

Instance details

Defined in GHC.Generics

type Rep (a) = D1 ('MetaData "Solo" "GHC.Tuple.Prim" "ghc-prim" 'False) (C1 ('MetaCons "MkSolo" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

Methods

from :: (a) -> Rep (a) x Source #

to :: Rep (a) x -> (a) Source #

Ix a => Ix (a) Source # 
Instance details

Defined in GHC.Ix

Methods

range :: ((a), (a)) -> [(a)] Source #

index :: ((a), (a)) -> (a) -> Int Source #

unsafeIndex :: ((a), (a)) -> (a) -> Int Source #

inRange :: ((a), (a)) -> (a) -> Bool Source #

rangeSize :: ((a), (a)) -> Int Source #

unsafeRangeSize :: ((a), (a)) -> Int Source #

Read a => Read (a) Source #

Since: base-4.15

Instance details

Defined in GHC.Read

Show a => Show (a) Source #

Since: base-4.15

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a) -> ShowS Source #

show :: (a) -> String Source #

showList :: [(a)] -> ShowS Source #

Eq a => Eq (a) 
Instance details

Defined in GHC.Classes

Methods

(==) :: (a) -> (a) -> Bool Source #

(/=) :: (a) -> (a) -> Bool Source #

Ord a => Ord (a) 
Instance details

Defined in GHC.Classes

Methods

compare :: (a) -> (a) -> Ordering Source #

(<) :: (a) -> (a) -> Bool Source #

(<=) :: (a) -> (a) -> Bool Source #

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

(>=) :: (a) -> (a) -> Bool Source #

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

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

type Rep1 Solo Source #

Since: base-4.15

Instance details

Defined in GHC.Generics

type Rep1 Solo = D1 ('MetaData "Solo" "GHC.Tuple.Prim" "ghc-prim" 'False) (C1 ('MetaCons "MkSolo" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))
type Rep (a) Source #

Since: base-4.15

Instance details

Defined in GHC.Generics

type Rep (a) = D1 ('MetaData "Solo" "GHC.Tuple.Prim" "ghc-prim" 'False) (C1 ('MetaCons "MkSolo" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

getSolo :: (a) -> a Source #

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)

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

Extract the first component of a pair.

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

Extract the second component of a pair.

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

curry converts an uncurried function to a curried function.

Examples

Expand
>>> curry fst 1 2
1

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

uncurry converts a curried function to a function on pairs.

Examples

Expand
>>> uncurry (+) (1,2)
3
>>> uncurry ($) (show, 1)
"1"
>>> map (uncurry max) [(1,2), (3,4), (6,8)]
[2,4,8]

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

Swap the components of a pair.

data Unit Source #

The unit datatype Unit has one non-undefined member, the nullary constructor ().

Since: ghc-prim-0.11.0

Constructors

() 

Instances

Instances details
Data () Source #

Since: base-4.0.0.0

Instance details

Defined in Data.Data

Methods

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

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: () -> Int Source #

alignment :: () -> Int Source #

peekElemOff :: Ptr () -> Int -> IO () Source #

pokeElemOff :: Ptr () -> Int -> () -> IO () Source #

peekByteOff :: Ptr b -> Int -> IO () Source #

pokeByteOff :: Ptr b -> Int -> () -> IO () Source #

peek :: Ptr () -> IO () Source #

poke :: Ptr () -> () -> IO () Source #

Monoid () Source #

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: () Source #

mappend :: () -> () -> () Source #

mconcat :: [()] -> () Source #

Semigroup () Source #

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

(<>) :: () -> () -> () Source #

sconcat :: NonEmpty () -> () Source #

stimes :: Integral b => b -> () -> () Source #

Bounded () Source #

Since: base-2.1

Instance details

Defined in GHC.Enum

Methods

minBound :: () Source #

maxBound :: () Source #

Enum () Source #

Since: base-2.1

Instance details

Defined in GHC.Enum

Methods

succ :: () -> () Source #

pred :: () -> () Source #

toEnum :: Int -> () Source #

fromEnum :: () -> Int Source #

enumFrom :: () -> [()] Source #

enumFromThen :: () -> () -> [()] Source #

enumFromTo :: () -> () -> [()] Source #

enumFromThenTo :: () -> () -> () -> [()] Source #

Generic () Source # 
Instance details

Defined in GHC.Generics

Associated Types

type Rep ()

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

type Rep () = D1 ('MetaData "Unit" "GHC.Tuple.Prim" "ghc-prim" 'False) (C1 ('MetaCons "()" 'PrefixI 'False) (U1 :: Type -> Type))

Methods

from :: () -> Rep () x Source #

to :: Rep () x -> () Source #

Ix () Source #

Since: base-2.1

Instance details

Defined in GHC.Ix

Methods

range :: ((), ()) -> [()] Source #

index :: ((), ()) -> () -> Int Source #

unsafeIndex :: ((), ()) -> () -> Int Source #

inRange :: ((), ()) -> () -> Bool Source #

rangeSize :: ((), ()) -> Int Source #

unsafeRangeSize :: ((), ()) -> Int Source #

Read () Source #

Since: base-2.1

Instance details

Defined in GHC.Read

Show () Source #

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> () -> ShowS Source #

show :: () -> String Source #

showList :: [()] -> ShowS Source #

Eq () 
Instance details

Defined in GHC.Classes

Methods

(==) :: () -> () -> Bool Source #

(/=) :: () -> () -> Bool Source #

Ord () 
Instance details

Defined in GHC.Classes

Methods

compare :: () -> () -> Ordering Source #

(<) :: () -> () -> Bool Source #

(<=) :: () -> () -> Bool Source #

(>) :: () -> () -> Bool Source #

(>=) :: () -> () -> Bool Source #

max :: () -> () -> () Source #

min :: () -> () -> () Source #

Generic1 (URec (Ptr ()) :: k -> Type) Source # 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 (URec (Ptr ()) :: k -> Type)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

type Rep1 (URec (Ptr ()) :: k -> Type) = D1 ('MetaData "URec" "GHC.Generics" "base" 'False) (C1 ('MetaCons "UAddr" 'PrefixI 'True) (S1 ('MetaSel ('Just "uAddr#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UAddr :: k -> Type)))

Methods

from1 :: forall (a :: k). URec (Ptr ()) a -> Rep1 (URec (Ptr ()) :: k -> Type) a Source #

to1 :: forall (a :: k). Rep1 (URec (Ptr ()) :: k -> Type) a -> URec (Ptr ()) a Source #

Foldable (UAddr :: Type -> Type) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Foldable

Methods

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 #

sum :: Num a => UAddr a -> a Source #

product :: Num a => UAddr a -> a Source #

Traversable (UAddr :: Type -> Type) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> UAddr a -> f (UAddr b) Source #

sequenceA :: Applicative f => UAddr (f a) -> f (UAddr a) Source #

mapM :: Monad m => (a -> m b) -> UAddr a -> m (UAddr b) Source #

sequence :: Monad m => UAddr (m a) -> m (UAddr a) Source #

Functor (URec (Ptr ()) :: Type -> Type) Source #

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

fmap :: (a -> b) -> URec (Ptr ()) a -> URec (Ptr ()) b Source #

(<$) :: a -> URec (Ptr ()) b -> URec (Ptr ()) a Source #

Generic (URec (Ptr ()) p) Source # 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec (Ptr ()) p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

type Rep (URec (Ptr ()) p) = D1 ('MetaData "URec" "GHC.Generics" "base" 'False) (C1 ('MetaCons "UAddr" 'PrefixI 'True) (S1 ('MetaSel ('Just "uAddr#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UAddr :: Type -> Type)))

Methods

from :: URec (Ptr ()) p -> Rep (URec (Ptr ()) p) x Source #

to :: Rep (URec (Ptr ()) p) x -> URec (Ptr ()) p Source #

Eq (URec (Ptr ()) p) Source #

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

(==) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool Source #

(/=) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool Source #

Ord (URec (Ptr ()) p) Source #

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

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

Instance details

Defined in GHC.Generics

type Rep () = D1 ('MetaData "Unit" "GHC.Tuple.Prim" "ghc-prim" 'False) (C1 ('MetaCons "()" 'PrefixI 'False) (U1 :: Type -> Type))
data URec (Ptr ()) (p :: k) Source #

Used for marking occurrences of Addr#

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

data URec (Ptr ()) (p :: k) = UAddr {}
type Rep1 (URec (Ptr ()) :: k -> Type) Source #

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

type Rep1 (URec (Ptr ()) :: k -> Type) = D1 ('MetaData "URec" "GHC.Generics" "base" 'False) (C1 ('MetaCons "UAddr" 'PrefixI 'True) (S1 ('MetaSel ('Just "uAddr#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UAddr :: k -> Type)))
type Rep (URec (Ptr ()) p) Source #

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

type Rep (URec (Ptr ()) p) = D1 ('MetaData "URec" "GHC.Generics" "base" 'False) (C1 ('MetaCons "UAddr" 'PrefixI 'True) (S1 ('MetaSel ('Just "uAddr#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UAddr :: Type -> Type)))

data Solo a Source #

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.

Constructors

MkSolo a 

Instances

Instances details
MonadFix Solo Source #

Since: base-4.15

Instance details

Defined in Control.Monad.Fix

Methods

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

MonadZip Solo Source #

Since: base-4.15.0.0

Instance details

Defined in Control.Monad.Zip

Methods

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

mzipWith :: (a -> b -> c) -> (a) -> (b) -> (c) Source #

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

Foldable Solo Source #

Since: base-4.15

Instance details

Defined in Data.Foldable

Methods

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 #

toList :: (a) -> [a] Source #

null :: (a) -> Bool Source #

length :: (a) -> Int Source #

elem :: Eq a => a -> (a) -> Bool Source #

maximum :: Ord a => (a) -> a Source #

minimum :: Ord a => (a) -> a Source #

sum :: Num a => (a) -> a Source #

product :: Num a => (a) -> a Source #

Foldable1 Solo Source #

Since: base-4.18.0.0

Instance details

Defined in Data.Foldable1

Methods

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 #

head :: (a) -> a Source #

last :: (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

Instance details

Defined in Data.Functor.Classes

Methods

liftEq :: (a -> b -> Bool) -> (a) -> (b) -> Bool Source #

Ord1 Solo Source #

Since: base-4.15

Instance details

Defined in Data.Functor.Classes

Methods

liftCompare :: (a -> b -> Ordering) -> (a) -> (b) -> Ordering Source #

Read1 Solo Source #

Since: base-4.15

Instance details

Defined in Data.Functor.Classes

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (a) Source #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [(a)] Source #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (a) Source #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [(a)] Source #

Show1 Solo Source #

Since: base-4.15

Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> (a) -> ShowS Source #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [(a)] -> ShowS Source #

Traversable Solo Source #

Since: base-4.15

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> (a) -> f (b) Source #

sequenceA :: Applicative f => (f a) -> f (a) Source #

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

sequence :: Monad m => (m a) -> m (a) Source #

Applicative Solo Source #

Since: base-4.15

Instance details

Defined in GHC.Base

Methods

pure :: a -> (a) Source #

(<*>) :: (a -> b) -> (a) -> (b) Source #

liftA2 :: (a -> b -> c) -> (a) -> (b) -> (c) Source #

(*>) :: (a) -> (b) -> (b) Source #

(<*) :: (a) -> (b) -> (a) Source #

Functor Solo Source #

Since: base-4.15

Instance details

Defined in GHC.Base

Methods

fmap :: (a -> b) -> (a) -> (b) Source #

(<$) :: a -> (b) -> (a) Source #

Monad Solo Source #

Since: base-4.15

Instance details

Defined in GHC.Base

Methods

(>>=) :: (a) -> (a -> (b)) -> (b) Source #

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

return :: a -> (a) Source #

Generic1 Solo Source # 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 Solo

Since: base-4.15

Instance details

Defined in GHC.Generics

type Rep1 Solo = D1 ('MetaData "Solo" "GHC.Tuple.Prim" "ghc-prim" 'False) (C1 ('MetaCons "MkSolo" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))

Methods

from1 :: (a) -> Rep1 Solo a Source #

to1 :: Rep1 Solo a -> (a) Source #

Data a => Data (a) Source #

Since: base-4.15

Instance details

Defined in Data.Data

Methods

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

Instance details

Defined in GHC.Base

Methods

mempty :: (a) Source #

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

mconcat :: [(a)] -> (a) Source #

Semigroup a => Semigroup (a) Source #

Since: base-4.15

Instance details

Defined in GHC.Base

Methods

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

sconcat :: NonEmpty (a) -> (a) Source #

stimes :: Integral b => b -> (a) -> (a) Source #

Bounded a => Bounded (a) Source # 
Instance details

Defined in GHC.Enum

Methods

minBound :: (a) Source #

maxBound :: (a) Source #

Enum a => Enum (a) Source # 
Instance details

Defined in GHC.Enum

Methods

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

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

toEnum :: Int -> (a) Source #

fromEnum :: (a) -> Int Source #

enumFrom :: (a) -> [(a)] Source #

enumFromThen :: (a) -> (a) -> [(a)] Source #

enumFromTo :: (a) -> (a) -> [(a)] Source #

enumFromThenTo :: (a) -> (a) -> (a) -> [(a)] Source #

Generic (a) Source # 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a)

Since: base-4.15

Instance details

Defined in GHC.Generics

type Rep (a) = D1 ('MetaData "Solo" "GHC.Tuple.Prim" "ghc-prim" 'False) (C1 ('MetaCons "MkSolo" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

Methods

from :: (a) -> Rep (a) x Source #

to :: Rep (a) x -> (a) Source #

Ix a => Ix (a) Source # 
Instance details

Defined in GHC.Ix

Methods

range :: ((a), (a)) -> [(a)] Source #

index :: ((a), (a)) -> (a) -> Int Source #

unsafeIndex :: ((a), (a)) -> (a) -> Int Source #

inRange :: ((a), (a)) -> (a) -> Bool Source #

rangeSize :: ((a), (a)) -> Int Source #

unsafeRangeSize :: ((a), (a)) -> Int Source #

Read a => Read (a) Source #

Since: base-4.15

Instance details

Defined in GHC.Read

Show a => Show (a) Source #

Since: base-4.15

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a) -> ShowS Source #

show :: (a) -> String Source #

showList :: [(a)] -> ShowS Source #

Eq a => Eq (a) 
Instance details

Defined in GHC.Classes

Methods

(==) :: (a) -> (a) -> Bool Source #

(/=) :: (a) -> (a) -> Bool Source #

Ord a => Ord (a) 
Instance details

Defined in GHC.Classes

Methods

compare :: (a) -> (a) -> Ordering Source #

(<) :: (a) -> (a) -> Bool Source #

(<=) :: (a) -> (a) -> Bool Source #

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

(>=) :: (a) -> (a) -> Bool Source #

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

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

type Rep1 Solo Source #

Since: base-4.15

Instance details

Defined in GHC.Generics

type Rep1 Solo = D1 ('MetaData "Solo" "GHC.Tuple.Prim" "ghc-prim" 'False) (C1 ('MetaCons "MkSolo" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))
type Rep (a) Source #

Since: base-4.15

Instance details

Defined in GHC.Generics

type Rep (a) = D1 ('MetaData "Solo" "GHC.Tuple.Prim" "ghc-prim" 'False) (C1 ('MetaCons "MkSolo" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

data Tuple2 a b Source #

A tuple of two elements.

Since: ghc-prim-0.11.0

Constructors

(,) a b 

Instances

Instances details
Bifoldable Tuple2 Source #

Since: base-4.10.0.0

Instance details

Defined in Data.Bifoldable

Methods

bifold :: Monoid m => (m, m) -> m Source #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> (a, b) -> m Source #

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

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

Bifoldable1 Tuple2 Source # 
Instance details

Defined in Data.Bifoldable1

Methods

bifold1 :: Semigroup m => (m, m) -> m Source #

bifoldMap1 :: Semigroup m => (a -> m) -> (b -> m) -> (a, b) -> m Source #

Bifunctor Tuple2 Source #

Class laws for tuples hold only up to laziness. Both first id and second id are lazier than id (and fmap id):

>>> first id (undefined :: (Int, Word)) `seq` ()
()
>>> second id (undefined :: (Int, Word)) `seq` ()
()
>>> id (undefined :: (Int, Word)) `seq` ()
*** Exception: Prelude.undefined

Since: base-4.8.0.0

Instance details

Defined in Data.Bifunctor

Methods

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

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

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

Bitraversable Tuple2 Source #

Since: base-4.10.0.0

Instance details

Defined in Data.Bitraversable

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> (a, b) -> f (c, d) Source #

Eq2 Tuple2 Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

Ord2 Tuple2 Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

Read2 Tuple2 Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> Int -> (a, b) -> ShowS Source #

liftShowList2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> [(a, b)] -> ShowS Source #

Generic1 (Tuple2 a :: Type -> Type) Source # 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 (Tuple2 a :: Type -> Type)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Methods

from1 :: (a, a0) -> Rep1 (Tuple2 a) a0 Source #

to1 :: Rep1 (Tuple2 a) a0 -> (a, a0) Source #

Foldable (Tuple2 a) Source #

Since: base-4.7.0.0

Instance details

Defined in Data.Foldable

Methods

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 #

sum :: Num a0 => (a, a0) -> a0 Source #

product :: Num a0 => (a, a0) -> a0 Source #

Foldable1 (Tuple2 a) Source #

Since: base-4.18.0.0

Instance details

Defined in Data.Foldable1

Methods

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

Instance details

Defined in Data.Functor.Classes

Methods

liftEq :: (a0 -> b -> Bool) -> (a, a0) -> (a, b) -> Bool Source #

Ord a => Ord1 (Tuple2 a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftCompare :: (a0 -> b -> Ordering) -> (a, a0) -> (a, b) -> Ordering Source #

Read a => Read1 (Tuple2 a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> Int -> (a, a0) -> ShowS Source #

liftShowList :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> [(a, a0)] -> ShowS Source #

Traversable (Tuple2 a) Source #

Since: base-4.7.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a0 -> f b) -> (a, a0) -> f (a, b) Source #

sequenceA :: Applicative f => (a, f a0) -> f (a, a0) Source #

mapM :: Monad m => (a0 -> m b) -> (a, a0) -> m (a, b) Source #

sequence :: Monad m => (a, m a0) -> m (a, a0) Source #

Monoid a => Applicative (Tuple2 a) Source #

For tuples, the Monoid constraint on a determines how the first values merge. For example, Strings concatenate:

("hello ", (+15)) <*> ("world!", 2002)
("hello world!",2017)

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

pure :: a0 -> (a, a0) Source #

(<*>) :: (a, a0 -> b) -> (a, a0) -> (a, b) Source #

liftA2 :: (a0 -> b -> c) -> (a, a0) -> (a, b) -> (a, c) Source #

(*>) :: (a, a0) -> (a, b) -> (a, b) Source #

(<*) :: (a, a0) -> (a, b) -> (a, a0) Source #

Functor (Tuple2 a) Source #

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

fmap :: (a0 -> b) -> (a, a0) -> (a, b) Source #

(<$) :: a0 -> (a, b) -> (a, a0) Source #

Monoid a => Monad (Tuple2 a) Source #

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

(>>=) :: (a, a0) -> (a0 -> (a, b)) -> (a, b) Source #

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

return :: a0 -> (a, a0) Source #

(Data a, Data b) => Data (a, b) Source #

Since: base-4.0.0.0

Instance details

Defined in Data.Data

Methods

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

Instance details

Defined in GHC.Base

Methods

mempty :: (a, b) Source #

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

mconcat :: [(a, b)] -> (a, b) Source #

(Semigroup a, Semigroup b) => Semigroup (a, b) Source #

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

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

sconcat :: NonEmpty (a, b) -> (a, b) Source #

stimes :: Integral b0 => b0 -> (a, b) -> (a, b) Source #

(Bounded a, Bounded b) => Bounded (a, b) Source #

Since: base-2.1

Instance details

Defined in GHC.Enum

Methods

minBound :: (a, b) Source #

maxBound :: (a, b) Source #

Generic (a, b) Source # 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Methods

from :: (a, b) -> Rep (a, b) x Source #

to :: Rep (a, b) x -> (a, b) Source #

(Ix a, Ix b) => Ix (a, b) Source #

Since: base-2.1

Instance details

Defined in GHC.Ix

Methods

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

Instance details

Defined in GHC.Read

Methods

readsPrec :: Int -> ReadS (a, b) Source #

readList :: ReadS [(a, b)] Source #

readPrec :: ReadPrec (a, b) Source #

readListPrec :: ReadPrec [(a, b)] Source #

(Show a, Show b) => Show (a, b) Source #

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b) -> ShowS Source #

show :: (a, b) -> String Source #

showList :: [(a, b)] -> ShowS Source #

(Eq a, Eq b) => Eq (a, b) 
Instance details

Defined in GHC.Classes

Methods

(==) :: (a, b) -> (a, b) -> Bool Source #

(/=) :: (a, b) -> (a, b) -> Bool Source #

(Ord a, Ord b) => Ord (a, b) 
Instance details

Defined in GHC.Classes

Methods

compare :: (a, b) -> (a, b) -> Ordering Source #

(<) :: (a, b) -> (a, b) -> Bool Source #

(<=) :: (a, b) -> (a, b) -> Bool Source #

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

(>=) :: (a, b) -> (a, b) -> Bool Source #

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

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

type Rep1 (Tuple2 a :: Type -> Type) Source #

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

type Rep (a, b) Source #

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

data Tuple3 a b c Source #

A tuple of three elements.

Since: ghc-prim-0.11.0

Constructors

(,,) a b c 

Instances

Instances details
Generic1 (Tuple3 a b :: Type -> Type) Source # 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 (Tuple3 a b :: Type -> Type)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Methods

from1 :: (a, b, a0) -> Rep1 (Tuple3 a b) a0 Source #

to1 :: Rep1 (Tuple3 a b) a0 -> (a, b, a0) Source #

Bifoldable (Tuple3 x) Source #

Since: base-4.10.0.0

Instance details

Defined in Data.Bifoldable

Methods

bifold :: Monoid m => (x, m, m) -> m Source #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> (x, a, b) -> m Source #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> (x, a, b) -> c Source #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> (x, a, b) -> c Source #

Bifoldable1 (Tuple3 x) Source # 
Instance details

Defined in Data.Bifoldable1

Methods

bifold1 :: Semigroup m => (x, m, m) -> m Source #

bifoldMap1 :: Semigroup m => (a -> m) -> (b -> m) -> (x, a, b) -> m Source #

Bifunctor (Tuple3 x1) Source #

Since: base-4.8.0.0

Instance details

Defined in Data.Bifunctor

Methods

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

first :: (a -> b) -> (x1, a, c) -> (x1, b, c) Source #

second :: (b -> c) -> (x1, a, b) -> (x1, a, c) Source #

Bitraversable (Tuple3 x) Source #

Since: base-4.10.0.0

Instance details

Defined in Data.Bitraversable

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> (x, a, b) -> f (x, c, d) Source #

Eq a => Eq2 (Tuple3 a) Source #
>>> eq2 ('x', True, "str") ('x', True, "str")
True

Since: base-4.16.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftEq2 :: (a0 -> b -> Bool) -> (c -> d -> Bool) -> (a, a0, c) -> (a, b, d) -> Bool Source #

Ord a => Ord2 (Tuple3 a) Source #
>>> compare2 ('x', True, "aaa") ('x', True, "zzz")
LT

Since: base-4.16.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftCompare2 :: (a0 -> b -> Ordering) -> (c -> d -> Ordering) -> (a, a0, c) -> (a, b, d) -> Ordering Source #

Read a => Read2 (Tuple3 a) Source #
>>> readPrec_to_S readPrec2 0 "('x', True, 2)" :: [((Char, Bool, Int), String)]
[(('x',True,2),"")]

Since: base-4.16.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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 #
>>> showsPrec2 0 ('x', True, 2 :: Int) ""
"('x',True,2)"

Since: base-4.16.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec2 :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> Int -> (a, a0, b) -> ShowS Source #

liftShowList2 :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> [(a, a0, b)] -> ShowS Source #

(Eq a, Eq b) => Eq1 (Tuple3 a b) Source #

Since: base-4.16.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftEq :: (a0 -> b0 -> Bool) -> (a, b, a0) -> (a, b, b0) -> Bool Source #

(Ord a, Ord b) => Ord1 (Tuple3 a b) Source #

Since: base-4.16.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

Instance details

Defined in Data.Functor.Classes

Methods

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

Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> Int -> (a, b, a0) -> ShowS Source #

liftShowList :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> [(a, b, a0)] -> ShowS Source #

(Monoid a, Monoid b) => Applicative (Tuple3 a b) Source #

Since: base-4.14.0.0

Instance details

Defined in GHC.Base

Methods

pure :: a0 -> (a, b, a0) Source #

(<*>) :: (a, b, a0 -> b0) -> (a, b, a0) -> (a, b, b0) Source #

liftA2 :: (a0 -> b0 -> c) -> (a, b, a0) -> (a, b, b0) -> (a, b, c) Source #

(*>) :: (a, b, a0) -> (a, b, b0) -> (a, b, b0) Source #

(<*) :: (a, b, a0) -> (a, b, b0) -> (a, b, a0) Source #

Functor (Tuple3 a b) Source #

Since: base-4.14.0.0

Instance details

Defined in GHC.Base

Methods

fmap :: (a0 -> b0) -> (a, b, a0) -> (a, b, b0) Source #

(<$) :: a0 -> (a, b, b0) -> (a, b, a0) Source #

(Monoid a, Monoid b) => Monad (Tuple3 a b) Source #

Since: base-4.14.0.0

Instance details

Defined in GHC.Base

Methods

(>>=) :: (a, b, a0) -> (a0 -> (a, b, b0)) -> (a, b, b0) Source #

(>>) :: (a, b, a0) -> (a, b, b0) -> (a, b, b0) Source #

return :: a0 -> (a, b, a0) Source #

(Data a, Data b, Data c) => Data (a, b, c) Source #

Since: base-4.0.0.0

Instance details

Defined in Data.Data

Methods

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

Instance details

Defined in GHC.Base

Methods

mempty :: (a, b, c) Source #

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

mconcat :: [(a, b, c)] -> (a, b, c) Source #

(Semigroup a, Semigroup b, Semigroup c) => Semigroup (a, b, c) Source #

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

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

sconcat :: NonEmpty (a, b, c) -> (a, b, c) Source #

stimes :: Integral b0 => b0 -> (a, b, c) -> (a, b, c) Source #

(Bounded a, Bounded b, Bounded c) => Bounded (a, b, c) Source #

Since: base-2.1

Instance details

Defined in GHC.Enum

Methods

minBound :: (a, b, c) Source #

maxBound :: (a, b, c) Source #

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

Defined in GHC.Generics

Associated Types

type Rep (a, b, c)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Methods

from :: (a, b, c) -> Rep (a, b, c) x Source #

to :: Rep (a, b, c) x -> (a, b, c) Source #

(Ix a1, Ix a2, Ix a3) => Ix (a1, a2, a3) Source #

Since: base-2.1

Instance details

Defined in GHC.Ix

Methods

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

Instance details

Defined in GHC.Read

Methods

readsPrec :: Int -> ReadS (a, b, c) Source #

readList :: ReadS [(a, b, c)] Source #

readPrec :: ReadPrec (a, b, c) Source #

readListPrec :: ReadPrec [(a, b, c)] Source #

(Show a, Show b, Show c) => Show (a, b, c) Source #

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c) -> ShowS Source #

show :: (a, b, c) -> String Source #

showList :: [(a, b, c)] -> ShowS Source #

(Eq a, Eq b, Eq c) => Eq (a, b, c) 
Instance details

Defined in GHC.Classes

Methods

(==) :: (a, b, c) -> (a, b, c) -> Bool Source #

(/=) :: (a, b, c) -> (a, b, c) -> Bool Source #

(Ord a, Ord b, Ord c) => Ord (a, b, c) 
Instance details

Defined in GHC.Classes

Methods

compare :: (a, b, c) -> (a, b, c) -> Ordering Source #

(<) :: (a, b, c) -> (a, b, c) -> Bool Source #

(<=) :: (a, b, c) -> (a, b, c) -> Bool Source #

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

(>=) :: (a, b, c) -> (a, b, c) -> Bool Source #

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

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

type Rep1 (Tuple3 a b :: Type -> Type) Source #

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

type Rep (a, b, c) Source #

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

data Tuple4 a b c d Source #

A tuple of four elements.

Since: ghc-prim-0.11.0

Constructors

(,,,) a b c d 

Instances

Instances details
Generic1 (Tuple4 a b c :: Type -> Type) Source # 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 (Tuple4 a b c :: Type -> Type)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Methods

from1 :: (a, b, c, a0) -> Rep1 (Tuple4 a b c) a0 Source #

to1 :: Rep1 (Tuple4 a b c) a0 -> (a, b, c, a0) Source #

Bifoldable (Tuple4 x y) Source #

Since: base-4.10.0.0

Instance details

Defined in Data.Bifoldable

Methods

bifold :: Monoid m => (x, y, m, m) -> m Source #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> (x, y, a, b) -> m Source #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> (x, y, a, b) -> c Source #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> (x, y, a, b) -> c Source #

Bifoldable1 (Tuple4 x y) Source # 
Instance details

Defined in Data.Bifoldable1

Methods

bifold1 :: Semigroup m => (x, y, m, m) -> m Source #

bifoldMap1 :: Semigroup m => (a -> m) -> (b -> m) -> (x, y, a, b) -> m Source #

Bifunctor (Tuple4 x1 x2) Source #

Since: base-4.8.0.0

Instance details

Defined in Data.Bifunctor

Methods

bimap :: (a -> b) -> (c -> d) -> (x1, x2, a, c) -> (x1, x2, b, d) Source #

first :: (a -> b) -> (x1, x2, a, c) -> (x1, x2, b, c) Source #

second :: (b -> c) -> (x1, x2, a, b) -> (x1, x2, a, c) Source #

Bitraversable (Tuple4 x y) Source #

Since: base-4.10.0.0

Instance details

Defined in Data.Bitraversable

Methods

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 #
>>> eq2 ('x', True, "str", 2) ('x', True, "str", 2 :: Int)
True

Since: base-4.16.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftEq2 :: (a0 -> b0 -> Bool) -> (c -> d -> Bool) -> (a, b, a0, c) -> (a, b, b0, d) -> Bool Source #

(Ord a, Ord b) => Ord2 (Tuple4 a b) Source #
>>> compare2 ('x', True, "str", 2) ('x', True, "str", 3 :: Int)
LT

Since: base-4.16.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftCompare2 :: (a0 -> b0 -> Ordering) -> (c -> d -> Ordering) -> (a, b, a0, c) -> (a, b, b0, d) -> Ordering Source #

(Read a, Read b) => Read2 (Tuple4 a b) Source #
>>> readPrec_to_S readPrec2 0 "('x', True, 2, 4.5)" :: [((Char, Bool, Int, Double), String)]
[(('x',True,2,4.5),"")]

Since: base-4.16.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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 #
>>> showsPrec2 0 ('x', True, 2 :: Int, 4.5 :: Double) ""
"('x',True,2,4.5)"

Since: base-4.16.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec2 :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> (Int -> b0 -> ShowS) -> ([b0] -> ShowS) -> Int -> (a, b, a0, b0) -> ShowS Source #

liftShowList2 :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> (Int -> b0 -> ShowS) -> ([b0] -> ShowS) -> [(a, b, a0, b0)] -> ShowS Source #

(Eq a, Eq b, Eq c) => Eq1 (Tuple4 a b c) Source #

Since: base-4.16.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftEq :: (a0 -> b0 -> Bool) -> (a, b, c, a0) -> (a, b, c, b0) -> Bool Source #

(Ord a, Ord b, Ord c) => Ord1 (Tuple4 a b c) Source #

Since: base-4.16.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

Instance details

Defined in Data.Functor.Classes

Methods

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

Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> Int -> (a, b, c, a0) -> ShowS Source #

liftShowList :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> [(a, b, c, a0)] -> ShowS Source #

(Monoid a, Monoid b, Monoid c) => Applicative (Tuple4 a b c) Source #

Since: base-4.14.0.0

Instance details

Defined in GHC.Base

Methods

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

Instance details

Defined in GHC.Base

Methods

fmap :: (a0 -> b0) -> (a, b, c, a0) -> (a, b, c, b0) Source #

(<$) :: a0 -> (a, b, c, b0) -> (a, b, c, a0) Source #

(Monoid a, Monoid b, Monoid c) => Monad (Tuple4 a b c) Source #

Since: base-4.14.0.0

Instance details

Defined in GHC.Base

Methods

(>>=) :: (a, b, c, a0) -> (a0 -> (a, b, c, b0)) -> (a, b, c, b0) Source #

(>>) :: (a, b, c, a0) -> (a, b, c, b0) -> (a, b, c, b0) Source #

return :: a0 -> (a, b, c, a0) Source #

(Data a, Data b, Data c, Data d) => Data (a, b, c, d) Source #

Since: base-4.0.0.0

Instance details

Defined in Data.Data

Methods

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

Instance details

Defined in GHC.Base

Methods

mempty :: (a, b, c, d) Source #

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

mconcat :: [(a, b, c, d)] -> (a, b, c, d) Source #

(Semigroup a, Semigroup b, Semigroup c, Semigroup d) => Semigroup (a, b, c, d) Source #

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

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

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

stimes :: Integral b0 => b0 -> (a, b, c, d) -> (a, b, c, d) Source #

(Bounded a, Bounded b, Bounded c, Bounded d) => Bounded (a, b, c, d) Source #

Since: base-2.1

Instance details

Defined in GHC.Enum

Methods

minBound :: (a, b, c, d) Source #

maxBound :: (a, b, c, d) Source #

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

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Methods

from :: (a, b, c, d) -> Rep (a, b, c, d) x Source #

to :: Rep (a, b, c, d) x -> (a, b, c, d) Source #

(Ix a1, Ix a2, Ix a3, Ix a4) => Ix (a1, a2, a3, a4) Source #

Since: base-2.1

Instance details

Defined in GHC.Ix

Methods

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

Instance details

Defined in GHC.Read

Methods

readsPrec :: Int -> ReadS (a, b, c, d) Source #

readList :: ReadS [(a, b, c, d)] Source #

readPrec :: ReadPrec (a, b, c, d) Source #

readListPrec :: ReadPrec [(a, b, c, d)] Source #

(Show a, Show b, Show c, Show d) => Show (a, b, c, d) Source #

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c, d) -> ShowS Source #

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

showList :: [(a, b, c, d)] -> ShowS Source #

(Eq a, Eq b, Eq c, Eq d) => Eq (a, b, c, d) 
Instance details

Defined in GHC.Classes

Methods

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

(/=) :: (a, b, c, d) -> (a, b, c, d) -> Bool Source #

(Ord a, Ord b, Ord c, Ord d) => Ord (a, b, c, d) 
Instance details

Defined in GHC.Classes

Methods

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

Instance details

Defined in GHC.Generics

type Rep (a, b, c, d) Source #

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

data Tuple5 a b c d e Source #

A tuple of five elements.

Since: ghc-prim-0.11.0

Constructors

(,,,,) a b c d e 

Instances

Instances details
Generic1 (Tuple5 a b c d :: Type -> Type) Source # 
Instance details

Defined in GHC.Generics

Methods

from1 :: (a, b, c, d, a0) -> Rep1 (Tuple5 a b c d) a0 Source #

to1 :: Rep1 (Tuple5 a b c d) a0 -> (a, b, c, d, a0) Source #

Bifoldable (Tuple5 x y z) Source #

Since: base-4.10.0.0

Instance details

Defined in Data.Bifoldable

Methods

bifold :: Monoid m => (x, y, z, m, m) -> m Source #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> (x, y, z, a, b) -> m Source #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> (x, y, z, a, b) -> c Source #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> (x, y, z, a, b) -> c Source #

Bifoldable1 (Tuple5 x y z) Source # 
Instance details

Defined in Data.Bifoldable1

Methods

bifold1 :: Semigroup m => (x, y, z, m, m) -> m Source #

bifoldMap1 :: Semigroup m => (a -> m) -> (b -> m) -> (x, y, z, a, b) -> m Source #

Bifunctor (Tuple5 x1 x2 x3) Source #

Since: base-4.8.0.0

Instance details

Defined in Data.Bifunctor

Methods

bimap :: (a -> b) -> (c -> d) -> (x1, x2, x3, a, c) -> (x1, x2, x3, b, d) Source #

first :: (a -> b) -> (x1, x2, x3, a, c) -> (x1, x2, x3, b, c) Source #

second :: (b -> c) -> (x1, x2, x3, a, b) -> (x1, x2, x3, a, c) Source #

Bitraversable (Tuple5 x y z) Source #

Since: base-4.10.0.0

Instance details

Defined in Data.Bitraversable

Methods

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

Instance details

Defined in GHC.Base

Methods

fmap :: (a0 -> b0) -> (a, b, c, d, a0) -> (a, b, c, d, b0) Source #

(<$) :: a0 -> (a, b, c, d, b0) -> (a, b, c, d, a0) Source #

(Data a, Data b, Data c, Data d, Data e) => Data (a, b, c, d, e) Source #

Since: base-4.0.0.0

Instance details

Defined in Data.Data

Methods

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

Instance details

Defined in GHC.Base

Methods

mempty :: (a, b, c, d, e) Source #

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

mconcat :: [(a, b, c, d, e)] -> (a, b, c, d, e) Source #

(Semigroup a, Semigroup b, Semigroup c, Semigroup d, Semigroup e) => Semigroup (a, b, c, d, e) Source #

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

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

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

stimes :: Integral b0 => b0 -> (a, b, c, d, e) -> (a, b, c, d, e) Source #

(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e) => Bounded (a, b, c, d, e) Source #

Since: base-2.1

Instance details

Defined in GHC.Enum

Methods

minBound :: (a, b, c, d, e) Source #

maxBound :: (a, b, c, d, e) Source #

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

Defined in GHC.Generics

Methods

from :: (a, b, c, d, e) -> Rep (a, b, c, d, e) x Source #

to :: Rep (a, b, c, d, e) x -> (a, b, c, d, e) Source #

(Ix a1, Ix a2, Ix a3, Ix a4, Ix a5) => Ix (a1, a2, a3, a4, a5) Source #

Since: base-2.1

Instance details

Defined in GHC.Ix

Methods

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

Instance details

Defined in GHC.Read

Methods

readsPrec :: Int -> ReadS (a, b, c, d, e) Source #

readList :: ReadS [(a, b, c, d, e)] Source #

readPrec :: ReadPrec (a, b, c, d, e) Source #

readListPrec :: ReadPrec [(a, b, c, d, e)] Source #

(Show a, Show b, Show c, Show d, Show e) => Show (a, b, c, d, e) Source #

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c, d, e) -> ShowS Source #

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

showList :: [(a, b, c, d, e)] -> ShowS Source #

(Eq a, Eq b, Eq c, Eq d, Eq e) => Eq (a, b, c, d, e) 
Instance details

Defined in GHC.Classes

Methods

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

(/=) :: (a, b, c, d, e) -> (a, b, c, d, e) -> Bool Source #

(Ord a, Ord b, Ord c, Ord d, Ord e) => Ord (a, b, c, d, e) 
Instance details

Defined in GHC.Classes

Methods

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

Instance details

Defined in GHC.Generics

type Rep (a, b, c, d, e) Source #

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

data Tuple6 a b c d e f Source #

A tuple of six elements.

Since: ghc-prim-0.11.0

Constructors

(,,,,,) a b c d e f 

Instances

Instances details
Generic1 (Tuple6 a b c d e :: Type -> Type) Source # 
Instance details

Defined in GHC.Generics

Methods

from1 :: (a, b, c, d, e, a0) -> Rep1 (Tuple6 a b c d e) a0 Source #

to1 :: Rep1 (Tuple6 a b c d e) a0 -> (a, b, c, d, e, a0) Source #

Bifoldable (Tuple6 x y z w) Source #

Since: base-4.10.0.0

Instance details

Defined in Data.Bifoldable

Methods

bifold :: Monoid m => (x, y, z, w, m, m) -> m Source #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> (x, y, z, w, a, b) -> m Source #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> (x, y, z, w, a, b) -> c Source #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> (x, y, z, w, a, b) -> c Source #

Bifunctor (Tuple6 x1 x2 x3 x4) Source #

Since: base-4.8.0.0

Instance details

Defined in Data.Bifunctor

Methods

bimap :: (a -> b) -> (c -> d) -> (x1, x2, x3, x4, a, c) -> (x1, x2, x3, x4, b, d) Source #

first :: (a -> b) -> (x1, x2, x3, x4, a, c) -> (x1, x2, x3, x4, b, c) Source #

second :: (b -> c) -> (x1, x2, x3, x4, a, b) -> (x1, x2, x3, x4, a, c) Source #

Bitraversable (Tuple6 x y z w) Source #

Since: base-4.10.0.0

Instance details

Defined in Data.Bitraversable

Methods

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

Instance details

Defined in GHC.Base

Methods

fmap :: (a0 -> b0) -> (a, b, c, d, e, a0) -> (a, b, c, d, e, b0) Source #

(<$) :: a0 -> (a, b, c, d, e, b0) -> (a, b, c, d, e, a0) Source #

(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

Instance details

Defined in Data.Data

Methods

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

Instance details

Defined in GHC.Enum

Methods

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

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

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

Defined in GHC.Generics

Methods

from :: (a, b, c, d, e, f) -> Rep (a, b, c, d, e, f) x Source #

to :: Rep (a, b, c, d, e, f) x -> (a, b, c, d, e, f) Source #

(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

Instance details

Defined in GHC.Ix

Methods

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

Instance details

Defined in GHC.Read

Methods

readsPrec :: Int -> ReadS (a, b, c, d, e, f) Source #

readList :: ReadS [(a, b, c, d, e, f)] Source #

readPrec :: ReadPrec (a, b, c, d, e, f) Source #

readListPrec :: ReadPrec [(a, b, c, d, e, f)] Source #

(Show a, Show b, Show c, Show d, Show e, Show f) => Show (a, b, c, d, e, f) Source #

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c, d, e, f) -> ShowS Source #

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

showList :: [(a, b, c, d, e, f)] -> ShowS Source #

(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f) => Eq (a, b, c, d, e, f) 
Instance details

Defined in GHC.Classes

Methods

(==) :: (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 #

(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f) => Ord (a, b, c, d, e, f) 
Instance details

Defined in GHC.Classes

Methods

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

Instance details

Defined in GHC.Generics

type Rep (a, b, c, d, e, f) Source #

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

data Tuple7 a b c d e f g Source #

A tuple of seven elements.

Since: ghc-prim-0.11.0

Constructors

(,,,,,,) a b c d e f g 

Instances

Instances details
Generic1 (Tuple7 a b c d e f :: Type -> Type) Source # 
Instance details

Defined in GHC.Generics

Methods

from1 :: (a, b, c, d, e, f, a0) -> Rep1 (Tuple7 a b c d e f) a0 Source #

to1 :: Rep1 (Tuple7 a b c d e f) a0 -> (a, b, c, d, e, f, a0) Source #

Bifoldable (Tuple7 x y z w v) Source #

Since: base-4.10.0.0

Instance details

Defined in Data.Bifoldable

Methods

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

Instance details

Defined in Data.Bifunctor

Methods

bimap :: (a -> b) -> (c -> d) -> (x1, x2, x3, x4, x5, a, c) -> (x1, x2, x3, x4, x5, b, d) Source #

first :: (a -> b) -> (x1, x2, x3, x4, x5, a, c) -> (x1, x2, x3, x4, x5, b, c) Source #

second :: (b -> c) -> (x1, x2, x3, x4, x5, a, b) -> (x1, x2, x3, x4, x5, a, c) Source #

Bitraversable (Tuple7 x y z w v) Source #

Since: base-4.10.0.0

Instance details

Defined in Data.Bitraversable

Methods

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

Instance details

Defined in GHC.Base

Methods

fmap :: (a0 -> b0) -> (a, b, c, d, e, f, a0) -> (a, b, c, d, e, f, b0) Source #

(<$) :: a0 -> (a, b, c, d, e, f, b0) -> (a, b, c, d, e, f, a0) Source #

(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

Instance details

Defined in Data.Data

Methods

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

Instance details

Defined in GHC.Enum

Methods

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

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

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

Defined in GHC.Generics

Methods

from :: (a, b, c, d, e, f, g) -> Rep (a, b, c, d, e, f, g) x Source #

to :: Rep (a, b, c, d, e, f, g) x -> (a, b, c, d, e, f, g) Source #

(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

Instance details

Defined in GHC.Ix

Methods

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

Instance details

Defined in GHC.Read

Methods

readsPrec :: Int -> ReadS (a, b, c, d, e, f, g) Source #

readList :: ReadS [(a, b, c, d, e, f, g)] Source #

readPrec :: ReadPrec (a, b, c, d, e, f, g) Source #

readListPrec :: ReadPrec [(a, b, c, d, e, f, g)] Source #

(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

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c, d, e, f, g) -> ShowS Source #

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

showList :: [(a, b, c, d, e, f, g)] -> ShowS Source #

(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g) => Eq (a, b, c, d, e, f, g) 
Instance details

Defined in GHC.Classes

Methods

(==) :: (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 #

(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g) => Ord (a, b, c, d, e, f, g) 
Instance details

Defined in GHC.Classes

Methods

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

Instance details

Defined in GHC.Generics

type Rep (a, b, c, d, e, f, g) Source #

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

data Tuple8 a b c d e f g h Source #

A tuple of eight elements.

Since: ghc-prim-0.11.0

Constructors

(,,,,,,,) a b c d e f g h 

Instances

Instances details
Generic1 (Tuple8 a b c d e f g :: Type -> Type) Source # 
Instance details

Defined in GHC.Generics

Methods

from1 :: (a, b, c, d, e, f, g, a0) -> Rep1 (Tuple8 a b c d e f g) a0 Source #

to1 :: Rep1 (Tuple8 a b c d e f g) a0 -> (a, b, c, d, e, f, g, a0) Source #

(Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g, Bounded h) => Bounded (a, b, c, d, e, f, g, h) Source #

Since: base-2.1

Instance details

Defined in GHC.Enum

Methods

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

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

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

Defined in GHC.Generics

Methods

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

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

(Ix a1, Ix a2, Ix a3, Ix a4, Ix a5, Ix a6, Ix a7, Ix a8) => Ix (a1, a2, a3, a4, a5, a6, a7, a8) Source #

Since: base-4.15.0.0

Instance details

Defined in GHC.Ix

Methods

range :: ((a1, a2, a3, a4, a5, a6, a7, a8), (a1, a2, a3, a4, a5, a6, a7, a8)) -> [(a1, a2, a3, a4, a5, a6, a7, a8)] Source #

index :: ((a1, a2, a3, a4, a5, a6, a7, a8), (a1, a2, a3, a4, a5, a6, a7, a8)) -> (a1, a2, a3, a4, a5, a6, a7, a8) -> Int Source #

unsafeIndex :: ((a1, a2, a3, a4, a5, a6, a7, a8), (a1, a2, a3, a4, a5, a6, a7, a8)) -> (a1, a2, a3, a4, a5, a6, a7, a8) -> Int Source #

inRange :: ((a1, a2, a3, a4, a5, a6, a7, a8), (a1, a2, a3, a4, a5, a6, a7, a8)) -> (a1, a2, a3, a4, a5, a6, a7, a8) -> Bool Source #

rangeSize :: ((a1, a2, a3, a4, a5, a6, a7, a8), (a1, a2, a3, a4, a5, a6, a7, a8)) -> Int Source #

unsafeRangeSize :: ((a1, a2, a3, a4, a5, a6, a7, a8), (a1, a2, a3, a4, a5, a6, a7, a8)) -> Int Source #

(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h) => Read (a, b, c, d, e, f, g, h) Source #

Since: base-2.1

Instance details

Defined in GHC.Read

Methods

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

readList :: ReadS [(a, b, c, d, e, f, g, h)] Source #

readPrec :: ReadPrec (a, b, c, d, e, f, g, h) Source #

readListPrec :: ReadPrec [(a, b, c, d, e, f, g, h)] Source #

(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h) => Show (a, b, c, d, e, f, g, h) Source #

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

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

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

showList :: [(a, b, c, d, e, f, g, h)] -> ShowS Source #

(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h) => Eq (a, b, c, d, e, f, g, h) 
Instance details

Defined in GHC.Classes

Methods

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

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

(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h) => Ord (a, b, c, d, e, f, g, h) 
Instance details

Defined in GHC.Classes

Methods

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

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

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

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

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

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

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

type Rep1 (Tuple8 a b c d e f g :: Type -> Type) Source #

Since: base-4.16.0.0

Instance details

Defined in GHC.Generics

type Rep (a, b, c, d, e, f, g, h) Source #

Since: base-4.16.0.0

Instance details

Defined in GHC.Generics

data Tuple9 a b c d e f g h i Source #

A tuple of nine elements.

Since: ghc-prim-0.11.0

Constructors

(,,,,,,,,) a b c d e f g h i 

Instances

Instances details
Generic1 (Tuple9 a b c d e f g h :: Type -> Type) Source # 
Instance details

Defined in GHC.Generics

Methods

from1 :: (a, b, c, d, e, f, g, h, a0) -> Rep1 (Tuple9 a b c d e f g h) a0 Source #

to1 :: Rep1 (Tuple9 a b c d e f g h) a0 -> (a, b, c, d, e, f, g, h, a0) Source #

(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

Instance details

Defined in GHC.Enum

Methods

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

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

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

Defined in GHC.Generics

Methods

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

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

(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

Instance details

Defined in GHC.Ix

Methods

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

Instance details

Defined in GHC.Read

Methods

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

readList :: ReadS [(a, b, c, d, e, f, g, h, i)] Source #

readPrec :: ReadPrec (a, b, c, d, e, f, g, h, i) Source #

readListPrec :: ReadPrec [(a, b, c, d, e, f, g, h, i)] Source #

(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

Instance details

Defined in GHC.Show

Methods

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

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

showList :: [(a, b, c, d, e, f, g, h, i)] -> ShowS Source #

(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) 
Instance details

Defined in GHC.Classes

Methods

(==) :: (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 #

(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) 
Instance details

Defined in GHC.Classes

Methods

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

Instance details

Defined in GHC.Generics

type Rep (a, b, c, d, e, f, g, h, i) Source #

Since: base-4.16.0.0

Instance details

Defined in GHC.Generics

data Tuple10 a b c d e f g h i j Source #

A tuple of ten elements.

Since: ghc-prim-0.11.0

Constructors

(,,,,,,,,,) a b c d e f g h i j 

Instances

Instances details
Generic1 (Tuple10 a b c d e f g h i :: Type -> Type) Source # 
Instance details

Defined in GHC.Generics

Methods

from1 :: (a, b, c, d, e, f, g, h, i, a0) -> Rep1 (Tuple10 a b c d e f g h i) a0 Source #

to1 :: Rep1 (Tuple10 a b c d e f g h i) a0 -> (a, b, c, d, e, f, g, h, i, a0) Source #

(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

Instance details

Defined in GHC.Enum

Methods

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

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

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

Defined in GHC.Generics

Methods

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

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

(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

Instance details

Defined in GHC.Ix

Methods

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

Instance details

Defined in GHC.Read

Methods

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

readList :: ReadS [(a, b, c, d, e, f, g, h, i, j)] Source #

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

readListPrec :: ReadPrec [(a, b, c, d, e, f, g, h, i, j)] Source #

(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

Instance details

Defined in GHC.Show

Methods

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

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

showList :: [(a, b, c, d, e, f, g, h, i, j)] -> ShowS Source #

(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) 
Instance details

Defined in GHC.Classes

Methods

(==) :: (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 #

(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) 
Instance details

Defined in GHC.Classes

Methods

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

Instance details

Defined in GHC.Generics

type Rep (a, b, c, d, e, f, g, h, i, j) Source #

Since: base-4.16.0.0

Instance details

Defined in GHC.Generics

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

Constructors

(,,,,,,,,,,) a b c d e f g h i j k 

Instances

Instances details
Generic1 (Tuple11 a b c d e f g h i j :: Type -> Type) Source # 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 (Tuple11 a b c d e f g h i j :: Type -> Type)

Since: base-4.16.0.0

Instance details

Defined in GHC.Generics

Methods

from1 :: (a, b, c, d, e, f, g, h, i, j, a0) -> Rep1 (Tuple11 a b c d e f g h i j) a0 Source #

to1 :: Rep1 (Tuple11 a b c d e f g h i j) a0 -> (a, b, c, d, e, f, g, h, i, j, a0) Source #

(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

Instance details

Defined in GHC.Enum

Methods

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

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

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

Defined in GHC.Generics

Methods

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

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

(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

Instance details

Defined in GHC.Ix

Methods

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

Instance details

Defined in GHC.Read

Methods

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

readList :: ReadS [(a, b, c, d, e, f, g, h, i, j, k)] Source #

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

readListPrec :: ReadPrec [(a, b, c, d, e, f, g, h, i, j, k)] Source #

(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

Instance details

Defined in GHC.Show

Methods

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

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

showList :: [(a, b, c, d, e, f, g, h, i, j, k)] -> ShowS Source #

(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) 
Instance details

Defined in GHC.Classes

Methods

(==) :: (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 #

(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) 
Instance details

Defined in GHC.Classes

Methods

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

Instance details

Defined in GHC.Generics

type Rep (a, b, c, d, e, f, g, h, i, j, k) Source #

Since: base-4.16.0.0

Instance details

Defined in GHC.Generics

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

Constructors

(,,,,,,,,,,,) a b c d e f g h i j k l 

Instances

Instances details
Generic1 (Tuple12 a b c d e f g h i j k :: Type -> Type) Source # 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 (Tuple12 a b c d e f g h i j k :: Type -> Type)

Since: base-4.16.0.0

Instance details

Defined in GHC.Generics

Methods

from1 :: (a, b, c, d, e, f, g, h, i, j, k, a0) -> Rep1 (Tuple12 a b c d e f g h i j k) a0 Source #

to1 :: Rep1 (Tuple12 a b c d e f g h i j k) a0 -> (a, b, c, d, e, f, g, h, i, j, k, a0) Source #

(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

Instance details

Defined in GHC.Enum

Methods

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

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

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

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d, e, f, g, h, i, j, k, l)

Since: base-4.16.0.0

Instance details

Defined in GHC.Generics

Methods

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

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

(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

Instance details

Defined in GHC.Ix

Methods

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

Instance details

Defined in GHC.Read

Methods

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

readList :: ReadS [(a, b, c, d, e, f, g, h, i, j, k, l)] Source #

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

readListPrec :: ReadPrec [(a, b, c, d, e, f, g, h, i, j, k, l)] 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 (a, b, c, d, e, f, g, h, i, j, k, l) Source #

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

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

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

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

(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) 
Instance details

Defined in GHC.Classes

Methods

(==) :: (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 #

(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) 
Instance details

Defined in GHC.Classes

Methods

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

Instance details

Defined in GHC.Generics

type Rep (a, b, c, d, e, f, g, h, i, j, k, l) Source #

Since: base-4.16.0.0

Instance details

Defined in GHC.Generics

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

Constructors

(,,,,,,,,,,,,) a b c d e f g h i j k l m 

Instances

Instances details
Generic1 (Tuple13 a b c d e f g h i j k l :: Type -> Type) Source # 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 (Tuple13 a b c d e f g h i j k l :: Type -> Type)

Since: base-4.16.0.0

Instance details

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)))))

Methods

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

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

(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

Instance details

Defined in GHC.Enum

Methods

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

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

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

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d, e, f, g, h, i, j, k, l, m)

Since: base-4.16.0.0

Instance details

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))))))

Methods

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

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

(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

Instance details

Defined in GHC.Ix

Methods

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

Instance details

Defined in GHC.Read

Methods

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

readList :: ReadS [(a, b, c, d, e, f, g, h, i, j, k, l, m)] Source #

readPrec :: ReadPrec (a, b, c, d, e, f, g, h, i, j, k, l, m) Source #

readListPrec :: ReadPrec [(a, b, c, d, e, f, g, h, i, j, k, l, m)] 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 (a, b, c, d, e, f, g, h, i, j, k, l, m) Source #

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

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

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

showList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m)] -> ShowS Source #

(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) 
Instance details

Defined in GHC.Classes

Methods

(==) :: (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 #

(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) 
Instance details

Defined in GHC.Classes

Methods

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

Instance details

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

Instance details

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

Constructors

(,,,,,,,,,,,,,) a b c d e f g h i j k l m n 

Instances

Instances details
Generic1 (Tuple14 a b c d e f g h i j k l m :: Type -> Type) Source # 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 (Tuple14 a b c d e f g h i j k l m :: Type -> Type)

Since: base-4.16.0.0

Instance details

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)))))

Methods

from1 :: (a, b, c, d, e, f, g, h, i, j, k, l, m, a0) -> Rep1 (Tuple14 a b c d e f g h i j k l m) a0 Source #

to1 :: Rep1 (Tuple14 a b c d e f g h i j k l m) a0 -> (a, b, c, d, e, f, g, h, i, j, k, l, m, a0) Source #

(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

Instance details

Defined in GHC.Enum

Methods

minBound :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source #

maxBound :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source #

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

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n)

Since: base-4.16.0.0

Instance details

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))))))

Methods

from :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n) x Source #

to :: Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n) x -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source #

(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

Instance details

Defined in GHC.Ix

Methods

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

Instance details

Defined in GHC.Read

Methods

readsPrec :: Int -> ReadS (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source #

readList :: ReadS [(a, b, c, d, e, f, g, h, i, j, k, l, m, n)] Source #

readPrec :: ReadPrec (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source #

readListPrec :: ReadPrec [(a, b, c, d, e, f, g, h, i, j, k, l, m, n)] 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 (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source #

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> ShowS Source #

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

showList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m, n)] -> ShowS Source #

(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) 
Instance details

Defined in GHC.Classes

Methods

(==) :: (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 #

(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) 
Instance details

Defined in GHC.Classes

Methods

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

Instance details

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

Instance details

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

Constructors

(,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o 

Instances

Instances details
Generic1 (Tuple15 a b c d e f g h i j k l m n :: Type -> Type) Source # 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 (Tuple15 a b c d e f g h i j k l m n :: Type -> Type)

Since: base-4.16.0.0

Instance details

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)))))

Methods

from1 :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, a0) -> Rep1 (Tuple15 a b c d e f g h i j k l m n) a0 Source #

to1 :: Rep1 (Tuple15 a b c d e f g h i j k l m n) a0 -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, a0) Source #

(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

Instance details

Defined in GHC.Enum

Methods

minBound :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source #

maxBound :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source #

Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source # 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)

Since: base-4.16.0.0

Instance details

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))))))

Methods

from :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) x Source #

to :: Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) x -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source #

(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

Instance details

Defined in GHC.Ix

Methods

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

Instance details

Defined in GHC.Read

Methods

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

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> ShowS Source #

show :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> String Source #

showList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)] -> ShowS Source #

(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) 
Instance details

Defined in GHC.Classes

Methods

(==) :: (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 #

(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) 
Instance details

Defined in GHC.Classes

Methods

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

Instance details

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

Instance details

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))))))